You are on page 1of 8

VBA Excel Userform Database – Staff Job Allocator

Contents [show]

Overview
In this project we will be using a Excel userform database that will run a complete staff allocation system. This truly is an awesome
application.
You will be able to allocate staff to a job number and make them available again after the job is completed and check the status of all of
your staff at any time.
It would be especially suited to somebody who is sending staff to multiple jobs in a day and having them then return to their base.
The complete application is run from a userform and all information is archived to keep a complete history of all work that staff has been
sent to.
You can also create a PDF copy of a particular job number or certain job numbers during the day.

This tutorial is for the more advanced student.


I will not be going into the normal details as I anticipate those doing this tutorial will understand the basics.
This application has been designed by Trevor Easton for training purposes.  You are able to use this for your personal use. The
application as is or modified in not permitted for sale in any form. No warranties are implied or given with this application.

Video1: Overview video


Download the template
Template Allocation Database
 

Video 2: Creating the userform and adding the named ranges


Still to come

Adding the named ranges


Here are the named ranges that should be added now:
5 static named ranges
2 dynamic  named ranges

Name Formula
ArchiveSheet =Archive!$A$1
Staff_ListSheet =Staff_List!$A$1
Job_AllocationSheet =Jobs_Allocation!$A$1
Skills =OFFSET(Jobs_Allocation!$P$7,,,COUNTA(Jobs_Allocation!$P$7:$P$100))
Trades =OFFSET(Staff_List!$R$6,1,,COUNTA(Staff_List!$R$6:$R$9994),9)
 
There are 2 other ranges that we will create as we need them.
One is for the archiving “Booked”
The other is for the print area “PDFrng”
 
Creating the Userform
Add a userform and add the controls from the illustration below.
Make sure to use the right control type and assign the exact name shown.
Note: Reg2 and Reg3 should have the properties set to invisible.

 Do not group the option buttons.


 Set the listbox RowSource with the dynamic named range “Trades”
 Set the Combobox cboSkills RowSource to “Skills”

Note the special properties for our listbox.


These 4 things you must have correct in the properties for the listbox:

 The listbox name lstSelector


 ColumnCount = 9
 ColumnWidths = 80pt; 80pt; 80pt; 80pt; 80pt; 80pt; 80pt; 80pt; 80pt
 MultiSelect =  1-frrmMultiSelectMulti

Test the userform with the run button or by pushing the F5 key.
Note: We will be assigning the items to cboBooked as the userform initialises as we do not want this information to change.

Code for the Userform


Procedures
Userform Initialise
When the user form initializes we need to add some items to our combo box. I am hard coding these items because I do not want them
changed by the user as we would in a dynamic list that would populate the row source of the combo box.
You will notice that we are protecting fiercely that staff ID that we will be using as the key element for editing and deleting. When the
user form initialises we're going to disable this control and change the colour. Also we want to stop any editing occurring at this stage
so we disable the edit button as well.
Private Sub UserForm_Initialize()
'add combobox items
    Me.cboBooked.AddItem "Booked"
    Me.cboBooked.AddItem "Available"
    Me.cboBooked.AddItem ""
    'disable ID
    Me.Reg4.Enabled = False
    'change the back color
    Me.Reg4.BackColor = RGB(192, 192, 192)
    'disable edit
    Me.cmdEdit.Enabled = False
    FilterMe
End Sub

 Add to the database


This is a procedure it is not assigned or button that will be called from another module when necessary. All of this procedure does is
adds the values from the multi-selected listbox and copy them one row at a time to our Job Allocation list. You will notice that we have
nine columns in our listbox.
Sub Addme()
'declare the variables
    Dim Addme As Range
    Dim x As Integer
    'error handler
    On Error GoTo errHandler:
'find the next black row in the database
    Set Addme = Sheet1.Cells(Rows.Count, 3).End(xlUp).Offset(1, 0)
    'loop through multi selected items and add them to the database
    For x = 0 To Me.lstSelector.ListCount- 1
        If Me.lstSelector.Selected(x) Then
            Addme = Me.lstSelector.List(x)
            Addme.Offset(0, 1) = Me.cboBooked.Value
            Addme.Offset(0, 2) = Me.txtJob.Value
            Addme.Offset(0, 3) = Me.lstSelector.List(x, 3)
            Addme.Offset(0, 4) = Me.lstSelector.List(x, 4)
            Addme.Offset(0, 5) = Me.lstSelector.List(x, 5)
            Addme.Offset(0, 6) = Me.lstSelector.List(x, 6)
            Addme.Offset(0, 7) = Me.lstSelector.List(x, 7)
            Addme.Offset(0, 8) = Me.lstSelector.List(x, 8)
            Set Addme = Addme.Offset(1, 0)
        End If
    Next x
    'error block
    On Error GoTo 0
    Exit Sub
errHandler:
    MsgBox "An Error has Occurred  " & vbCrLf & "The error number is:  " _
           & Err.Number & vbCrLf & Err.Description & vbCrLf & _
           "Please notify the administrator"
End Sub

Combobox criteria
As you will see in a moment in our advanced filter macro we have multiple criteria in fact 2 criteria. This combo box is one of the criteria.
It allows for three options. First to filter our database by those who are Booked, second to filter the database by those who are
Available, and third a blank option that will allow for all to be shown with the filter. I would suggest that you look at this code very
carefully because here you will find that we are excluding and including other controls depending on our selection. As an example if we
would choose the criteria "Available" which means we are bringing staff back to base then we would not want to assign a job number so
we disable that feature and change the colour of the control to stop our staff from making this error.
Private Sub cboBooked_Change()
'enable and disable buttons based on selection
    If Me.cboBooked.Value = "Available" Then
    'disable Job numbers
        Me.txtJob.Enabled = False
        'change the button back color
        Me.txtJob.BackColor = RGB(192, 192, 192)
        'disable skills list
        Me.cboSkills.Enabled = False
        'change the button back color
        Me.cboSkills.BackColor = RGB(192, 192, 192)
    ElseIf Me.cboBooked.Value = "Booked" Then
    'enable Job numbers
        Me.txtJob.Enabled = True
        'change the button back color
        Me.txtJob.BackColor = RGB(255, 255, 255)
        'enable skills
        Me.cboSkills.Enabled = True
        'change the button back color
        Me.cboSkills.BackColor = RGB(255, 255, 255)
    End If
End Sub

Before we go any further we need to go to our Assorted Module and add a if you macros that are
necessary at this stage of our development.Do not copy the code that you see the below into the userform
, it goes in the Assorted Module.

Code for the module


Call the userform
Our first little procedure simply calls the user form. Assign this macro to the button on the Job Allocation sheet.
Sub Showme()
'show the userform
    frmSelector.Show
End Sub

Filter our database with multiple criteria


This is our advanced filter that we will be calling the many times throughout our application to be able to get the right data at the right
time depending on the criteria that you select. You will notice to get the range to be dynamic I have used the Current Region setting.
There are two criteria in this advanced filter.
Sub FilterMe()
'error handler
    On Error GoTo errHandler:
'advanced filter
    Sheet2.Range("D6").CurrentRegion.AdvancedFilter Action:=xlFilterCopy, _
    CriteriaRange:=Sheet2.Range("O6:P7"), CopyToRange:=Sheet2.Range("R6:Z6"), Unique:=False
'error block
    On Error GoTo 0
    Exit Sub
errHandler:
    MsgBox "An Error has Occurred  " & vbCrLf & "The error number is:  " _
           & Err.Number & vbCrLf & Err.Description & vbCrLf & _
           "Please notify the administrator"
End Sub

Sort the database


The macro below will again be called from a user form when we add the data to our database. The result will be that our database will
be sorted in ascending order. We will be using this procedure in our next part of these tutorials but I thought I would add it now to
complete the assorted module.
Sub Sortit()
'select the sheet
    Sheet2.Select
    'sort the data
    With Sheet2
        .Range("D7:L10000").Sort Key1:=.Range("D7"), Order1:=xlAscending, Header:=xlNo
    End With
End Sub

More userform code


Code for our Run button
Navigate back to the user form and add this code. Again be warned that do not just copy this code and hope for the best take the time
and read through it carefully. This is the code that takes our criteria from the two combo boxes and sends them to the worksheet to be
filtered. Before we run the filter we run a number of checks to make sure that there are no duplicates to make sure that we have all the
data et cetera.
Private Sub cmdBook_Click()
    Dim findvalue
    Dim x As Integer
    Dim lCol As Variant
    'error handler
    On Error GoTo errHandler:
    'filter criteria is sent to the sheet
    Sheet2.Range("P7").Value = Me.cboBooked.Value
    Sheet2.Range("O7").Value = Me.cboSkills.Value
    'loop through and find list items
    For x = 0 To Me.lstSelector.ListCount- 1
        If Me.lstSelector.Selected(x) Then
            lCol = Me.lstSelector.List(x, 3)
            Set findvalue = Sheet2.Range("G:G").Find(What:=lCol, LookIn:=xlValues).Offset(0, -2)
            'check that job number has been added
            If Me.cboBooked.Value = "Booked" And Me.txtJob.Value = "" Then
                MsgBox "You need to add a job number"
                Exit Sub
            End If
            'add booked and job number to the database
            If Me.cboBooked.Value = "Booked" Then
                findvalue.Value = Me.cboBooked
                findvalue.Offset(0, 1).Value = Me.txtJob
            End If
            'add available if selected
            If Me.cboBooked.Value = "Available" Then
                findvalue.Value = Me.cboBooked
                findvalue.Offset(0, 1).Value = ""
            End If
        End If
        'next selected item
    Next x
    'if booked then add to job allocation
    If Me.cboBooked.Value = "Booked" Then Addme
    'run the advanced filter with the criteria above
    FilterMe
    'refresh the userform
    Unload Me
    frmSelector.Show
    'error block
    On Error GoTo 0
    Exit Sub
errHandler:
    MsgBox "An Error has Occurred  " & vbCrLf & "The error number is:  " _
           & Err.Number & vbCrLf & Err.Description & vbCrLf & _
           "Please notify the administrator"
End Sub
By this stage of our development you should be able to filter your staff add them to job allocations and see all of these results in the
listbox in a user form. Test is very carefully before you proceed.
In our next part we will be looking at how we can add new staff to our database and edit and delete them where necessary.

The code below is for the add and edit and delete features of this application at the bottom
of the userform.
Adding new staff members
If you have completed the Staff Database project then this section of the application will be a breeze you. I have used the code from
that application with a couple of small modifications in order to add edit and delete staff from our Staff Allocator Application.
Please take the time to read through the code below and try to figure out what is happening.

 Setting an error handler


 Checking that the first for values have been added
 Looking for duplicates so we don’t add the same staff member twice
 Setting a variable for the number of controls to add
 Looping through to add the values
 Clearing all the controls after the values have been successfully added
 Sorting the database
 Running a error handling block

 
Private Sub cmdAdd_Click()
    Application.ScreenUpdating = False
    Dim nextrow As Range
    'error handler
    On Error GoTo errHandler:
    'set the next row in the database
    Set nextrow = Sheet2.Cells(Rows.Count, 4).End(xlUp).Offset(1, 0)
    'check for values in the first 4 controls
    If Me.Reg1.Value = "" Or Me.Reg4.Value = "" Or Me.Reg5.Value = "" Then
        MsgBox "You need to add the skill and first and last names"
        Exit Sub
    End If
    'check for duplicate payroll numbers
    If WorksheetFunction.CountIf(Sheet2.Range("G:G"), Me.Reg4.Value) > 0 Then
        MsgBox "This staff member already exists"
        Exit Sub
    End If
    'number of controls to loop through
    cNum = 9
    'add the data to the database
    For x = 1 To cNum
        nextrow = Me.Controls("Reg" & x).Value
        Set nextrow = nextrow.Offset(0, 1)
    Next
    'clear the controls
    For x = 1 To cNum
        Me.Controls("Reg" & x).Value = ""
    Next
    'sort the database
    Sortit
    'error block
    On Error GoTo 0
    Exit Sub
errHandler::
    MsgBox "An Error has Occurred  " & vbCrLf & "The error number is:  " _
           & Err.Number & vbCrLf & Err.Description & vbCrLf & _
           "Please notify the administrator"
End Sub

 Working with our option buttons


The option button is unable us to be able to add and edit and at the same time exclude all include the necessary features that we want
available to the end user. You will notice that I have changed the colour of the controls in order to help the end user to see what is
available to them and what they cannot use.

Option Add
Private Sub optAdd_Click()
'what to do when the add option button is clicked
'allow the adding of an ID
 Me.Reg4.Enabled = True
 'change the back color
 Me.Reg4.BackColor = RGB(255, 255, 255)
 'disable the edit button
 Me.cmdEdit.Enabled = False
 'enable the add button
 Me.cmdAdd.Enabled = True
End Sub

Option Edit
Private Sub optEdit_Click()
'what ot do when the edit option is selected
'disable the ID
 Me.Reg4.Enabled = False
 'change the ID color background
 Me.Reg4.BackColor = RGB(192, 192, 192)
 'enable the edit button
 Me.cmdEdit.Enabled = True
 'disable the add button
 Me.cmdAdd.Enabled = False
End Sub

Adding the first and last names and combining them


As we are adding the first and last names we want the end user to be able to see them being concatenated into our combined named
to control. The two procedures below are associated with the change events for the first and last names.

First name control


Private Sub Reg5_Change()
'contatinate values
    Me.Reg7.Value = Me.Reg5.Value + " " + Me.Reg6.Value
End Sub

Last name control


Private Sub Reg6_Change()
'contatinate values
Me.Reg7.Value = Me.Reg5.Value + " " + Me.Reg6.Value
End Sub

 Editing and deleting staff


Before we can edit or delete our staff we need to select them from the listbox and take their values and put them into the controls for
editing or deleting.I am using the double-click event in the listbox to do this.
Here is a dot point summary of what the code will accomplish.

 Find the selected item in the listbox and set it as a variable


 Locate the payroll number associated with that staff member
 Find all of the values associated with the staff member
 Add them to the controls in the user form
 Disables the add button
 Adds an error handling block

 
 Private Sub lstSelector_DblClick(ByVal Cancel As MSForms.ReturnBoolean)
'declare the variables
    Dim cPayroll As String
    Dim I As Integer
    Dim findvalue
    Dim cNum As Integer
    'error block
    On Error GoTo errHandler:
    'get the select value from the listbox
    For I = 0 To lstSelector.ListCount- 1
        If lstSelector.Selected(I) = True Then
            cPayroll = lstSelector.List(I, 3)
        End If
    Next I
    'find the payroll number
    Set findvalue = Sheet2.Range("G:G").Find(What:=cPayroll, LookIn:=xlValues).Offset(0, -3)
    'add the database values to the userform
    cNum = 9
    For x = 1 To cNum
        Me.Controls("Reg" & x).Value = findvalue
        Set findvalue = findvalue.Offset(0, 1)
    Next
    'disable adding
    Me.cmdAdd.Enabled = False
    Me.cmdEdit.Enabled = True
    'error block
    On Error GoTo 0
    Exit Sub
errHandler::
    MsgBox "An Error has Occurred  " & vbCrLf & "The error number is:  " _
           & Err.Number & vbCrLf & Err.Description & vbCrLf & _
           "Please notify the administrator"
End Sub

Deleting staff
What does this code do?

 Check if values exist to be deleted


 Give the user an opportunity to change their mind
 Finds the staff ID number for our staff member
 Deletes the entire row
 Clears all the controls
 Runs the advanced filter
 Refreshes the userform

Private Sub cmdDelete_Click()


