Вы находитесь на странице: 1из 54

Excel Macros / VBA Bank Reconciliation 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 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 Bank Reconciliation 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 VBA Ref. Page No. -

Home Page

HP

Bank Rec. Setup Manual (online) Copyright Donate (online) Save & Close

HP01 HP02 HP03 HP04 HP05 HP06

8 9 10 11 12 13

Setup Menu

MS

Name of Company / Organisation Bank Account Name Currency Symbol Currency: no decimal places Currency: 2 decimal places Drop Down Lists Home

MS01 MS02 MS03 MS04 MS05 MS06 MS07

14 15 16 17 22 27 28

Bank Rec. Menu

MR

Enter month & year Enter bank balance Bank Reconciliation Print bank reconciliation (format 1) Print bank reconciliation (format 2) Home

MR01 MR02 MR03 MR04 MR05 MR06

29 30 31 32 33 34

Bank Reconciliation Page

BRP

Back Sort by date Insert Row Delete Last Row Insert Row

BR01 BR02 BR03 BR04 BR05

35 36 39 39 39

Page

Worksheet Name Bank Reconciliation Page

VBA Ref. Button BRP Delete Last Row Insert Row Delete Last Row Insert Row Delete Last Row Insert Row Delete Last Row Insert Row Delete Last Row

VBA Ref. BR06 BR07 BR08 BR09 BR10 BR11 BR12 BR13 BR14

Page No. 39 40 40 40 40 41 41 41 41

Bank Reconciliation Report (1)

BRR1

Bank Reconciliation Report (2)

BRR2

Monthly Data

MD

Back Home

MD01 MD02

42 43

Setup

SU

Back Home

SU01 SU02

44 45

Drop Down Lists

DL

Page

Procedures not linked to command buttons

Called Procedures

Procedure Name InsertRow DeleteRow EraseData

Purpose Inserts new row Deletes row Erases data from row

Page No. 46 48 50

Worksheet Procedures (procedure name represents the event which triggers the procedure) VBA Worksheet Name: Procedure Name Purpose Worksheet_Change Calls procedure EraseData when Erase entry is selected in the down list of the observation cell. Worksheet_SelectionChange Disables cut & paste 52 Page No. 52

Workbook Procedures (procedure name represents the event which triggers the procedure) Procedure Name Workbook_Open Purpose Show message & open on home page Disables cell drag & drop Workbook_BeforeClose Enables cell drag & drop 54 Page No. 53

Page

Named Ranges Worksheet Name Bank Reconciliation Page (section 1) Name BRPS1Copy BRPS1Sort_1 BRPS1Sort_2 BRPS1FRow Purpose in VBA Code Insert rows (defines copy range) Sort by date (defines sort area) Sort by date (defines sort area) Insert rows (locates first row)

Bank Reconciliation Page (section 2)

BRPS2Copy BRPS2Sort_1 BRPS2Sort_2 BRPS2FRow

Insert rows (defines copy range) Sort by date (defines sort area) Sort by date (defines sort area) Insert rows (locates first row)

Bank Reconciliation Page (section 3)

BRPS3Copy BRPS3Sort_1 BRPS3Sort_2 BRPS3FRow

Insert rows (defines copy range) Sort by date (defines sort area) Sort by date (defines sort area) Insert rows (locates first row)

Bank Reconciliation Page (section 4)

BRPS4Copy BRPS4Sort_1 BRPS4Sort_2 BRPS4FRow

Insert rows (defines copy range) Sort by date (defines sort area) Sort by date (defines sort area) Insert rows (locates first row)

Bank Reconciliation Page (section 5)

BRPS5Copy BRPS5Sort_1 BRPS5Sort_2 BRPS5FRow

Insert rows (defines copy range) Sort by date (defines sort area) Sort by date (defines sort area) Insert rows (locates first row)

Bank Reconciliation Page (section 6)

BRPS6Copy BRPS6Sort_1 BRPS6Sort_2 BRPS6FRow

Insert rows (defines copy range) Sort by date (defines sort area) Sort by date (defines sort area) Insert rows (locates first row)

