Consulting

Results 1 to 4 of 4

Thread: VBA - sending a meeting invitation to several people

  1. #1

    VBA - sending a meeting invitation to several people

    Hello!


    I am having trouble with writing a code for the following function.


    I have a table that has previously been completed by vba code, in which there are columns with names, surnames, e-mail addresses and in the last one: whether the person will receive the invitation for outlook meeting or not.

    The entire invitation sent via Outlook with a link to Teams works great, but I have a problem with writing code that only people with an annotation "Invite" will be choosen for "RequiredAttendees" into a meeting.



    Does anyone know how to sum these selected fields with e-mail addresses?

    Thank you!

  2. #2
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,189
    Location
    Hi hotmochaccin,

    Welcome to the furum.

    Do you have any code that you can share? - we can then look through what you have already.
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved

    Excel 365, Version 2403, Build 17425.20146

  3. #3
    Hello georgiboy, thank you . Below are fragments of what I have:


    Sub MeetingInvitation()
    
    
    Dim OutApp As Outlook.Application
    Dim Outmeet As Outlook.AppointmentItem
    Set OutApp = Outlook.Application
    Set Outmeet = OutApp.CreateItem(olAppointmentItem)
    
    
    'who will receive an invitation
    Dim people As Long
    Dim i As Integer
    Dim last_row As Integer
    last_row = Application.WorksheetFunction.CountA(X.Range("F:F"))
    For i = X.Range("B12").Value To last_row
    people = X.Range("A" & i).Value
    Next
    
    
    (...)
    
    
    'invitation
    With Outmeet
    .Subject = X.Range("B2").Value & " - X"
    .RequiredAttendees = people      /this part is problematic
    .Start = X.Range("F3").Value & " " & Format(X.Range("D3").Value, "h:mm")
    (...)
    End With
    
    (...)
    End Sub
    
    
    The table looks like this:
    
    e-mail     |  status?
    xx            | Invite
    yy            | Reservation list
    zz            |Invite

    The previous code is setting the status so only two comments are possible. How many people will be invited is a constant value, but for example not always it will be the first 10 people.

    The problem is that I don't quite know how to use 'If' or 'Loop' using the neighbor cell condition. I've already tried to do it by the hard way - copy only people to be invited to the adjacent column by adding "; " at the end of the email, but this method didn't work either.
    Last edited by hotmochaccin; 04-01-2022 at 08:33 AM.

  4. #4
    Moderator VBAX Master georgiboy's Avatar
    Joined
    Mar 2008
    Location
    Kent, England
    Posts
    1,189
    Location
    Maybe you could try the below, it assumes the email address is in column 'F' and the word 'Invite' is in column 'G' it will look through the list and build a list of email addresses that have 'Invite' next to them and pass this to the 'RequiredAttendees' piece at the end.

    Sub MeetingInvitation()    Dim OutApp As Outlook.Application
        Dim Outmeet As Outlook.AppointmentItem
        Dim i As Long, x As Long, last_row As Long, people As String
        
        Set OutApp = Outlook.Application
        Set Outmeet = OutApp.CreateItem(olAppointmentItem)
        
        'who will receive an invitation
        last_row = Range("F" & Rows.Count).End(xlUp).Row
        For i = 2 To last_row
            If Range("G" & i).Value = "Invite" Then
                people = people & Range("F" & i).Value & "; "
            End If
        Next
        
        If Len(people) > 0 Then
            people = Left(people, Len(people) - 2)
        Else
            MsgBox "No invites"
            GoTo ender
        End If
        
        'invitation
        With Outmeet
            .Display
            .Subject = Range("B2").Value & " - X"
            .RequiredAttendees = people
            .Start = Range("F3").Value & " " & Format(Range("D3").Value, "h:mm")
        End With
        
        Exit Sub
    ender:
        Outmeet.Delete
        OutApp.Quit
    End Sub
    Hope this helps
    Click here for a guide on how to add code tags
    Click here for a guide on how to mark a thread as solved

    Excel 365, Version 2403, Build 17425.20146

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
  •