'declare the variables
    Dim findvalue As Range
    Dim cDelete As VbMsgBoxResult
    Dim cNum As Integer
    'check for values
    If Reg1.Value = "" Or Reg4.Value = "" Then
        MsgBox "There is not data to delete"
        Exit Sub
    End If
    'give the user a chance to change their mind
    cDelete = MsgBox("Are you sure that you want to delete thsi staff member", vbYesNo + vbDefaultButton2, "Are you sure????")
    If cDelete = vbYes Then
        'delete the row
        Set findvalue = Sheet2.Range("G:G").Find(What:=Reg4, LookIn:=xlValues)
        findvalue.EntireRow.Delete
    End If
    'clear the controls
    cNum = 9
    For x = 1 To cNum
        Me.Controls("Reg" & x).Value = ""
    Next
    'refresh the listbox
    FilterMe
    Unload Me
    frmSelector.Show
End Sub

Editing our staff members


Macro overview of main functions

 Check that there are values


 Find the payroll numbers this staff member in the database
 Edit the database values
 Refreshes the userform Listbox
 Adds error handling

Private Sub cmdEdit_Click()


'declare the variables
    Dim findvalue As Range
    Dim cNum As Integer
    'error handling
    On Error GoTo errHandler:
    'check for values
    If Reg1.Value = "" Or Reg4.Value = "" Then
        MsgBox "There is not data to edit"
        Exit Sub
    End If
    'edit the row
    Set findvalue = Sheet2.Range("G:G").Find(What:=Reg4, LookIn:=xlValues).Offset(0, -3)
    'if the edit is a name then add it
     Me.Reg7.Value = Me.Reg5.Value + " " + Me.Reg6.Value
     'set the number of controls and loop through them
    cNum = 9
    For x = 1 To cNum
        findvalue = Me.Controls("Reg" & x).Value
        Set findvalue = findvalue.Offset(0, 1)
    Next
    'refresh the userform
    FilterMe
    Unload Me
    frmSelector.Show
    'error block
    On Error GoTo 0
    Exit Sub
errHandler:
    MsgBox "An Error has Occurred  " & vbCrLf & _
           "The error number is:  " & Err.Number & vbCrLf & _
           Err.Description & vbCrLf & "Please notify the administrator"
End Sub

Archiving and clearing the data


This procedure will  archive the data and delete it from the job Allocation sheet. It will also remove the values "Booked" and "Available"
from the staff database. Read this carefully befor you attempt to modify the code.
Private Sub cmdClear_Click()
'declare the variables
    Dim CheckDelete As VbMsgBoxResult
    Dim DstRng As Range
    Dim SrcRng As Range
    'error handler
    On Error GoTo errHandler:
    If Sheet1.Range("C7").Value = "" Then
        MsgBox "There is no data to delete"
        Exit Sub
    End If
    'give the user a chance to cancel the action
    CheckDelete = MsgBox("Are you sure you want to delete this data?", vbYesNo + vbDefaultButton2)
    'if yes then proceed
    If CheckDelete = vbYes Then
    'create a named range for the for data
        Sheet1.Range("C7:K" & Cells(Rows.Count, "C").End(xlUp).Row).Name = "Booked"
        'set the destination and copy ranges
        Set SrcRng = Sheet1.Range("Booked")
        Set DstRng = Sheet3.Cells(Rows.Count, 3).End(xlUp).Offset(1, 0)
        'copy and paste
        SrcRng.Copy
        DstRng.PasteSpecial xlPasteValues
        'delete the range of data
        Sheet1.Range("Booked").ClearContents
        'clear the values from the database
        Sheet2.Range("E7:F10000").ClearContents
        'reset the form
        Unload Me
        frmSelector.Show
    End If
    'error block
    On Error GoTo 0
    Exit Sub
errHandler:
    MsgBox "An Error has Occurred  " & vbCrLf & "The error number is:  " _
           & Err.Number & vbCrLf & Err.Description & vbCrLf & _
           "Please notify the administrator"
End Sub

Clearing multi selected items


Here we loop through the listbox and deselect the select items in the listbox
Private Sub cmdRefresh_Click()
    'clear all selected items in the listbox
    For x = 0 To Me.lstSelector.ListCount- 1
        If Me.lstSelector.Selected(x) Then Me.lstSelector.Selected(x) = False
    Next x
End Sub

Closes the form


Private Sub cmdClose_Click()
'close the form
    Unload Me
End Sub

Make sure the test that all of these features and functions are working for you in your
application.

You might also like