Page

Worksheet Name Bank Reconciliation Page (all sections)

Name BRPDec_1 BRPDec_2

Purpose in VBA Code Change decimal places (defines cell range) Change decimal places (defines cell range)

Bank Reconciliation Report (1)

BRR1S1Copy BRR1S2Copy BRR1S3Copy BRR1S4Copy BRR1S5Copy BRR1S6Copy BRR1Dec_1 BRR1Dec_2

Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Change decimal places (defines cell range) Change decimal places (defines cell range) Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Insert rows (defines copy range) Change decimal places (defines cell range) Change decimal places (defines cell range)

Bank Reconciliation Report (2)

BRR2S1Copy BRR2S2Copy BRR2S3Copy BRR2S4Copy BRR2S5Copy BRR2S6Copy BRR2Dec_1 BRR2Dec_2

Monthly Data

MDDec_1 MDDec_2

Change decimal places (defines cell range) Change decimal places (defines cell range)

Page

Button: Bank Rec. (HP01) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell MR.Activate MR.Range("A1").Select 'Make sure 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

Button: Setup (HP02) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell MS.Activate MS.Range("A1").Select 'Make sure 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

Button: Manual Online (HP03) 'Function: Opens webpage 'Declaration of variables Dim Answer As Integer 'Error management On Error GoTo Errors 'Message MsgBox "You must be connected to the internet to view the manual." & Chr(13) & Chr(13) & "If you are already familiar with bank reconciliations, the short chapter 'Bank Reconciliation Page' is all you should have to read in order to use the program." & Chr(13) & Chr(13) & "If you are using this program to learn how to do a bank reconciliation, the key chapter is 'Bank Reconciliation: Step by Step'.", 0 + 64, "Bank Reconciliation Manual" 'View manual online ThisWorkbook.FollowHyperlink Address:=" http://www.scribd.com/doc/136210927/BankReconciliation-Manual", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the manual online 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 are still unable to view the manual online using this button, go to my account in Scribd (Rupert Parsons), then select the document 'Bank Reconciliation Manual' under Published or the collection Accounting (Bank Recs)", vbOKOnly + vbCritical, "Error"

Page 10

Button: Copyright (HP04) 'Function: Opens webpage 'Error management On Error GoTo Errors 'Message MsgBox "You must be connected to the internet to view the copyright details.", 0 + 64, "Copyright details" 'View copyright online ThisWorkbook.FollowHyperlink Address:="http://creativecommons.org/licenses/bysa/3.0/deed.en", NewWindow:=True Exit Sub 'Error management Errors: MsgBox "The program was unable to access the copyright licence online 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 are still unable to view the copyright licence online using this button, select the spreadsheet tab Introduction and then click the link in the Copyright section.", vbOKOnly + vbCritical, "Error"

Page 11

Button: Donate Online (HP05) 'Function: Opens webpage 'Error management On Error GoTo Errors 'Message MsgBox "Many thanks for donating. You will be taken to the website where you can make an online donation. Your kind donation will be passed on to one or more of my nominated charities. Further details are given on the website.", 0 + 64, "Donation" 'View copyright online 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 copyright licence online 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 are still unable to view the copyright licence online using this button, select the spreadsheet tab Introduction and then click the link in the Copyright section.", vbOKOnly + vbCritical, "Error"

Page 12

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 13

Button: Name of Company / Organisation (MS01) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=0 SU.Range("B9").Select 'Make sure 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 14

Button: Bank Account Name (MS02) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=6 SU.Range("B15").Select 'Make sure 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 15

Button: Currency Symbol (MS03) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=12 SU.Range("B21").Select 'Make sure 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 16

Button: Currency no decimal places (MS04) 'Function: Changes the number of decimal places displayed in currency cells from 2 to 0 'Declaration of variables Dim CellRange1 As String Dim CellRange2 As String 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" 'Disable screen updating (stop screen flickering) Application.ScreenUpdating = False 'Change cursor to an hour glass Application.Cursor = xlWait 'Show status bar Application.DisplayStatusBar = True Application.StatusBar = "Changing the decimal places displayed..." ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: BRP BRP.Activate

