Consulting

Results 1 to 9 of 9

Thread: VBA macro code for Word doc convert to PDF, then email by Outlook 365, ask "subject"

  1. #1
    VBAX Regular
    Joined
    Oct 2018
    Location
    Antwerp
    Posts
    41
    Location

    VBA macro code for Word doc convert to PDF, then email by Outlook 365, ask "subject"

    How Do I make a BVA macro code in Word 365, so that my doc is converted to PDF, then asks (give Subject), and can be mailed by Outlook 365.
    Thanks

  2. #2
    VBAX Guru Kenneth Hobs's Avatar
    Joined
    Nov 2005
    Location
    Tecumseh, OK
    Posts
    4,956
    Location
    Welcome to the forum! Your question is a multi-part one which is often the case for Integration questions. As such, response time might take longer.

    I normally work in Excel. I created this macro by recording the macro in Word first. You can do the same. I can make this into a Word macro if needed. It can readily be used as-is in any VBA project though.
    'Requires Tools > References > Microsoft Word 16.0 Object Library
    Sub MakeWordPDFFile(sMSWordFilename As String, sOutputFilename As String)
      Dim wdApp As Word.Application, wdDoc As Word.Document
      Dim wdExportFormatPDF As Integer, wdExportOptimizeForPrint As Integer
      Dim wdExportAllDocument As Integer, wdExportDocumentContent As Integer
      Dim wdExportCreateNoBookmarks As Integer
      
      If Not CreateObject("Scripting.FileSystemObject").FileExists(sMSWordFilename) Then _
        Exit Sub
        
      On Error GoTo errorHandler
      Set wdApp = New Word.Application
      With wdApp
        Set wdDoc = .Documents.Open(sMSWordFilename)
        .Visible = False
      End With
      
      If CreateObject("Scripting.FileSystemObject").FileExists(sOutputFilename) Then _
        Kill sOutputFilename
      
      wdExportFormatPDF = 17
      wdExportOptimizeForPrint = 0
      wdExportAllDocument = 0
      wdExportDocumentContent = 0
      wdExportCreateNoBookmarks = 0
        
      wdDoc.ExportAsFixedFormat _
        OutputFileName:=sOutputFilename, ExportFormat:=wdExportFormatPDF, _
        OpenAfterExport:=False, OptimizeFor:=wdExportOptimizeForPrint, Range:= _
        wdExportAllDocument, From:=1, To:=1, Item:=wdExportDocumentContent, _
        IncludeDocProps:=True, KeepIRM:=True, CreateBookmarks:= _
        wdExportCreateNoBookmarks, DocStructureTags:=True, BitmapMissingFonts:= _
        True, UseISO19005_1:=False
      wdDoc.Close False
      
    errorExit:
      On Error Resume Next
      Set wdDoc = Nothing
      Set wdApp = Nothing
      Exit Sub
     
    errorHandler:
      MsgBox "Unexpected error: " & Err.Number & vbLf & Err.Description
      Resume errorExit
    End Sub
    To get the text for the Subject, one can use Inputbox() or Application.InputBox() or a Userform with TextBox control(s) or other ways. I guess that your Outlook To field's value would always be the same.

    The Outlook part is easy after you have what you need above. Ron de Bruin has several examples on his site. Some are Excel based but the VBA code part is the same in Outlook less the method to get values for the properties. Most of those you would set manually except for the Subject.

    e.g.
    'More Excel to Outlook Examples: http://www.rondebruin.nl/win/s1/outlook/bmail4.htm
    'http://www.rondebruin.nl/win/s1/outlook/signature.htm
    
    
    Sub Main()
      'Add reference: Microsoft Outlook xx.x Library, where xx.x is 14.0, 15.0, 16.0, etc.
      'Dim olApp As Outlook.Application, olMail As Outlook.MailItem 'Early binding.
      Dim olApp As Object, olMail As Object 'Late binding.
      Dim pdfPath$, oExists As Boolean
      
      'pdfPath = "I:\FST\R&D and Projects\Samples\Sample Requests\"
      pdfPath = ThisWorkbook.Path & "\"
      pdfPath = pdfPath & "Order.pdf"
      Worksheets(1).ExportAsFixedFormat xlTypePDF, pdfPath
      
      On Error Resume Next
      '  Set olApp = New Outlook.Application 'Early binding
      Set olApp = GetObject(, "Outlook.Application")
      If Err Then
        Set olApp = CreateObject("Outlook.Application")
        oExists = True
      End If
      On Error GoTo 0
      
      Set olMail = olApp.CreateItem(olMailItem)
      With olMail
        .To = " abc@abc.co.uk;def@def.co.uk"
        '.CC = "cc@cc.com"
        .Subject = "Order Attachment"
        .Body = "please can we order the attached"
        .Attachments.Add pdfPath, Position:=Len(.Body) + 10
        .Display
        '.Send
      End With
      
      Set olMail = Nothing
      If oExists Then olApp.Quit
      Set olApp = Nothing
    End Sub
    If you need more help, please post back.

  3. #3
    I would do it as follows. Note that the code calls a function to open Outlook properly which can be copied from the link. The macro asks if you want to send as PDF then saves the document as such and opens the message for you to complete.

    Sub Send_As_Mail_Attachment()
    'Graham Mayor = http://www.gmayor.com
    'Send the document as an attachment _
      in an Outlook Email message
    'Requires the code from - http://www.rondebruin.nl/win/s1/outlook/openclose.htm
    'to either retrieve an open instance of Outlook or open Outlook if it is closed.
    Dim bStarted As Boolean
    Dim olApp As Object
    Dim oItem As Object
    Dim oDoc As Document
    Dim strName As String
    Dim strDocName As String
    Dim strPath As String
    Dim intPos As Integer
    Dim iFormat As Long
        Set oDoc = ActiveDocument
        'Prompt the user to save the document
        On Error GoTo err_Handler:
        oDoc.Save
        strDocName = oDoc.Name
        iFormat = MsgBox("Send as PDF format?", vbYesNoCancel)
        If iFormat = 2 Then GoTo lbl_Exit
        If iFormat = 7 Then strDocName = oDoc.FullName: strName = oDoc.Name
        If iFormat = 6 Then
            'Get the document name and path
            strPath = oDoc.path & "\"
            intPos = InStrRev(strDocName, ".")
            strDocName = Left(strDocName, intPos - 1)
            strName = strDocName & ".pdf"
            strDocName = strPath & strDocName & ".pdf"
    
            'And save the document as PDF
            oDoc.ExportAsFixedFormat OutputFilename:=strDocName, _
                                     ExportFormat:=wdExportFormatPDF, _
                                     OpenAfterExport:=False, _
                                     OptimizeFor:=wdExportOptimizeForPrint, _
                                     Range:=wdExportAllDocument, From:=1, to:=1, _
                                     Item:=wdExportDocumentContent, _
                                     IncludeDocProps:=True, _
                                     KeepIRM:=True, _
                                     CreateBookmarks:=wdExportCreateHeadingBookmarks, _
                                     DocStructureTags:=True, _
                                     BitmapMissingFonts:=True, _
                                     UseISO19005_1:=False
    
            'Now close the document without saving as we have finished with it
            oDoc.Close 0
        End If
        'Get Outlook if it's running
        Set olApp = OutlookApp()
        On Error GoTo 0
        'Create a new mailitem
        Set oItem = olApp.CreateItem(0)
    
        With oItem
            .Attachments.Add strDocName
            .Display
        End With
    
    lbl_Exit:
        Set oItem = Nothing
        Set olApp = Nothing
        Exit Sub
    err_Handler:
        Err.Clear
        GoTo lbl_Exit
    End Sub
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  4. #4
    VBAX Regular
    Joined
    Oct 2018
    Location
    Antwerp
    Posts
    41
    Location

    @gmayor

    Thanks for your kind help. I tried your code but got a error "Set olApp = OutlookApp()" -> Sub of function not defined. So te macro does no work. Any idea why this happens?

  5. #5
    VBAX Regular
    Joined
    Oct 2018
    Location
    Antwerp
    Posts
    41
    Location
    Thank you. The macro does not werk, error message: sMSWordFilename: variable not defined. Any idea? Thanks!

  6. #6
    VBAX Guru Kenneth Hobs's Avatar
    Joined
    Nov 2005
    Location
    Tecumseh, OK
    Posts
    4,956
    Location
    Use one of the 2 methods that I showed in #2 to set the outlook application object.
      '  Set olApp = New Outlook.Application 'Early binding
      Set olApp = GetObject(, "Outlook.Application")

  7. #7
    Quote Originally Posted by wdg1 View Post
    Thanks for your kind help. I tried your code but got a error "Set olApp = OutlookApp()" -> Sub of function not defined. So te macro does no work. Any idea why this happens?
    You clearly didn't read the warning at the top of the macro as you have obviously not installed the function listed on that page-

    'Requires the code from - http://www.rondebruin.nl/win/s1/outlook/openclose.htm
    'to either retrieve an open instance of Outlook or open Outlook if it is closed
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  8. #8
    VBAX Regular
    Joined
    Oct 2018
    Location
    Antwerp
    Posts
    41
    Location
    thank you for your nice help. So, I did copy your macro codend added a extra line: Set olApp = GetObject(, "Outlook.Application")
    but I got an error: variable olApp not defined.What to do now? Thank you.

  9. #9
    VBAX Guru Kenneth Hobs's Avatar
    Joined
    Nov 2005
    Location
    Tecumseh, OK
    Posts
    4,956
    Location
    Most coders will Dim the variables as their first line(s) of code as Graham and I did. You must have added the Set line before the Dim alApp as Object line? You could remove the requirement to declare variables in VBE's Options or remove the Option Explicit line. I recommend requiring declarations myself.

    Or, just do as Graham said and add the routine for OutlookApp() from Ron de Bruin's site. http://www.rondebruin.nl/win/s1/outlook/openclose.htm
    That method is handy as it forces Outlook to open. If Outlook is not open for macros that Send, then those sends are put into the Output folder and won't send until you open Outlook.

Posting Permissions

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