Excel Macros / VBA (Fixed Asset Program)
Excel Macros / VBA (Fixed Asset Program)
Easy access to the program source code Copy & paste code segments for use in your own Excel macros Example code for those learning to write Excel macros using Visual Basic for Applications (VBA)
Page
If you are using this publication for code segments or for learning how to write Excel macros: This publication includes code written in Visual Basic for Applications (VBA) that carries out the following: Selects a worksheet Inserts a row Eliminates a row Erases data Sorts data Configures spreadsheet reports for printing according to user preferences and enables more than one report to be easily printed on the same worksheet Changes the number format of spreadsheet cells Opens a web page using the default browser Disables cut & paste / cell drag & drop Saves & closes the spreadsheet
Copyright Excel Macros / VBA Fixed Asset Program Copyright 2013 Rupert Parsons This document is licensed under the Creative Commons Attribution Share Alike License version 3. You may copy, distribute and/or modify it under the conditions stipulated in the copyright licence. Click the link below to view the details of the copyright licence which applies to this publication: http://creativecommons.org/licenses/by-sa/3.0/deed.en Important: You can copy and modify code segments contained in this publication for use in your own spreadsheets without any copyright restriction.
Page
Program Structure Worksheet Name Introduction VBA Ref. Button (name or description) VBA Ref. Page No. -
Home Page
HP
Fixed Assets Year End Procedure Program Setup Manual (online) Donate (to charity) Save & Close
11 12 13 14 15 16
FM
Fixed asset category 1 Fixed asset category 2 Fixed asset category 3 Fixed asset category 4 Fixed asset category 5 Fixed asset category 6 Summary of asset movements Home
17 18 19 20 21 22 23 25
YE
Check for errors Move year end balances to prior yr Enter new accounting period Check y/e has been comp correctly Home
26 28 37 38 41
Setup Menu
SM
Name of Company / Organisation Currency Symbol Current Accounting Period Fixed Asset Categories Balance Sheet Account Codes
42 43 44 45 46
Page
VBA Ref. Button (name or description) SM Fixed Asset Locations Depreciation Policies Profit & Loss Account Codes Rounding (depreciation charge) Print Settings (reports) Amounts: no decimal places Amounts: 2 decimal places Home
VBA Ref. SM06 SM07 SM08 SM09 SM10 SM11 SM12 SM13
Page No. 47 48 49 50 51 52 61 70
Documentation
MC
Entering data from another s.sheet Year end procedure New fixed assets Fixed asset disposals Reports Verification of fixed assets Revaluation Impairment Prior year adjustments Cut & paste / cell drag & drop Changing column widths Fixed asset manual (all chapters) Macros / VBA Code Home
MC01 MC02 MC03 MC04 MC05 MC06 MC07 MC08 MC09 MC10 MC11 MC12 MC13 MC14
71 72 73 74 75 76 77 78 79 80 81 82 83
Fixed Asset Category 1 Fixed Asset Category 2 Fixed Asset Category 3 Fixed Asset Category 4 Fixed Asset Category 5 Fixed Asset Category 6
Back Home New Row Delete Row FA Cost Report Depreciation Report NBV Report
84 85 86 87 89 92 95
Page 4
Worksheet Name
VBA Ref. Button (name or description) FA Register Report Dep. Journal Report Dep. Charge Report Cost Centre Report Sort by date Sort by location
Depreciation Journal 1 Depreciation Journal 2 Depreciation Journal 3 Depreciation Journal 4 Depreciation Journal 5 Depreciation Journal 6
FS
Accounting Period
AP
AP01 AP02
114 115
Setup
SU
Back Home Preview (cost report) Preview (depreciation report) Preview (NBV report) Preview (register report) Preview (dep. journal report) Preview (dep. charge report) Preview (cost centre report) Preview (summary report) Preview (error report)
SU01 SU02 SU03 SU04 SU05 SU06 SU07 SU08 SU09 SU10 SU11
116 117 118 121 124 127 130 133 136 139 141
Page
DL
Page
Procedures not linked to command buttons Workbook Procedures (procedure name represents the event which triggers the procedure) Procedure Name Workbook_Open Purpose Show messages & opens on home page Disables cell drag & drop Workbook_BeforeClose Enables cell drag & drop 147 Page No. 146
Worksheet Procedures (procedure name represents the event which triggers the procedure) VBA Worksheet Name: Procedure Name Purpose Worksheet_SheetSelectionChange Disables cut & paste Page No. 147
Page
Named Ranges Worksheet Name Accounting Period Menu Name First_Use Purpose in VBA Code Move year end balances to prior year (selects cell that registers if this has been done before)
Fixed Asset Category 1 Fixed Asset Category 2 Fixed Asset Category 3 Fixed Asset Category 4 Fixed Asset Category 5 Fixed Asset Category 6
FAsset_01 FAsset_02 FAsset_03 FAsset_04 FAsset_05 FAsset_06 FAsset_07 FAsset_08 FAsset_09 FAsset_10 FAsset_11 FAsset_12 FAsset_13 FAsset_14 FAsset_15 FAsset_16 FAsset_17 FAsset_18 FAsset_19 FAsset_20
Insert Row (copies blank row) Insert Row (selects cell, above which row is inserted) Conf. cost report (defines print area) Conf. depreciation report (defines print area) Conf. NBV report (defines print area) Conf. dep. charge report (defines print area) Conf. cost centre report (defines print area) Conf. register report (defines print area) Decimal Places (defines area to search & replace) New Financial Year (copies costs c/f) New Financial Year (pastes costs c/f to b/f column) New Financial Year (copies depreciation c/f) New Financial Year (pastes dep. c/f to b/f column) Sort by date / location (defines sort area) Sort by date / location (defines sort area) Sort by date (selects date column) Sort by location (selects location column) New Financial Year (restores links to dep. charge) New Financial Year (restores links to dep. charge) New Financial Year (restores links to dep. charge)
Depreciation Journal 1 Depreciation Journal 2 Depreciation Journal 3 Depreciation Journal 4 Depreciation Journal 5
Journal
Page
Name
Summary
Setup
Setup_01 Setup_02 Setup_03 Setup_04 Setup_05 Setup_06 Setup_07 Setup_08 Setup_09 Setup_10 Setup_11 Setup_12 Setup_13 Setup_14 Setup_15 Setup_16 Setup_17 Setup_18 Setup_19 Setup_20 Setup_21 Setup_22 Setup_23 Setup_24 Setup_25 Setup_26 Setup_27
Conf. report (fixed asset category 1 name in footer) Conf. report (fixed asset category 2 name in footer) Conf. report (fixed asset category 3 name in footer) Conf. report (fixed asset category 4 name in footer) Conf. report (fixed asset category 5 name in footer) Conf. report (fixed asset category 6 name in footer) Conf. cost report (selects paper size) Conf. cost report (selects orientation) Conf. cost report (selects scaling) Conf. depreciation report (selects paper size) Conf. depreciation report (selects orientation) Conf. depreciation report (selects scaling) Conf. NBV report (selects paper size) Conf. NBV report (selects orientation) Conf. NBV report (selects scaling) Conf. register report (selects paper size) Conf. register report (selects orientation) Conf. register report (selects scaling) Conf. journal report (selects paper size) Conf. journal report (selects orientation) Conf. journal report (selects scaling) Conf. depreciation charge report (selects paper size) Conf. depreciation charge report (selects orientation) Conf. depreciation charge report (selects scaling) Conf. cost centre report (selects paper size) Conf. cost centre report (selects orientation) Conf. cost centre report (selects scaling)
Page 9
Worksheet Name
Purpose in VBA Code Conf. summary report (selects paper size) Conf. summary report (selects orientation) Conf. summary report (selects scaling) Conf. error report (selects paper size) Conf. error report (selects orientation) Conf. error report (selects scaling) Decimal Places (selects rounding cell)
Error Report
Error_No
Check for errors (selects cell that registers the number of errors)
Page 10
Button: Fixed Assets (HP01) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell FM.Activate FM.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 11
Button: Year End Procedure (HP02) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Message MsgBox "Before carrying out the year end procedure, make sure you have a backup copy of this spreadsheet file., 0 + 48, "Year End Procedure" 'Selects worksheet & spreadsheet cell YE.Activate YE.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 12
Button: Program Setup (HP03) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SM.Activate SM.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 13
Button: Manual (HP04) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell MC.Activate MC.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect 'Message MsgBox "You must be connected to the internet to view all documentation supporting this program. All documentation can also be downloaded from the website.", 0 + 64, "Documentation" Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 14
Button: Donate (HP05) 'Function: opens webpage 'Error management On Error GoTo Errors 'Message MsgBox "Your kind donation will be passed on to one or more of my nominated charities. You will be taken to the website which details my nominated charities and where you can make an online donation.", 0 + 64, "Donate" 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://sourceforge.net/donate/?user_id=2152376", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the webpage probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address for feedback and I will send you the web link.", vbOKOnly + vbCritical, "Error"
Page 15
Button: Save & Close (HP06) 'Function: saves & closes spreadsheet 'Error management On Error GoTo Errors 'Function: Enables cell drag & drop Application.CellDragAndDrop = True 'Saves & closes program ActiveWorkbook.Save ActiveWorkbook.Close Exit Sub 'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel is unable to save & close the program and returns the following error message:" & Chr(13) & Chr(13) _ & Err.Description, vbOKOnly + vbCritical, "Error" Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" End Select
Page 16
Button: Fixed asset category 1 (FM01) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell AC1.Activate ActiveWindow.SmallScroll Up:=1000 AC1.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 17
Button: Fixed asset category 2 (FM02) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell AC2.Activate ActiveWindow.SmallScroll Up:=1000 AC2.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 18
Button: Fixed asset category 3 (FM03) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell AC3.Activate ActiveWindow.SmallScroll Up:=1000 AC3.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 19
Button: Fixed asset category 4 (FM04) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell AC4.Activate ActiveWindow.SmallScroll Up:=1000 AC4.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 20
Button: Fixed asset category 5 (FM05) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell AC5.Activate ActiveWindow.SmallScroll Up:=1000 AC5.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 21
Button: Fixed asset category 6 (FM06) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell AC6.Activate ActiveWindow.SmallScroll Up:=1000 AC6.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 22
Button: Summary of fixed asset movements (FM07) 'Function: configures report for printing 'Declaration of variables Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." _ , 0 + 64, "Reports" 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_28" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_29" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_30" Scaling = ActiveCell.Value 'Selects worksheet FS.Activate 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape
Page 23
'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet FM.Activate Exit Sub 'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 24
Button: Home (FM08) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 25
Button: Check for errors (YE01) 'Function: checks the error count and takes the user to error report if there are 1 or more errors 'Declaration of variables Dim ErrorCount As Integer 'Error management On Error GoTo Errors 'Disables screen updating (flickering) Application.ScreenUpdating = False 'Checks number of errors Application.GoTo Reference:="Error_No" ErrorCount = ActiveCell.Value If ErrorCount = 0 Then GoTo Exit1 'Enables screen updating (flickering) Application.ScreenUpdating = True 'Selects worksheet & spreadsheet cell ER.Activate ER.Range("A6").Select 'Message MsgBox "The program has found & ErrorCount & error(s)." & Chr(13) & Chr(13) & _ The error report on this page provides further details. & Chr(13) & Chr(13) & _ In addition to correcting these errors, a fixed asset reconciliation should be completed for each fixed asset category at the year end (i.e. comparing the total cost & accumulated depreciation carried forward per the spreadsheet reports to the financial accounts and correcting any differences found). _ , 0 + 48, "Error Report" 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub
Page 26
'Exit management Exit1: MsgBox "The program has not found any errors & Chr(13) & Chr(13) & _ However, this does not guarantee that your fixed asset details are error free. It is very important that a fixed asset reconciliation is completed for each fixed asset category at the year end (i.e. comparing the total cost & accumulated depreciation carried forward per the spreadsheet reports to the financial accounts and correcting any differences found). _ , 0 + 64, "Error Report" YE.Activate YE.Range("A1").Select Application.ScreenUpdating = True Exit Sub 'Error management Errors: MsgBox "A problem with the program has been detected. It is possible that the spreadsheet has been modified without reflecting these changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Application.ScreenUpdating = True
Page 27
Button: Move year end balances to prior year (YE02) 'Function: copies & pastes cells 'Declaration of variables Dim ErrorCount As Integer Dim Answer As Integer Dim CellRange1 As String Dim CellRange2 As String 'Error management On Error GoTo Errors 'Disables screen updating (flickering) Application.ScreenUpdating = False 'Checks for errors Application.GoTo Reference:="Error_No" ErrorCount = ActiveCell.Value If ErrorCount > 0 Then Answer = MsgBox ("The program has found & ErrorCount & error(s). Do you want to proceed? & Chr(13) & Chr(13) & _ Click Yes to confirm that you want to move year end costs & accumulated depreciation to the prior year (not recommended as errors will be bought forward into the new financial year). & Chr(13) & Chr(13) & _ Click No to cancel & view error report which provides further details of the errors found (recommended). _ , 4 + 48, "Warning") If Answer = 7 Then GoTo Exit1 End If 'Checks if new financial procedure has been run for the first time Application.GoTo Reference:="First_Use" If ActiveCell.Text = Yes Then Answer = MsgBox (This is the first time you have run the year end procedure. Have you entered all your existing fixed asset details? & Chr(13) & Chr(13) & _
Page 28
Click Yes to confirm that you have copied / entered all your existing fixed asset details including depreciation brought forward. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 32, "Confirm") If Answer = 7 Then GoTo Exit2 End If 'Confirms operation Answer = MsgBox (The program will move, for each fixed asset, the year end cost and accumulated depreciation to the prior year. Also any links to the calculated depreciation charge that were broken due to the calculated charge being overridden will be restored. For further details go the fixed asset manual (chapter Year End Procedure). Do you want to proceed? & Chr(13) & Chr(13) & _ Click Yes to confirm. (this may take a few moments to complete) & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 32, "Confirm Operation") If Answer = 7 Then GoTo Exit2 'Changes cursor to an hour glass Application.Cursor = xlWait 'Shows status bar Application.DisplayStatusBar = True Application.StatusBar = "Moving year end balances to prior year..." ---------------------------------------------------------------------------------------------------------------------------------Worksheet: AC1 (Fixed Asset Category 1) 'Selects worksheet AC1.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Copies & pastes the year end costs to prior year Application.GoTo Reference:="FAsset_10" Selection.Copy Application.GoTo Reference:="FAsset_11" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _
Page 29
False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Copies & pastes the year end accumulated depreciation to prior year Application.GoTo Reference:="FAsset_12" Selection.Copy Application.GoTo Reference:="FAsset_13" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _ False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Restores any links that were broken due to the depreciation charge being manually overridden Application.GoTo Reference:="FAsset_18" Selection.Copy Application.GoTo Reference:="FAsset_19" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_20" Selection.Offset(-1, 0).Select CellRange2 = ActiveCell.Address AC1.Range(CellRange1 & ":" & CellRange2).Select ActiveSheet.Paste 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------Worksheet: AC2 (Fixed Asset Category 2) 'Selects worksheet AC2.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Copies & pastes the year end costs to prior year Application.GoTo Reference:="FAsset_10" Selection.Copy Application.GoTo Reference:="FAsset_11" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _
Page 30
False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Copies & pastes the year end accumulated depreciation to prior year Application.GoTo Reference:="FAsset_12" Selection.Copy Application.GoTo Reference:="FAsset_13" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _ False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Restores any links that were broken due to the depreciation charge being manually overridden Application.GoTo Reference:="FAsset_18" Selection.Copy Application.GoTo Reference:="FAsset_19" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_20" Selection.Offset(-1, 0).Select CellRange2 = ActiveCell.Address AC2.Range(CellRange1 & ":" & CellRange2).Select ActiveSheet.Paste 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------Worksheet: AC3 (Fixed Asset Category 3) 'Selects worksheet AC3.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Copies & pastes the year end costs to prior year Application.GoTo Reference:="FAsset_10" Selection.Copy Application.GoTo Reference:="FAsset_11" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _
Page 31
False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Copies & pastes the year end accumulated depreciation to prior year Application.GoTo Reference:="FAsset_12" Selection.Copy Application.GoTo Reference:="FAsset_13" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _ False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Restores any links that were broken due to the depreciation charge being manually overridden Application.GoTo Reference:="FAsset_18" Selection.Copy Application.GoTo Reference:="FAsset_19" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_20" Selection.Offset(-1, 0).Select CellRange2 = ActiveCell.Address AC3.Range(CellRange1 & ":" & CellRange2).Select ActiveSheet.Paste 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------Worksheet: AC4 (Fixed Asset Category 4) 'Selects worksheet AC4.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Copies & pastes the year end costs to prior year Application.GoTo Reference:="FAsset_10" Selection.Copy Application.GoTo Reference:="FAsset_11" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _
Page 32
False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Copies & pastes the year end accumulated depreciation to prior year Application.GoTo Reference:="FAsset_12" Selection.Copy Application.GoTo Reference:="FAsset_13" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _ False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Restores any links that were broken due to the depreciation charge being manually overridden Application.GoTo Reference:="FAsset_18" Selection.Copy Application.GoTo Reference:="FAsset_19" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_20" Selection.Offset(-1, 0).Select CellRange2 = ActiveCell.Address AC4.Range(CellRange1 & ":" & CellRange2).Select ActiveSheet.Paste 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------Worksheet: AC5 (Fixed Asset Category 5) 'Selects worksheet AC5.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Copies & pastes the year end costs to prior year Application.GoTo Reference:="FAsset_10" Selection.Copy Application.GoTo Reference:="FAsset_11" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _
Page 33
False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Copies & pastes the year end accumulated depreciation to prior year Application.GoTo Reference:="FAsset_12" Selection.Copy Application.GoTo Reference:="FAsset_13" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _ False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Restores any links that were broken due to the depreciation charge being manually overridden Application.GoTo Reference:="FAsset_18" Selection.Copy Application.GoTo Reference:="FAsset_19" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_20" Selection.Offset(-1, 0).Select CellRange2 = ActiveCell.Address AC5.Range(CellRange1 & ":" & CellRange2).Select ActiveSheet.Paste 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------Worksheet: AC6 (Fixed Asset Category 6) 'Selects worksheet AC6.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Copies & pastes the year end costs to prior year Application.GoTo Reference:="FAsset_10" Selection.Copy Application.GoTo Reference:="FAsset_11" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _
Page 34
False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Copies & pastes the year end accumulated depreciation to prior year Application.GoTo Reference:="FAsset_12" Selection.Copy Application.GoTo Reference:="FAsset_13" Selection.PasteSpecial Paste:=xlValues, Operation:=xlNone, SkipBlanks:= _ False, Transpose:=False Selection.PasteSpecial Paste:=xlPasteFormats, Operation:=xlNone, _ SkipBlanks:=False, Transpose:=False 'Restores any links that were broken due to the depreciation charge being manually overridden Application.GoTo Reference:="FAsset_18" Selection.Copy Application.GoTo Reference:="FAsset_19" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_20" Selection.Offset(-1, 0).Select CellRange2 = ActiveCell.Address AC6.Range(CellRange1 & ":" & CellRange2).Select ActiveSheet.Paste 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Registers that the new year financial procedure has been run one or more times Application.GoTo Reference:="First_Use" ActiveSheet.Unprotect ActiveCell.Value = No ActiveSheet.Protect 'Enables screen updating (flickering) Application.ScreenUpdating = True 'Changes cursor back to default style Application.Cursor = xlDefault 'Hides status bar
Page 35
Application.StatusBar = False 'Message MsgBox "The year end cost and accumulated depreciation balances are now registered as brought forward balances (previous year).", 0 + 64, "Operation Complete" Exit Sub 'Exit management Exit1: Application.ScreenUpdating = True ER.Activate ER.Range("A6").Select ActiveSheet.Protect Exit Sub Exit2: Exit Sub 'Error management Errors: MsgBox "A problem with the program has been detected. It is possible that the spreadsheet has been modified without reflecting these changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" ActiveSheet.Protect Application.ScreenUpdating = True Application.Cursor = xlDefault Application.StatusBar = False
Page 36
Button: Enter new accounting period (YE03) 'Function: takes user to another worksheet 'Declaration of variables Dim Answer As Integer 'Error management On Error GoTo Errors 'Message Answer = MsgBox (It is very important that step 3 has been completed (year end balances moved to the prior year) before entering the new financial year. Have you done step 3? & Chr(13) & Chr(13) & _ Click Yes to confirm. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 48, "New Accounting Period") If Answer = 7 Then GoTo Exit1 'Selects worksheet & spreadsheet cell AP.Activate AP.Range("A26").Select ActiveWindow.SmallScroll Up:=1000 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Exit management Exit1: Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 37
Button: Check year end has been completed correctly (YE04) 'Function: configures report for printing 'Declaration of variables Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "Click OK to view the report Summary of Fixed Asset Movements. Carry out the following checks using this report to confirm whether or not the year end procedure has been completed correctly:" & Chr(13) & Chr(13) & _ Check dates & Chr(13) & Chr(13) & _ Check that the new accounting period appears correctly in the report. If not, go back to step 4 and correct. & Chr(13) & Chr(13) & _ Check balances brought forward & Chr(13) & Chr(13) & _ This report shows the total net book value at the beginning of year. Make sure this amount is equal to the total NBV at the end of the year in the same report for the previous year. To view the equivalent report for the previous year, go the spreadsheet for the previous year and click Fixed Assets on the home page and then click Summary of Fixed Asset Movements. & Chr(13) & Chr(13) & _ If the amounts are different on the two reports, then the year end procedure has not been completed correctly e.g. step 3 was not done, was done twice or was done in the wrong order. To correct, delete this file and carry out the year end procedure again. _ , 0 + 64, "Year End Procedure" 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_28" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_29" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_30" Scaling = ActiveCell.Value 'Selects worksheet
Page 38
FS.Activate 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet YE.Activate YE.Range("A1").Select Exit Sub 'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect
Page 39
changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 40
Button: Home (YE05) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 41
Button: Name of Company / Organisation (SM01) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=0 SU.Range("B9").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 42
Button: Currency Symbol (SM02) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=6 SU.Range("B15").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 43
Button: Current Accounting Period (SM03) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell AP.Activate AP.Range("A26").Select ActiveWindow.SmallScroll Up:=1000 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 44
Button: Fixed Asset Categories (SM04) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=12 SU.Range("Setup_01").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 45
Button: Balance Sheet Account Codes (SM05) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=29 SU.Range("B41").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 46
Button: Fixed Asset Locations (SM06) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=170 SU.Range("B180").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 47
Button: Depreciation Policies (SM07) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=48 'Message MsgBox For each fixed asset category, enter the depreciation policy. Note that the declining balance depreciation method is also known as the reducing balance method. & Chr(13) & Chr(13) & _ For additional details that you may need to register in order to calculate depreciation, these are entered on the fixed asset pages (e.g. salvage value, partial depreciation in first year). You can also determine the depreciation policy per asset on the fixed asset pages. _ , 0 + 64, "Depreciation Policies" 'Selects spreadsheet cell SU.Range("AN59").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 48
Button: Profit & Loss Account Codes (SM08) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=83 SU.Range("AH94").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 49
Button: Rounding (SM09) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=103 SU.Range("Setup_34").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 50
Button: Print Settings (SM10) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=138 SU.Range("AM146").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 51
Button: Amounts no decimal places (SM11) 'Function: Changes the number of decimal places displayed in currency cells from 2 to 0 'Declaration of variables Dim Cell As Range Dim Answer As Integer 'Error management On Error GoTo Errors 'Message Answer = MsgBox("Are you sure that you do not want to display decimal places for amounts?" & Chr(13) & Chr(13) & _ Click Yes to confirm. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 32, "Decimal Places") If Answer = 7 Then GoTo Exit1 'Message MsgBox "Please wait a few moments while the program changes the number of decimal places displayed.", 0 + 64, "Decimal Places" 'Disables screen updating (stop screen flickering) Application.ScreenUpdating = False 'Changes cursor to an hour glass Application.Cursor = xlWait 'Shows status bar Application.DisplayStatusBar = True Application.StatusBar = "Changing the decimal places displayed..." ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC1 (Fixed Asset Category 1) 'Selects worksheet AC1.Activate
Page 52
'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In AC1.Range("FAsset_09") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC2 (Fixed Asset Category 2) 'Selects worksheet AC2.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In AC2.Range("FAsset_09") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC3 (Fixed Asset Category 3) 'Selects worksheet AC3.Activate 'Unprotects worksheet ActiveSheet.Unprotect
Page 53
'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In AC3.Range("FAsset_09") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC4 (Fixed Asset Category 4) 'Selects worksheet AC4.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In AC4.Range("FAsset_09") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC5 (Fixed Asset Category 5) 'Selects worksheet AC5.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0
Page 54
For Each Cell In AC5.Range("FAsset_09") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC6 (Fixed Asset Category 6) 'Selects worksheet AC6.Activate
'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In AC6.Range("FAsset_09") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ1 (Depreciation Journal 1) 'Selects worksheet DJ1.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In DJ1.Range("Journal")
Page 55
If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ2 (Depreciation Journal 2) 'Selects worksheet DJ2.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In DJ2.Range("Journal") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ3 (Depreciation Journal 3) 'Selects worksheet DJ3.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In DJ3.Range("Journal") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell
Page 56
'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ4 (Depreciation Journal 4) 'Selects worksheet DJ4.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In DJ4.Range("Journal") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ5 (Depreciation Journal 5) 'Selects worksheet DJ5.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In DJ5.Range("Journal") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet
Page 57
ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ6 (Depreciation Journal 6) 'Selects worksheet DJ6.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In DJ6.Range("Journal") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: FS (Fixed Asset Summary) 'Selects worksheet FS.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In FS.Range("Summary") If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------Page 58
'Worksheet: SM (Setup Menu) 'Selects worksheet SM.Activate 'Enables screen updating Application.ScreenUpdating = True 'Changes cursor back to default style Application.Cursor = xlDefault 'Hides status bar Application.StatusBar = False Message MsgBox "No decimal places are now displayed for amounts.", 0 + 64, "Decimal Places" 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=103 SU.Range("Setup_34").Select 'Rounds depreciation charges to nearest whole number ActiveCell.Value = 0 'Message MsgBox "As you have chosen not to display decimal places, the depreciation charges will be rounded to the nearest whole number. However, you can change the rounding in the orange cell.", 0 + 64, "Decimal Places" Exit Sub 'Exit management Exit1: Exit Sub
Page 59
'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" ActiveSheet.Protect Application.ScreenUpdating = True Application.Cursor = xlDefault Application.StatusBar = False
Page 60
Button: Amounts 2 decimal places (SM12) 'Function: Changes the number of decimal places displayed in currency cells from 0 to 2 'Declaration of variables Dim Cell As Range Dim Answer As Integer 'Error management On Error GoTo Errors 'Message Answer = MsgBox("Are you sure that you want to display amounts to 2 decimal places? (you only need select this option i.e. click Yes if you have previously selected no decimal places in the setup menu)." & Chr(13) & Chr(13) & _ Click Yes to confirm. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 32, "Decimal Places") If Answer = 7 Then GoTo Exit1 'Message MsgBox "Please wait a few moments while the program changes the number of decimal places displayed.", 0 + 64, "Decimal Places" 'Disables screen updating (stop screen flickering) Application.ScreenUpdating = False 'Changes cursor to an hour glass Application.Cursor = xlWait 'Shows status bar Application.DisplayStatusBar = True Application.StatusBar = "Changing the decimal places displayed..." ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC1 (Fixed Asset Category 1) 'Selects worksheet AC1.Activate
Page 61
'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In AC1.Range("FAsset_09") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC2 (Fixed Asset Category 2) 'Selects worksheet AC2.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In AC2.Range("FAsset_09") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC3 (Fixed Asset Category 3) 'Selects worksheet AC3.Activate 'Unprotects worksheet
Page 62
ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In AC3.Range("FAsset_09") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC4 (Fixed Asset Category 4) 'Selects worksheet AC4.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In AC4.Range("FAsset_09") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC5 (Fixed Asset Category 5) 'Selects worksheet AC5.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2
Page 63
For Each Cell In AC5.Range("FAsset_09") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: AC6 (Fixed Asset Category 6) 'Selects worksheet AC6.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In AC6.Range("FAsset_09") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ1 (Depreciation Journal 1) 'Selects worksheet DJ1.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In DJ1.Range("Journal")
Page 64
If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ2 (Depreciation Journal 2) 'Selects worksheet DJ2.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In DJ2.Range("Journal") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ3 (Depreciation Journal 3) 'Selects worksheet DJ3.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In DJ3.Range("Journal") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell
Page 65
'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ4 (Depreciation Journal 4) 'Selects worksheet DJ4.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In DJ4.Range("Journal") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ5 (Depreciation Journal 5) 'Selects worksheet DJ5.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In DJ5.Range("Journal") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet
Page 66
ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: DJ6 (Depreciation Journal 6) 'Selects worksheet DJ6.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In DJ6.Range("Journal") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Worksheet: FS (Fixed Asset Summary) 'Selects worksheet FS.Activate 'Unprotects worksheet ActiveSheet.Unprotect 'Changes the number of decimal places displayed in currency cells from 0 a 2 For Each Cell In FS.Range("Summary") If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protects worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------Page 67
'Worksheet: SM (Setup Menu) 'Selects worksheet SM.Activate 'Enables screen updating Application.ScreenUpdating = True 'Changes cursor back to default style Application.Cursor = xlDefault 'Hides status bar Application.StatusBar = False Message MsgBox "Amounts are now displayed to 2 decimal places.", 0 + 64, "Decimal Places" 'Selects worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=103 SU.Range("Setup_34").Select 'Rounds depreciation charges to 2 decimal places ActiveCell.Value = 2 'Message MsgBox "As you have chosen to display amounts to 2 decimal places, the depreciation charges will be rounded to 2 decimal places. However, you can change the rounding in the orange cell.", 0 + 64, "Decimal Places" Exit Sub 'Exit management Exit1: Exit Sub
Page 68
'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" ActiveSheet.Protect Application.ScreenUpdating = True Application.Cursor = xlDefault Application.StatusBar = False
Page 69
Button: Home (SM13) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 70
Button: Entering data from another spreadsheet (MC01) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137551108/Enteringcopying-data-from-another-spreadsheet", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 71
Button: Year end procedure (MC02) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137552830/Year-EndProcedure", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 72
Button: New fixed assets (MC03) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137554125/New-FixedAssets", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 73
Button: Fixed asset disposals (MC04) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137555299/Fixed-AssetDisposals", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 74
Button: Reports (MC05) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137556943/Reports", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 75
Button: Verification of fixed assets (MC06) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137559159/Verificationof-Fixed-Assets", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 76
Button: Revaluation (MC07) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137560194/Revaluationof-Fixed-Assets", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 77
Button: Impairment (MC08) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137562571/Impairmentof-Fixed-Assets", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 78
Button: Prior year adjustments (MC09) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137564107/Prior-MonthPrior-Year-Adjustments", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 79
Button: Cut & paste / cell drag & drop (MC10) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137568203/Cut-PasteCell-Drag-Drop-disabled", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 80
Button: Changing column widths (MC11) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137569410/Columnschanging-widths-adding-deleting", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 81
Button: Fixed asset manual (MC12) 'Function: opens webpage 'Error management On Error GoTo Errors 'Opens webpage in default browser ThisWorkbook.FollowHyperlink Address:="http://www.scribd.com/doc/137548960/Fixed-AssetManual", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the web page probably due to the fact that your computer is not connected to the internet. Check your internet connection and try again. & Chr(13) & Chr(13) & _ If your internet connection is working and you still receive this error message, then write to me at the email address under Feedback on the home page and I will send you the web link for the manual chapter.", vbOKOnly + vbCritical, "Error"
Page 82
Button: Home (MC14) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 83
Button: Back (FA01) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell FM.Activate FM.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 84
Button: Home (FA02) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 85
Button: New Row (FA03) 'Function: inserts new row 'Error management On Error GoTo Errors 'Unprotects worksheet ActiveSheet.Unprotect 'Inserts new row Application.GoTo Reference:="FAsset_02" Selection.EntireRow.Insert 'Selects & copies blank row Application.GoTo Reference:="FAsset_01" Selection.Copy 'Selects new row and pastes blank row into new row Application.GoTo Reference:= "FAsset_02" ActiveCell.Offset(-1, 0).Select ActiveSheet.Paste 'Protects worksheet ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" ActiveSheet.Protect
Page 86
Button: Delete Row (FA04) 'Function: deletes selected row 'Declaration of variables Dim CellRange1 As String Dim CellRange2 As String Dim Answer As Integer 'Error management On Error GoTo Errors 'Message Answer = MsgBox (Have you selected a spreadsheet cell of the row you want to delete? (you can only delete fixed asset rows). & Chr(13) & Chr(13) & _ Click Yes to confirm. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 32, "Delete Row) If Answer = 7 Then GoTo Exit1 'Check selected row is a fixed asset row Do Until Mid(ActiveCell.Address, 2, 2) = "A$" ActiveCell.Offset(0, -1).Select Loop If ActiveCell.Text <> A Then GoTo Exit2 'Highlight row for deletion ActiveCell.Offset(0, 1).Select CellRange1 = ActiveCell.Address ActiveCell.Offset(0, 29).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select 'Message
Page 87
Answer = MsgBox (Are you sure that you want to delete this row? (assets should be deleted after the year of disposal). & Chr(13) & Chr(13) & _ Click Yes to confirm. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 48, "Delete Row") If Answer = 7 Then GoTo Exit1 'Deletes selected row ActiveSheet.Unprotect Selection.EntireRow.Delete ActiveSheet.Protect 'Message MsgBox "The selected row has been deleted.", 0 + 64, "Delete Row" Exit Sub 'Exit management Exit1: Exit Sub Exit2: ActiveCell.Offset(0, 1).Select MsgBox "You have not selected a fixed asset row." & Chr(13) & Chr(13) & _ (you indicate which row by first selecting the spreadsheet cell of the row you want to delete, then click Delete Row). _ , 0 + 16, "Error" Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" ActiveSheet.Protect
Page 88
Button: FA Cost Report (FA05) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to configure the report. _ , 0 + 64, "Reports" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_02" for fixed asset category 2 Application.GoTo Reference:="Setup_03" for fixed asset category 3 Application.GoTo Reference:="Setup_04" for fixed asset category 4 Application.GoTo Reference:="Setup_05" for fixed asset category 5 Application.GoTo Reference:="Setup_06" for fixed asset category 6 Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_07" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_08" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_09" Scaling = ActiveCell.Value 'Selects worksheet
Page 89
'AC2.Activate for fixed asset category 2 'AC3.Activate for fixed asset category 3 'AC4.Activate for fixed asset category 4 'AC5.Activate for fixed asset category 5 'AC6.Activate for fixed asset category 6 AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup .PrintArea = "FAsset_03" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview Exit Sub
Page 90
'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 91
Button: Depreciation Report (FA06) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to configure the report. _ , 0 + 64, "Reports" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_02" for fixed asset category 2 Application.GoTo Reference:="Setup_03" for fixed asset category 3 Application.GoTo Reference:="Setup_04" for fixed asset category 4 Application.GoTo Reference:="Setup_05" for fixed asset category 5 Application.GoTo Reference:="Setup_06" for fixed asset category 6 Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_10" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_11" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_12" Scaling = ActiveCell.Value 'Selects worksheet
Page 92
'AC2.Activate for fixed asset category 2 'AC3.Activate for fixed asset category 3 'AC4.Activate for fixed asset category 4 'AC5.Activate for fixed asset category 5 'AC6.Activate for fixed asset category 6 AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup .PrintArea = "FAsset_04" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview Exit Sub
Page 93
'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 94
Button: NBV Report (FA07) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to configure the report. _ , 0 + 64, "Reports" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_02" for fixed asset category 2 Application.GoTo Reference:="Setup_03" for fixed asset category 3 Application.GoTo Reference:="Setup_04" for fixed asset category 4 Application.GoTo Reference:="Setup_05" for fixed asset category 5 Application.GoTo Reference:="Setup_06" for fixed asset category 6 Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_13" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_14" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_15" Scaling = ActiveCell.Value 'Selects worksheet
Page 95
'AC2.Activate for fixed asset category 2 'AC3.Activate for fixed asset category 3 'AC4.Activate for fixed asset category 4 'AC5.Activate for fixed asset category 5 'AC6.Activate for fixed asset category 6 AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup .PrintArea = "FAsset_05" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview Exit Sub
Page 96
'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 97
Button: FA Register Report (FA08) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to configure the report. _ , 0 + 64, "Reports" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_02" for fixed asset category 2 Application.GoTo Reference:="Setup_03" for fixed asset category 3 Application.GoTo Reference:="Setup_04" for fixed asset category 4 Application.GoTo Reference:="Setup_05" for fixed asset category 5 Application.GoTo Reference:="Setup_06" for fixed asset category 6 Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_16" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_17" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_18" Scaling = ActiveCell.Value 'Selects worksheet
Page 98
'AC2.Activate for fixed asset category 2 'AC3.Activate for fixed asset category 3 'AC4.Activate for fixed asset category 4 'AC5.Activate for fixed asset category 5 'AC6.Activate for fixed asset category 6 AC1.Activate 'Page Setup (print area & margins left: 1.5 right: 1.5 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup .PrintArea = "FAsset_08" .LeftMargin = Application.InchesToPoints(0.590551181102362) .RightMargin = Application.InchesToPoints(0.590551181102362) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview Exit Sub
Page 99
'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 100
Button: Dep. Journal Report (FA09) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to configure the report. _ , 0 + 64, "Reports" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_02" for fixed asset category 2 Application.GoTo Reference:="Setup_03" for fixed asset category 3 Application.GoTo Reference:="Setup_04" for fixed asset category 4 Application.GoTo Reference:="Setup_05" for fixed asset category 5 Application.GoTo Reference:="Setup_06" for fixed asset category 6 Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_19" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_20" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_21" Scaling = ActiveCell.Value 'Selects worksheet
Page 101
'DJ2.Activate for fixed asset category 2 'DJ3.Activate for fixed asset category 3 'DJ4.Activate for fixed asset category 4 'DJ5.Activate for fixed asset category 5 'DJ6.Activate for fixed asset category 6 DJ1.Activate 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet 'AC2.Activate for fixed asset category 2 'AC3.Activate for fixed asset category 3 'AC4.Activate for fixed asset category 4 'AC5.Activate for fixed asset category 5 'AC6.Activate for fixed asset category 6 AC1.Activate Exit Sub
Page 102
'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 103
Button: Dep. Charge Report (FA10) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to configure the report. _ , 0 + 64, "Reports" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_02" for fixed asset category 2 Application.GoTo Reference:="Setup_03" for fixed asset category 3 Application.GoTo Reference:="Setup_04" for fixed asset category 4 Application.GoTo Reference:="Setup_05" for fixed asset category 5 Application.GoTo Reference:="Setup_06" for fixed asset category 6 Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_22" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_23" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_24" Scaling = ActiveCell.Value 'Selects worksheet
Page 104
'AC2.Activate for fixed asset category 2 'AC3.Activate for fixed asset category 3 'AC4.Activate for fixed asset category 4 'AC5.Activate for fixed asset category 5 'AC6.Activate for fixed asset category 6 AC1.Activate 'Page Setup (print area & margins left: 1.5 right: 1.5 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup .PrintArea = "FAsset_06" .LeftMargin = Application.InchesToPoints(0.590551181102362) .RightMargin = Application.InchesToPoints(0.590551181102362) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview Exit Sub
Page 105
'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 106
Button: Cost Centre Report (FA11) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to configure the report. _ , 0 + 64, "Reports" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_02" for fixed asset category 2 Application.GoTo Reference:="Setup_03" for fixed asset category 3 Application.GoTo Reference:="Setup_04" for fixed asset category 4 Application.GoTo Reference:="Setup_05" for fixed asset category 5 Application.GoTo Reference:="Setup_06" for fixed asset category 6 Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_25" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_26" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_27" Scaling = ActiveCell.Value 'Selects worksheet
Page 107
'AC2.Activate for fixed asset category 2 'AC3.Activate for fixed asset category 3 'AC4.Activate for fixed asset category 4 'AC5.Activate for fixed asset category 5 'AC6.Activate for fixed asset category 6 AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup .PrintArea = "FAsset_07" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview Exit Sub
Page 108
'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 109
Button: Sort by date (FA12) 'Function: sorts fixed assets into date order 'Declaration of Variables Dim Answer As Integer Dim CellRange1 As String Dim CellRange2 As String 'Error management On Error GoTo Errors 'Check there is at least one row Application.GoTo Reference:="FAsset_02" ActiveCell.Offset(-1, 0).Select If ActiveCell.Text <> A Then GoTo Exit1 'Message ActiveCell.Offset(0, 1).Select Answer = MsgBox("Fixed assets will be displayed from oldest to the most recent. Are you sure that you want to proceed?" & Chr(13) & Chr(13) & _ Click Yes to confirm. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 32, "Sort by date") If Answer = 7 Then GoTo Exit2 'Unprotects worksheet ActiveSheet.Unprotect 'Defines range of cells to sort Application.GoTo Reference:="FAsset_14" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_15" CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select 'Sorts fixed assets by date
Page 110
Selection.Sort Key1:=Range(FAsset_16).Offset(1,0), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Protects worksheet ActiveSheet.Protect 'Selects cell A1 ActiveWindow.SmallScroll Up:=1000 ActiveSheet.Range("A1").Select Message MsgBox "Fixed Assets have been sorted by date.", 0 + 64, "Sort by date" Exit Sub 'Exit management Exit1: ActiveCell.Offset(0, 1).Select MsgBox "There are no rows to sort." _ , 0 + 16, "Error" Exit Sub Exit2: Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" ActiveSheet.Protect
Page 111
Button: Sort by location (FA13) 'Function: sorts fixed assets by location 'Declaration of Variables Dim Answer As Integer Dim CellRange1 As String Dim CellRange2 As String 'Error management On Error GoTo Errors 'Check there is at least one row Application.GoTo Reference:="FAsset_02" ActiveCell.Offset(-1, 0).Select If ActiveCell.Text <> A Then GoTo Exit1 'Message ActiveCell.Offset(0, 8).Select Answer = MsgBox("Fixed assets will be grouped by location. Are you sure that you want to proceed?" & Chr(13) & Chr(13) & _ Click Yes to confirm. & Chr(13) & Chr(13) & _ Click No to cancel. _ , 4 + 32, "Sort by location") If Answer = 7 Then GoTo Exit2 'Unprotects worksheet ActiveSheet.Unprotect 'Defines range of cells to sort Application.GoTo Reference:="FAsset_14" Selection.Offset(1, 0).Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="FAsset_15" CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select 'Sorts fixed assets by date
Page 112
Selection.Sort Key1:=Range(FAsset_17).Offset(1,0), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Protects worksheet ActiveSheet.Protect 'Selects cell A1 ActiveWindow.SmallScroll Up:=1000 ActiveSheet.Range("A1").Select Message MsgBox "Fixed Assets have been sorted by location.", 0 + 64, "Sort by location" Exit Sub 'Exit management Exit1: ActiveCell.Offset(0, 1).Select MsgBox "There are no rows to sort." _ , 0 + 16, "Error" Exit Sub Exit2: Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" ActiveSheet.Protect
Page 113
Button: Setup (AP01) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SM.Activate SM.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 114
Button: Year End Procedure (AP02) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell YE.Activate YE.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 115
Button: Back (SU01) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell SM.Activate 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 116
Button: Home (SU02) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 117
Button: Preview Cost Report (SU03) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to prepare the preview. _ , 0 + 64, "Report Preview" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_07" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_08" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_09" Scaling = ActiveCell.Value 'Selects worksheet AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup
Page 118
.PrintArea = "FAsset_03" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=138 Exit Sub 'Error management Errors:
Page 119
Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 120
Button: Preview Depreciation Report (SU04) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to prepare the preview. _ , 0 + 64, "Report Preview" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_10" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_11" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_12" Scaling = ActiveCell.Value 'Selects worksheet AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup
Page 121
.PrintArea = "FAsset_04" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=138 Exit Sub 'Error management Errors:
Page 122
Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 123
Button: Preview NBV Report (SU05) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to prepare the preview. _ , 0 + 64, "Report Preview" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_13" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_14" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_15" Scaling = ActiveCell.Value 'Selects worksheet AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup
Page 124
.PrintArea = "FAsset_05" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=138 Exit Sub 'Error management Errors:
Page 125
Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 126
Button: Preview Register Report (SU06) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to prepare the preview. _ , 0 + 64, "Report Preview" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_16" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_17" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_18" Scaling = ActiveCell.Value 'Selects worksheet AC1.Activate 'Page Setup (print area & margins left: 1.5 right: 1.5 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup
Page 127
.PrintArea = "FAsset_08" .LeftMargin = Application.InchesToPoints(0.590551181102362) .RightMargin = Application.InchesToPoints(0.590551181102362) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=138 Exit Sub 'Error management Errors:
Page 128
Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 129
Button: Preview Dep. Journal Report (SU07) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to prepare the preview. _ , 0 + 64, "Report Preview" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_19" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_20" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_21" Scaling = ActiveCell.Value 'Selects worksheet DJ1.Activate 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4
Page 130
If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=138 Exit Sub 'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub
Page 131
Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 132
Button: Preview Dep. Charge Report (SU08) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to prepare the preview. _ , 0 + 64, "Report Preview" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_22" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_23" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_24" Scaling = ActiveCell.Value 'Selects worksheet AC1.Activate 'Page Setup (print area & margins left: 1.5 right: 1.5 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup
Page 133
.PrintArea = "FAsset_06" .LeftMargin = Application.InchesToPoints(0.590551181102362) .RightMargin = Application.InchesToPoints(0.590551181102362) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=138 Exit Sub 'Error management Errors:
Page 134
Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 135
Button: Preview Cost Centre Report (SU09) 'Function: configures report for printing 'Declaration of variables Dim Footer As String Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." & Chr(13) & Chr(13) & _ Please wait a few moments for the program to prepare the preview. _ , 0 + 64, "Report Preview" 'Selects fixed asset category name for report footer Application.GoTo Reference:="Setup_01" Footer = ActiveCell.Text 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_25" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_26" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_27" Scaling = ActiveCell.Value 'Selects worksheet AC1.Activate 'Page Setup (print area & margins left: 2.0 right: 2.0 top: 2.0 bottom: 2.0) With ActiveSheet.PageSetup
Page 136
.PrintArea = "FAsset_07" .LeftMargin = Application.InchesToPoints(0.78740157480315) .RightMargin = Application.InchesToPoints(0.78740157480315) .TopMargin = Application.InchesToPoints(0.78740157480315) .BottomMargin = Application.InchesToPoints(0.78740157480315) End With 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape 'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'If fixed asset category name contains &, replaces this with && so that the name appears correctly in report footer Footer = Replace(Footer, "&", "&&") 'Page Setup (footer) ActiveSheet.PageSetup.LeftFooter = Footer 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=147 Exit Sub 'Error management Errors:
Page 137
Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 138
Button: Preview Summary Report (SU10) 'Function: configures report for printing 'Declaration of variables Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." _ , 0 + 64, "Report Preview" 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_28" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_29" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_30" Scaling = ActiveCell.Value 'Selects worksheet FS.Activate 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape
Page 139
'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=147 Exit Sub 'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 140
Button: Preview Error Report (SU11) 'Function: configures report for printing 'Declaration of variables Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You will see a preview of how the report will look based on the selections you have made (paper size, orientation & scaling)." _ , 0 + 64, "Report Preview" 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_31" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_32" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_33" Scaling = ActiveCell.Value 'Selects worksheet ER.Activate 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape
Page 141
'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview 'Selects worksheet SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select SU.Range("E1").Select ActiveWindow.SmallScroll Down:=147 Exit Sub 'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 142
Button: Back (ER01) 'Function: takes user to another worksheet 'Error management On Error GoTo Errors 'Selects worksheet & spreadsheet cell YE.Activate YE.Range("A1").Select 'Ensures worksheet is protected ActiveSheet.Protect Exit Sub 'Error management Errors: MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 143
Button: Print (ER02) 'Function: configures report for printing 'Declaration of variables Dim Paper As String Dim Orientation As String Dim Scaling As Integer 'Error management On Error GoTo Errors 'Message MsgBox "The program configures the report (paper size, orientation & scaling) according to the selections made in the setup menu (print settings)." _ , 0 + 64, "Reports" 'Registers paper size selected in program setup (print settings) Application.GoTo Reference:="Setup_31" Paper = ActiveCell.Text 'Registers orientation selected in program setup (print settings) Application.GoTo Reference:="Setup_32" Orientation = ActiveCell.Text 'Registers scaling selected in program setup (print settings) Application.GoTo Reference:="Setup_33" Scaling = ActiveCell.Value 'Selects worksheet ER.Activate 'Page Setup (paper size) If Paper = "A4" Then ActiveSheet.PageSetup.PaperSize = xlPaperA4 If Paper = "Letter" Then ActiveSheet.PageSetup.PaperSize = xlPaperLetter If Paper = "Legal" Then ActiveSheet.PageSetup.PaperSize = xlPaperLegal 'Page Setup (orientation) If Orientation = "Portrait" Then ActiveSheet.PageSetup.Orientation = xlPortrait If Orientation = "Landscape" Then ActiveSheet.PageSetup.Orientation = xlLandscape
Page 144
'Page Setup (scaling) If Scaling <> 0 Then ActiveSheet.PageSetup.Zoom = Scaling 'Shows report in print preview ActiveWindow.SelectedSheets.PrintPreview Exit Sub 'Error management Errors: Select Case Err.Number Case 1004 MsgBox "Excel has returned the following error message:" & Chr(13) & Chr(13) _ & Err.Description & Chr(13) & Chr(13) _ & "It is possible that the there is a problem with the printer driver.", _ vbOKOnly + vbCritical, "Error" Exit Sub Case Else MsgBox "There is a problem with the macro associated with this button. It is possible that the spreadsheet has been modified without reflecting the changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error" Exit Sub End Select
Page 145
Procedure Name: Workbook_Open 'Function: Shows message & opens program on the home page 'Error management On Error GoTo Errors 'Disables cell drag & drop Application.CellDragAndDrop = False 'Select worksheet HP.Activate 'Ensures worksheet is protected ActiveSheet.Protect 'Message MsgBox "Fixed Asset Program Version 3" & Chr(13) & _ "Copyright 2013 Rupert Parsons" & Chr(13) & Chr(13) & _ "The program is licensed under the Creative Commons Attribution Share Alike License version 3. You may copy, distribute and/or modify this program under the conditions stipulated in the copyright licence. For further details, click the Introduction tab and go to the Copyright section." _ ,0 + 64, "Program Version & Copyright" 'Selects spreadsheet cell HP.Range("A1").Select Exit Sub 'Error management Errors: MsgBox "A problem with the program has been detected. It is possible that the spreadsheet has been modified without reflecting these changes in the program code or incorrect changes have been made to the program code. It is recommended that you download the program again.", vbOKOnly + vbCritical, "Error"
Page 146
Procedure Name: Workbook_BeforeClose 'Function: Enables cell drag & drop Application.CellDragAndDrop = True
Procedure Name: Worksheet_SelectionChange 'Function: Disables cut & paste / cell drag & drop If Application.CutCopyMode = xlCut Then Application.CutCopyMode = False End If
----------------------------------------------------------------------------------------------------------------------------------End of document
Page 147