Page 17

'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed BRP.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="BRPDecimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet ActiveSheet.Unprotect 'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In BRP.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protect worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: BRR1 BRR1.Activate 'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed BRR1.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="BRR1Decimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet ActiveSheet.Unprotect 'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In BRR1.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protect worksheet
Page 18

ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: BRR2 BRR2.Activate 'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed BRR2.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="BRR2Decimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet ActiveSheet.Unprotect 'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In BRR2.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protect worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: MD MD.Activate 'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed MD.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="MDDecimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet ActiveSheet.Unprotect
Page 19

'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In MD.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,##0.00;(#,##0.00);""-""" Then Cell.NumberFormat = "#,###;(#,###);""""" Next Cell 'Protect worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: MS MS.Activate 'Enable screen updating Application.ScreenUpdating = True 'Change cursor back to default style Application.Cursor = xlDefault 'Hide status bar Application.StatusBar = False Message MsgBox "No decimal places are now displayed for amounts.", 0 + 64, "Decimal Places" Exit Sub 'Error management Exit1: Exit Sub 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

ActiveSheet.Protect Application.ScreenUpdating = True Application.Cursor = xlDefault Application.StatusBar = False

Page 21

Button: Currency 2 decimal places (MS05) 'Function: Changes the number of decimal places displayed in currency cells to 2 decimal places 'Declaration of variables Dim CellRange1 As String Dim CellRange2 As String 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" 'Disable screen updating (stop screen flickering) Application.ScreenUpdating = False 'Change cursor to an hour glass Application.Cursor = xlWait 'Show status bar Application.DisplayStatusBar = True Application.StatusBar = "Changing the decimal places displayed..." ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: BRP BRP.Activate
Page 22

'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed BRP.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="BRPDecimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet ActiveSheet.Unprotect 'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In BRP.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protect worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: BRR1 BRR1.Activate 'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed BRR1.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="BRR1Decimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet ActiveSheet.Unprotect 'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In BRR1.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell

Page 23

'Protect worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: BRR2 BRR2.Activate 'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed BRR2.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="BRR2Decimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet ActiveSheet.Unprotect 'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In BRR2.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protect worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: MD MD.Activate 'Select the range of spreadsheet cells to find currency cells and change the decimal places displayed MD.Range("A1").Select CellRange1 = ActiveCell.Address Application.GoTo Reference:="MDDecimal" CellRange2 = ActiveCell.Address 'Unprotect worksheet

Page 24

ActiveSheet.Unprotect 'Change the number of decimal places displayed in currency cells from 2 a 0 For Each Cell In MD.Range(CellRange1 & ":" & CellRange2) If Cell.NumberFormat = "#,###;(#,###);""-""" Then Cell.NumberFormat = "#,##0.00;(#,##0.00);""""" Next Cell 'Protect worksheet ActiveSheet.Protect ---------------------------------------------------------------------------------------------------------------------------------'Go to worksheet: MS MS.Activate 'Enable screen updating Application.ScreenUpdating = True 'Change cursor back to default style Application.Cursor = xlDefault 'Hide status bar Application.StatusBar = False Message MsgBox "Amounts are now displayed to 2 decimal places.", 0 + 64, "Decimal Places" Exit Sub 'Error management Exit1: Exit Sub 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

ActiveSheet.Protect Application.ScreenUpdating = True Application.Cursor = xlDefault Application.StatusBar = False

Page 26

Button: Drop Down Lists (MS06) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell SU.Activate ActiveWindow.SmallScroll Up:=1000 SU.Range("A1").Select ActiveWindow.SmallScroll Down:=18 SU.Range("B28").Select 'Make sure 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 27

Button: Home (MS07) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Make sure 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 28

Button: Enter month & year (MR01) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell MD.Activate ActiveWindow.SmallScroll Up:=1000 MD.Range("A1").Select ActiveWindow.SmallScroll Down:=0 MD.Range("B9").Select 'Make sure 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 29

