Consulting

Results 1 to 16 of 16

Thread: VBA - Email notification when job added to list.

  1. #1
    VBAX Regular
    Joined
    Jan 2018
    Posts
    9
    Location

    VBA - Email notification when job added to list.

    Morning All,

    Within my department we use an excel based job register for employees to add engineering issues as they occur. Currently someone within my department has to sporadically check the register to see if any new jobs have been added and then assign them to an engineer and give it a priority etc. Is it possible to set up something within VBA that will send an email as a job has been added so they aren't missed and they can be assigned and reviewed quickly?

    The register will be saved in a general drive on a server that anyone can access. There is a team email address that I would like the notification sent to so all members will be alerted when a new job is added.

    Thanks,

    Jack

  2. #2
    VBAX Tutor
    Joined
    Mar 2014
    Posts
    210
    Location
    The best way I think is to use a form. User enters the new info, clicks save, and that would send the email.

    usage:

    sub btnSave_Click()
    call Email1("bob@myCo.com","New Person Added","This is to inform you...")
    end sub
    
    Public Function Email1(ByVal pvTo, ByVal pvSubj, ByVal pvBody, Optional ByVal pvFile) As Boolean
    Dim oApp As Outlook.Application
    Dim oMail As Outlook.MailItem
    
    On Error GoTo ErrMail
    
    '***   NOTE : YOU MUST HAVE THE OUTLOOK REFERENCE CHECKED IN VBE; ctl-G, menu,tools, references   ***
    
    Set oApp = CreateObject("Outlook.Application")
    Set oMail = oApp.createitem(olmailitem)
    With oMail
        .To = pvTo
        .Subject = pvSubj
        If Not IsNull(pvBody) Then .Body = pvBody
        If Not IsMissing(pvFile) Then .Attachments.Add pvFile, olByValue, 1
        
        .Display True
        .Send
    End With
    
    Email1 = True
    endit:
    Set oMail = Nothing
    Set oApp = Nothing
    Exit Function
    
    ErrMail:
    MsgBox Err.Description, vbCritical, Err
    Resume endit
    End Function

  3. #3
    VBAX Regular
    Joined
    Jan 2018
    Posts
    9
    Location
    Thank you for the response ranman.

    I only now the relative basic of VBA so I'm able to check the references are enabled and to create forms etc but I'm pretty lost from there.

    I was already using a form for the input of new jobs so I have just added the above code to the "submit job" button but to no avail.

    Will there be an issue with the fact that the job register itself will be saved on a general drive and people will be accessing the file from different PC's, log ins and email accounts to add jobs to the register?

    Ideally I'd just like a generic new job added message sent to a single email address every time somebody submits a new job to the register.

    Thanks

  4. #4
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    Put this line in the code where you save the new job

    Call Email1("bob@myCo.com","New Person Added","This is to inform you...")
    Change the email address to the group address, change the New Person Added to whatever you want the subject line to be and change the This is to inform you... to whatever you want the body text to be.

    Copy the Function code (Public Function Email... through to End Function) into a normal code module.

    You should be good to go!
    Semper in excretia sumus; solum profundum variat.

  5. #5
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    Semper in excretia sumus; solum profundum variat.

  6. #6
    VBAX Regular
    Joined
    Jan 2018
    Posts
    9
    Location
    I didn't realise both forums were linked? I was just trying to get as much help as possible so I wont cross post in future.

    I have done as you described above and I have a few minor questions. If I remove the .Display function from the module will that mean the email will send without bringing up the display window also?

    Also if someone adds a job from another computer/login etc. will the email sent be from their address?

  7. #7
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    The forums aren't linked but cross-posting is frowned on as anyone helping out doesn't have the full story and could be wasting their time.

    Yes, if you remove the .Display it will send without displaying.

    Yes, the default email address in Outlook is used. This can be changed, but I've never used it... see here for guidance:

    https://www.rondebruin.nl/win/s1/outlook/account.htm
    Semper in excretia sumus; solum profundum variat.

  8. #8
    VBAX Regular
    Joined
    Jan 2018
    Posts
    9
    Location
    Understood, I will refrain from cross-posting.

    I have removed the .Display and that has worked fine. I'm also happy for the default email address to be used.

    Is it possible to link some of the body of the email to the information added in the form? For example two of the section within the form are "programme" and "description" and it would make assigning the jobs a lot easier if these were included in the email?

    Thanks for all the help so far.

  9. #9
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    You could have different texts for different scenarios, something along the lines of:

        Dim BodyText As String, JobPhase As String
        If JobPhase = "Order" Then
            BodyText = "A new order has been received."
        ElseIf JobPhase = "New" Then
            BodyText = "A new job has been started."
        ElseIf JobPhase = "Sent" Then
            BodyText = "The order has been despatched"
        End If
        Call Email1("bob@myCo.com", "New Person Added", BodyText)
    You could also assign a variable to the subject in the same way, giving you more flexibility.
    Semper in excretia sumus; solum profundum variat.

  10. #10
    VBAX Regular
    Joined
    Jan 2018
    Posts
    9
    Location
    That could work. Where would excel be searching for the phrases to link to though? For example in your scenario where would excel be searching for the term "order" within the submitted data?

    I would look to assign the programme section to a certain phrase e.g if the programme "Test" is selected by the userform when they submit the job and send the email I would like to link the body text to include the phrase "Programme: Test - New job added to the register".

  11. #11
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    How are you selecting the different programmes in the userform?

    eg If it's a ComboBox then it would be:

        If ComboBox1 = "Test" Then
            BodyText = "Programme: Test - New job added to the register"
        ElseIf ...
    Even better, can you attach your workbook?
    Semper in excretia sumus; solum profundum variat.

  12. #12
    VBAX Regular
    Joined
    Jan 2018
    Posts
    9
    Location
    I have attached my workbook, a bit of a mess I know but its in the early stages and I have plans for it to be quite a complex beast by the end.

    Password to unprotect any sheet is ME12345 and passwords on certain buttons is ME1234
    Attached Files Attached Files
    Last edited by Jab331; 01-22-2018 at 08:25 AM. Reason: Missed Passwords

  13. #13
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    Private Sub CommandButton2_Click()
        'Copy inut values to sheet.
        Dim lRow As Long, BdyTxt As String
        Dim ws As Worksheet
        Set ws = Worksheets("ME Jobs")
        BdyTxt = " - New job added to the register."
        lRow = ws.Cells(Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        With ws
            .Cells(lRow, 1).Value = Me.TextBox1.Value
            .Cells(lRow, 3).Value = Me.TextBox2.Value
            .Cells(lRow, 4).Value = Me.ComboBox1.Value
            .Cells(lRow, 5).Value = Me.TextBox3.Value
            .Cells(lRow, 6).Value = Me.TextBox4.Value
            .Cells(lRow, 7).Value = Me.ComboBox2.Value
        End With
        'Clear input controls.
        Me.TextBox1.Value = ""
        Me.TextBox2.Value = ""
        Me.ComboBox1.Value = ""
        Me.TextBox3.Value = ""
        Me.TextBox4.Value = ""
         'Add your variable strings here-------------------------
        If ComboBox2 = "BK117" Then
            BdyTxt = "Programme: BK117" & BdyTxt
        ElseIf ComboBox2 = "EC135" Then
            BdyTxt = "Programme: EC135" & BdyTxt
        End If
        
        Me.ComboBox2.Value = ""
        Call Email1("Jack.Burge@GKNAerospace.com", "New Job Added to ME Job Register", BdyTxt & _
                "  Please assign a suitable ME and priority to the new job.")
    End Sub
    You can add as many ElseIf's as you need!
    Semper in excretia sumus; solum profundum variat.

  14. #14
    VBAX Regular
    Joined
    Jan 2018
    Posts
    9
    Location
    That works great, thank you. If I wanted to include more information, such as the department in ComboBox1, also included in the BdyTxt how would that be done?

  15. #15
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    Try this, I've altered the way it picks up Combobox2 too. You can compare them and have a play around. BTW, vbCr is the same as vbNewLine.
    You could add any of the Textboxes in there too, just move the 'clear' commands to below the 'add to string' commands otherwise you'll get nothing added!!

    Private Sub CommandButton2_Click()
         'Copy inut values to sheet.
        Dim lRow As Long, BdyTxt As String
        Dim ws As Worksheet
        Set ws = Worksheets("ME Jobs")
        BdyTxt = "New job added to the register."
        lRow = ws.Cells(Rows.Count, 1).End(xlUp).Offset(1, 0).Row
        With ws
            .Cells(lRow, 1).Value = Me.TextBox1.Value
            .Cells(lRow, 3).Value = "ME" & Format(rw - 6, "0000")
            .Cells(lRow, 4).Value = Me.ComboBox1.Value
            .Cells(lRow, 5).Value = Me.TextBox3.Value
            .Cells(lRow, 6).Value = Me.TextBox4.Value
            .Cells(lRow, 7).Value = Me.ComboBox2.Value
        End With
         'Clear input controls.
        Me.TextBox1.Value = ""
        Me.TextBox2.Value = ""
        Me.TextBox3.Value = ""
        Me.TextBox4.Value = ""
         'Add your variable strings here-------------------------
        BdyTxt = BdyTxt & vbCr & "Department: " & ComboBox1 & vbCr & "Programme : " & ComboBox2
        MsgBox BdyTxt
        Me.ComboBox1.Value = ""
        Me.ComboBox2.Value = ""
        Call Email1("Jack.Burge@GKNAerospace.com", "New Job Added to ME Job Register", BdyTxt & _
        "  Please assign a suitable ME and priority to the new job.")
    End Sub
    Semper in excretia sumus; solum profundum variat.

  16. #16
    VBAX Master paulked's Avatar
    Joined
    Apr 2006
    Posts
    1,007
    Location
    I have taken the liberty of adding a password form to your workbook. The main advantage of using this form over an inputbox is that it hides the characters of your password as you type them in.

    frmPassword.zip

    Unzip the frmPassword.zip to get the frmPassword.frm file.
    Right-click and Import File to your Forms directory in the VBA editor.

    To call it, instead of :

    Dim ThePW As String
        ThePW = InputBox("A password is required to run this procedure." & vbCrLf & _
        "Please enter the password:", "Password")
        If ThePW <> "ME1234" Then Exit Sub
    use:

        frmPassword.Show
        If frmPassword.Tag <> "1" Then Exit Sub
    In the user form code, change Tag = 1 to Tag = "1" - Sorry, missed that before uploading!
    Last edited by paulked; 01-24-2018 at 12:16 PM. Reason: Missed quotation marks
    Semper in excretia sumus; solum profundum variat.

Tags for this Thread

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •