Consulting

Results 1 to 7 of 7

Thread: VBA to insert text and hyperlink in Outlook

  1. #1

    VBA to insert text and hyperlink in Outlook

    Hi everybody,

    I have a code that works very well to insert some text in Outlook. Recently, I have tried to modify it slightly in order to insert a hyperlink, using these tags: <> but it doesn't work - it insert the link as text, not as a clickable hyperlink. I'm unsure what the syntax should be?

    I have also found some code to insert a link at the cursor position, and tried to modify it to insert text before and after the link, but it only insert text after the link

    I would appreciate your help

    Thank you!

    Sarah

    PS: in the code below the bit that says "website link here" is actually a www address but I had to change this as otherwise I couldn't post this thread

    Sub InsertText()
    
    Const sText As String = "If you wish to download or view our latest catalogue, please simply follow this link: " & vbNewLine & _
    "Click <a href=""website link here"">here</a>" & vbNewLine & _
    "Should you wish to review or enquire about any of our products, please do not hesitate to get in touch." & vbNewLine
    
    On Error GoTo ErrHandler
    If TypeName(ActiveWindow) = "Inspector" Then
        If ActiveInspector.IsWordMail And ActiveInspector.EditorType = olEditorWord Then
            ActiveInspector.WordEditor.Application.Selection.TypeText sText
        End If
    End If
    Exit Sub
    ErrHandler:
    Beep
    
    End Sub

  2. #2
    VBAX Mentor skatonni's Avatar
    Joined
    Jun 2006
    Posts
    347
    Location
    Try the code described here.

    ' http://www.outlookcode.com/codedetail.aspx?id=1726

    Sub Hyperlink_Selection()
    
        Dim objInsp As Inspector
        Dim objItem As mailItem
        
        ' requires reference to Microsoft Word library
        Dim objDoc As Word.Document
        Dim objSel As Word.Selection
        
        Dim strLink As String
        Dim strLinkText As String
        
        strLink = "http://www.outlookcode.com"
        strLinkText = "Get Outlook code samples here"
        On Error Resume Next
        Set objItem = ActiveInspector.currentItem
        On Error GoTo 0
        
        If objItem Is Nothing Then
        
            MsgBox "Open a message to insert text and hyperlink."
        
        Else
        
            Set objInsp = objItem.GetInspector
            Set objDoc = objInsp.WordEditor
            Set objSel = objDoc.Windows(1).Selection
        
            InsertText1
        
            If objItem.BodyFormat <> olFormatPlain Then
                objDoc.Hyperlinks.Add objSel.range, strLink, "", "", strLinkText, ""
            Else
                objSel.InsertAfter strLink
            End If
        
            InsertText2
            
        End If
        
    ExitRoutine:
        Set objInsp = Nothing
        Set objDoc = Nothing
        Set objSel = Nothing
        Set objItem = Nothing
        
    End Sub
    
    
    Private Sub InsertText1()
         
        Const sText As String = "If you wish to download or view our latest catalogue, please simply follow this link: " & vbNewLine
         
        On Error GoTo ErrHandler
        If TypeName(ActiveWindow) = "Inspector" Then
            If ActiveInspector.IsWordMail And ActiveInspector.EditorType = olEditorWord Then
                ActiveInspector.WordEditor.Application.Selection.TypeText sText
            End If
        End If
        Exit Sub
        
    ErrHandler:
        Beep
         
    End Sub
    
    
    Private Sub InsertText2()
         
        Const sText As String = vbNewLine & "Should you wish to review or enquire about any of our products, please do not hesitate to get in touch." & vbNewLine
         
        On Error GoTo ErrHandler
        If TypeName(ActiveWindow) = "Inspector" Then
            If ActiveInspector.IsWordMail And ActiveInspector.EditorType = olEditorWord Then
                ActiveInspector.WordEditor.Application.Selection.TypeText sText
            End If
        End If
        Exit Sub
        
    ErrHandler:
        Beep
         
    End Sub
    To debug, mouse-click anywhere in the code. Press F8 repeatedly to step through the code. http://www.cpearson.com/excel/DebuggingVBA.aspx

    If your problem has been solved in your thread, mark the thread "Solved" by going to the "Thread Tools" dropdown at the top of the thread. You might also consider rating the thread by going to the "Rate Thread" dropdown.

  3. #3
    Skatonni has this covered, and I didn't have time to post my version yesterday, but it's a little simpler to follow so I have added it to the thread. This version creates the message, but can easily be modified to work with an open message. The essence of either process is to employ the Word editor. Then it is as simple as editing a Word document using VBA.

    Option Explicit
    
    Sub AddHyperlink()
    Dim olEmail As Outlook.MailItem
    Dim olInsp As Outlook.Inspector
    Dim wdDoc As Object
    Dim oLink As Object
    Dim oRng As Object
    Dim strLink As String
    Dim strLinkText As String
    'The texts before and after the link
    Const strText1 As String = "If you wish to download or view our latest catalogue, please simply follow this link: " & vbCr & vbCr
    Const strText2 As String = vbCr & vbCr & "Should you wish to review or enquire about any of our products, please do not hesitate to get in touch."
    
        strLink = "http://www.gmayor.com" ' the link address
        strLinkText = "Click here for Graham Mayor's Web Site " ' the link display text
    
        On Error Resume Next
        Set olEmail = CreateItem(olMailItem)
        With olEmail
            .BodyFormat = olFormatHTML
            Set olInsp = .GetInspector
            Set wdDoc = olInsp.WordEditor
            Set oRng = wdDoc.Range(0, 0)
            oRng.Text = strText1
            oRng.collapse 0
            Set oLink = wdDoc.Hyperlinks.Add(Anchor:=oRng, _
                                 Address:=strLink, _
                                 SubAddress:="", _
                                 ScreenTip:="", _
                                 TextToDisplay:=strLinkText)
            Set oRng = oLink.Range
            oRng.collapse 0
            oRng.Text = strText2
            .Display
        End With
    lbl_Exit:
        Exit Sub
    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
    Quote Originally Posted by skatonni View Post
    Try the code described here.
    Thank you Skatonni for your reply, it worked perfectly. Due to my inexperience I initially got a "compile error: user-defined type not defined" for
    objDoc As Word.Document
    because I hadn't added a reference to Word. Pretty sure you know what I'm talking about , but if someone reads this and needs to know: in the VBA window, go to tools, then references, and tick Microsoft Word.

    Thank you very much again!

  5. #5
    Quote Originally Posted by gmayor View Post
    Skatonni has this covered, and I didn't have time to post my version yesterday, but it's a little simpler to follow so I have added it to the thread. This version creates the message, but can easily be modified to work with an open message. The essence of either process is to employ the Word editor. Then it is as simple as editing a Word document using VBA.
    Thank you very much Graham for your answer. Your code works perfectly (creating a brand new message) and since you mentioned it can be modified to work with an open message, I was curious and tried to play with it but I didn't go very far. Technically my problem is solved, so I am only asking out of curiosity!

    I thought I could replace
    Set olEmail = CreateItem(olMailItem)
    by
    Set olEmail = CurrentItem(olMailItem)
    but I get a compile error: sub or function not defined. Well at least I thought it was worth a shot

  6. #6
    The correct syntax for that line would be
    Set olEmail = ActiveInspector.CurrentItem
    (See Skatonni's code)
    but as you are creating the message anyway why not simply use the macro to create the message?
    Incidentally, if you define the Word elements as Objects, you don't need to add the reference to Word. You will see that my macro uses this (late binding) approach.
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  7. #7
    Thanks Graham, it is useful to know!

    I tend to start from a blank email as I have several macros that insert snippets of text which I use in various combinations. I also use a few macros to open up email templates I saved in the template folder where there's a bit more text in the body. For a hyperlink, I find it more practical to insert with a shortcut (I guess it all depends of content!).

    I am grateful that I now know both options - and, thank you for pointing about defining the Word elements as Objects as I hadn't realised it was an option.

    Cheers,

    Sarah

Posting Permissions

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