Button: Enter bank balance (MR02) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell MD.Activate ActiveWindow.SmallScroll Up:=1000 MD.Range("A1").Select ActiveWindow.SmallScroll Down:=8 MD.Range("B23").Select 'Make sure 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 30

Button: Bank Reconciliation (MR03) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell BRP.Activate ActiveWindow.SmallScroll Up:=1000 BRP.Range("A1").Select 'Make sure 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 31

Button: Print Bank Reconciliation format 1 (MR04) 'Function: Views selected report in print preview 'Error management On Error GoTo Errors 'Select worksheet BRR1.Activate 'Print Preview ActiveWindow.SelectedSheets.PrintPreview 'Select worksheet MR.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 32

Button: Print Bank Reconciliation format 2 (MR05) 'Function: Views selected report in print preview 'Error management On Error GoTo Errors 'Select worksheet BRR2.Activate 'Print Preview ActiveWindow.SelectedSheets.PrintPreview 'Select worksheet MR.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 33

Button: Home (MR06) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Make sure 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 34

Button: Back (BR01) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell MR.Activate MR.Range("A1").Select 'Make sure 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 35

Button: Sort by date (BR02) 'Function: Sorts reconciled items into date order 'Declaration of Variables Dim CellRange1 As String Dim CellRange2 As String 'Error management On Error GoTo Errors 'Unprotect worksheet ActiveSheet.Unprotect 'Section 1: Sort data in this section by date Application.GoTo Reference:="BRPS1Sort_1" CellRange1 = ActiveCell.Address Application.GoTo Reference:=" BRPS1Sort_2" Selection.Offset(-2, 0).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select Selection.Sort Key1:=Range(CellRange1), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Section 2: Sort data in this section by date Application.GoTo Reference:="BRPS2Sort_1" CellRange1 = ActiveCell.Address Application.GoTo Reference:=" BRPS2Sort_2" Selection.Offset(-2, 0).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select Selection.Sort Key1:=Range(CellRange1), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Section 3: Sort data in this section by date Application.GoTo Reference:="BRPS3Sort_1" CellRange1 = ActiveCell.Address Application.GoTo Reference:=" BRPS3Sort_2" Selection.Offset(-2, 0).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select
Page 36

Selection.Sort Key1:=Range(CellRange1), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Section 4: Sort data in this section by date Application.GoTo Reference:="BRPS4Sort_1" CellRange1 = ActiveCell.Address Application.GoTo Reference:=" BRPS4Sort_2" Selection.Offset(-2, 0).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select Selection.Sort Key1:=Range(CellRange1), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Section 5: Sort data in this section by date Application.GoTo Reference:="BRPS5Sort_1" CellRange1 = ActiveCell.Address Application.GoTo Reference:=" BRPS5Sort_2" Selection.Offset(-2, 0).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select Selection.Sort Key1:=Range(CellRange1), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Section 6: Sort data in this section by date Application.GoTo Reference:="BRPS6Sort_1" CellRange1 = ActiveCell.Address Application.GoTo Reference:=" BRPS6Sort_2" Selection.Offset(-2, 0).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select Selection.Sort Key1:=Range(CellRange1), Order1:=xlAscending, Header:=xlGuess, _ OrderCustom:=1, MatchCase:=False, Orientation:=xlTopToBottom 'Protect worksheet ActiveSheet.Protect 'Go to top of worksheet ActiveWindow.SmallScroll Up:=1000 ActiveSheet.Range("A1").Select

Page 37

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 38

Button: Insert Row (BR03) 'Function: Inserts a row in section 1 of this worksheet & inserts a corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): InsertRow "BRPS1Copy", "BRR1S1Copy", BRR2S1Copy

Button: Delete Last Row (BR04) 'Function: Deletes a row in section 1 of this worksheet & deletes the corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): DeleteRow BRPS1FRow, "BRPS1Copy", "BRR1S1Copy", BRR2S1Copy

Button: Insert Row (BR05) 'Function: Inserts a row in section 2 of this worksheet & inserts a corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): InsertRow "BRPS2Copy", "BRR1S2Copy", BRR2S2Copy

Button: Delete Last Row (BR06) 'Function: Deletes a row in section 2 of this worksheet & deletes the corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): DeleteRow BRPS2FRow, "BRPS2Copy", "BRR1S2Copy", BRR2S2Copy

Page 39

Button: Insert Row (BR07) 'Function: Inserts a row in section 3 of this worksheet & inserts a corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): InsertRow "BRPS3Copy", "BRR1S3Copy", BRR2S3Copy

Button: Delete Last Row (BR08) 'Function: Deletes a row in section 3 of this worksheet & deletes the corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): DeleteRow BRPS3FRow, "BRPS3Copy", "BRR1S3Copy", BRR2S3Copy

Button: Insert Row (BR09) 'Function: Inserts a row in section 4 of this worksheet & inserts a corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): InsertRow "BRPS4Copy", "BRR1S4Copy", BRR2S4Copy

Button: Delete Last Row (BR10) 'Function: Deletes a row in section 4 of this worksheet & deletes the corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): DeleteRow BRPS4FRow, "BRPS4Copy", "BRR1S4Copy", BRR2S4Copy

Page 40

Button: Insert Row (BR11) 'Function: Inserts a row in section 5 of this worksheet & inserts a corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): InsertRow "BRPS5Copy", "BRR1S5Copy", BRR2S5Copy

Button: Delete Last Row (BR12) 'Function: Deletes a row in section 5 of this worksheet & deletes the corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): DeleteRow BRPS5FRow, "BRPS5Copy", "BRR1S5Copy", BRR2S5Copy

Button: Insert Row (BR13) 'Function: Inserts a row in section 6 of this worksheet & inserts a corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): InsertRow "BRPS6Copy", "BRR1S6Copy", BRR2S6Copy

Button: Delete Last Row (BR14) 'Function: Deletes a row in section 6 of this worksheet & deletes the corresponding row in the bank reconciliation reports 'Called procedure (with named ranges to use in the procedure): DeleteRow BRPS6FRow, "BRPS6Copy", "BRR1S6Copy", BRR2S6Copy

Page 41

Button: Back (MD01) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell MR.Activate MR.Range("A1").Select 'Make sure 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: Home (MD02) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Make sure 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: Back (SU01) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell MS.Activate MS.Range("A1").Select 'Make sure 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: Home (SU02) 'Function: Navigates user to another worksheet 'Error management On Error GoTo Errors 'Select worksheet & spreadsheet cell HP.Activate HP.Range("A1").Select 'Make sure 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

Called Procedure: InsertRow Public Sub InsertRow (Range1 As String, Range2 As String, Range3 As String) 'Error management On Error GoTo Errors 'Disable screen updating (stop screen flickering) Application.ScreenUpdating = False 'Insert new Row in worksheet & copy formats & formulas into the new row ActiveSheet.Unprotect Application.GoTo Reference:=Range1 Selection.EntireRow.Insert Application.GoTo Reference:=Range1 Selection.Copy Selection.Offset(-1, 0).Select ActiveSheet.Paste ActiveSheet.Protect 'Insert a corresponding new row into worksheet: BRR1 (bank reconciliation report format 1) & copy formats & formulas into the new row Application.GoTo Reference:=Range2 ActiveSheet.Unprotect Selection.EntireRow.Insert Application.GoTo Reference:=Range2 Selection.Offset(-2, 0).Select Selection.Copy Application.GoTo Reference:=Range2 Selection.Offset(-1, 0).Select ActiveSheet.Paste ActiveSheet.Protect 'Insert a corresponding new row into worksheet: BRR2 (bank reconciliation report format 2) & copy formats & formulas into the new row Application.GoTo Reference:=Range3 ActiveSheet.Unprotect Selection.EntireRow.Insert

Page 46

Application.GoTo Reference:=Range3 Selection.Offset(-2, 0).Select Selection.Copy Application.GoTo Reference:=Range3 Selection.Offset(-1, 0).Select ActiveSheet.Paste ActiveSheet.Protect 'Go back to worksheet: BRP BRP.Activate Application.ScreenUpdating = True 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" Application.ScreenUpdating = True ActiveSheet.Protect End Sub

Page 47

Called Procedure: DeleteRow Public Sub DeleteRow (Range1 As String, Range2 As String, Range3 As String, Range4 As String) 'Declaration of Variables Dim CellRange1 As String Dim CellRange2 As String Dim Answer As Integer 'Error management On Error GoTo Errors 'Make sure that the first row is not deleted Application.GoTo Reference:=Range1 ActiveCell.Offset(-1, 0).Select If ActiveCell.Text = FR Then GoTo Exit1 'Highlight row for deletion Application.GoTo Reference:=Range2 ActiveCell.Offset(-1, 0).Select CellRange1 = ActiveCell.Address ActiveCell.Offset(0, 5).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select 'Message Answer = MsgBox("Are you sure you want to delete this row?", 48 + 4, "Delete Row") If Answer = 7 Then GoTo Exit2 'Disable screen updating (stop screen flickering) Application.ScreenUpdating = False 'Delete selected row in worksheet ActiveSheet.Unprotect Selection.EntireRow.Delete ActiveSheet.Protect 'Delete corresponding row in worksheet: BRR1 (bank reconciliation report format 1) Application.GoTo Reference:=Range3 Selection.Offset(-1, 0).Select ActiveSheet.Unprotect
Page 48

Selection.EntireRow.Delete ActiveSheet.Protect 'Delete corresponding row in worksheet: BRR2 (bank reconciliation report format 2) Application.GoTo Reference:=Range4 Selection.Offset(-1, 0).Select ActiveSheet.Unprotect Selection.EntireRow.Delete ActiveSheet.Protect 'Go back to worksheet: BRP BRP.Activate Application.ScreenUpdating = True Exit Sub 'Error management Exit1: MsgBox "The first row cannot be deleted.", 0 + 16, "Error" ActiveSheet.Protect Exit Sub Exit2: Exit Sub 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" Application.ScreenUpdating = True ActiveSheet.Protect End Sub

Page 49

Called Procedure: EraseData 'Declaration of Variables Dim CellRange1 As String Dim CellRange2 As String Dim Answer As Integer 'Error management On Error GoTo Errors 'Highlight data that will be erased Do Until Mid(ActiveCell.Address, 2, 2) = "A$" ActiveCell.Offset(0, -1).Select Loop CellRange1 = ActiveCell.Address ActiveCell.Offset(0, 5).Select CellRange2 = ActiveCell.Address Range(CellRange1 & ":" & CellRange2).Select 'Message Answer = MsgBox("Are you sure you want to erase the data from this row?" & Chr(13) & Chr(13) & (To remove blank rows above & between completed rows click Sort by date)., 48 + 4, "Erase Entry") If Answer = 7 Then GoTo ProgramExit 'Erase data Range(CellRange1).Select Selection.ClearContents ActiveCell. Offset(0, 1).Select Selection.ClearContents ActiveCell. Offset (0, 1).Select Selection.ClearContents ActiveSheet.Unprotect ActiveCell. Offset (0, 1).Select Selection.ClearContents ActiveSheet.Protect ActiveCell. Offset (0, 2).Select Selection.ClearContents
Page 50

'Highlight data that has been erased Range(CellRange1 & ":" & CellRange2).Select Exit Sub 'Error management ProgramExit: Exit Sub 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 51

Procedure Name: Worksheet_Change 'Function: Calls procedure EraseData when Erase entry is selected from the drop down list of the Observation spreadsheet cell If ActiveCell.Text = Erase reconciling item then EraseData

Procedure Name: Worksheet_SelectionChange 'Function: Disables cut & paste If Application.CutCopyMode = xlCut Then Application.CutCopyMode = False End If

Page 52

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 "Bank Reconciliation Program Version 2" & 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 Copyright on this page." _ ,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 53

Procedure Name: Workbook_BeforeClose 'Function: Enables cell drag & drop Application.CellDragAndDrop = True

----------------------------------------------------------------------------------------------------------------------------------End of document

Page 54

Вам также может понравиться