Consulting

Results 1 to 8 of 8

Thread: Translating Word VBA into Outlook VBA

  1. #1

    Translating Word VBA into Outlook VBA

    [Edited: I made the code a little more bulletproof]

    I scripted two VBA macros for Word documents that I am hoping to make functional in Outlook messages.

    Both commands search for a two-letter string; select the entire word that contains the string, and then copies the word to the clipboard.

    I am having a devil of a time "translating" my Word VBA into Outlook VBA. Can anyone give me a few clues?

    Word script 1:

    Sub Macro11()
    
    ' Collapse the selection to the right, and toggle off Extend mode.
    
    Selection.Collapse Direction:=wdCollapseEnd
    Selection.ExtendMode = False
    
    ' For testing: specify a search string. In the final version, Dragon will provide the value.
    
    Dim x As String
    Let x = "an" ' Search string
    
    ' Search forward for x, and wrap to top if not found.
    
    Selection.Find.ClearFormatting
    With Selection.Find
        .Text = x
        .Forward = True
        .Wrap = wdFindContinue
        .Execute
    End With
    
    ' If text is selected (presumedly because the search string was found) select the entire word and copy it to the clipboard
    
    If Len(Selection) > 1 Then
        Selection.Extend
        Selection.Extend
        Selection.Copy
    Else
        Beep
    End If
    End Sub
    Word Script 2:

    Sub Macro13()
    
    ' Collapse the selection to the right, and toggle off Extend mode.
    
    Selection.Collapse Direction:=wdCollapseEnd
    Selection.ExtendMode = False
    
    ' Redo the most recent search
    
    With Selection.Find
        .Forward = True
        .Wrap = wdFindContinue
        .Execute
    End With
    
    ' If text is selected (presumedly because the search string was found) select the entire word and copy it to the clipboard
    
    If Len(Selection) > 1 Then
        Selection.Extend
        Selection.Extend
        Selection.Copy
    Else
        Beep
    End If
    
    End Sub
    Last edited by acantor; 11-13-2017 at 01:41 PM.

  2. #2
    See if the following helps. The cursor must be in the body of the message

    Sub Macro1()
    Dim oDoc As Object
    Dim oRng As Object
    Dim oWord As Object
    Dim strText As String
        strText = "an"
        On Error GoTo ErrHandler
        If TypeName(ActiveWindow) = "Inspector" Then
            If ActiveInspector.IsWordMail And ActiveInspector.EditorType = olEditorWord Then
                Set oDoc = ActiveInspector.WordEditor
                Set oRng = oDoc.Range
                With oRng.Find
                    Do While .Execute(findText:=strText, MatchCase:=True)
                        Set oWord = oRng.Words(1)
                        MsgBox oWord.Text
                        oRng.collapse 0
                    Loop
                End With
            End If
        End If
    lbl_Exit:
        Set oDoc = Nothing
        Set oRng = Nothing
        Set oWord = Nothing
        Exit Sub
    ErrHandler:
        Beep
        Resume 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

  3. #3
    Thank you for that. It helps... helps me realize that getting comfortable with VBA for Outlook will be a major undertaking. Sigh! I was hoping translating from one dialect of VBA to the other would be relatively straightforward. My assumption was based on knowledge that many keyboard shortcuts in Word work exactly the same in Outlook messages -- even longstanding bugs in Word commands are faithfully reproduced when they are used in Outlook messages. For example, Rotate Case (Shift + F3) fails when the insertion point (cursor) is positioned one character to the left of a punctuation mark. (For example, in the previous sentence, if the cursor is between "mark" and the period, Shift + F3 fails to change the capitalization of "mark.") Case Rotate also fails when the insertion point is at the end of table cell; instead of the command acting on a word, it acts on the entire cell. These problems affected me enough that I was motivated to create a fix using Word VBA.)

    Despite the fact that a faulty Word command is amenable to a VBA repair, I am understanding now that similarities in keyboard interaction in the two programs do not necessarily reflect similarities in the underlying VBA. Lesson learned!

    Any resources people can recommend for self-studying Outlook VBA? I am looking for a resource to guide me during trial-and-error experimentation, which is how I learned Word VBA.
    Last edited by alanc; 11-16-2017 at 09:01 PM.

  4. #4
    Once you identify to the process that you are working in the text editor, the VBA is quite similar to that in Word, though when using late binding to Word as in the example, you must use the numeric equivalent of Word specific commands e.g. from your code - wdFindContinue.

    Lots of useful information at https://www.slipstick.com/outlook-developers/
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  5. #5
    Hi Graham,

    I have been experimenting with your code, and am getting close to achieving what I am trying to achieve. Thank you for your encouragement. The one aspect I have been unable to figure out is how to select the word that contains the found string within the message body, rather than displaying the word in a message box.

    Acting on the message in variable-space is elegant. I would like to get better at doing this. On the other hand, in this situation, I want to show the user the found word in context, and the most familiar way to do this is to select the word. Thus in my code, I am trying to do equivalent of pressing F8 twice to select the focused word, beginning with (VBA Word) ExtendMode toggled off:

    In Word VBA:

    Selection.Extend
    Selection.Extend
    Last edited by alanc; 11-20-2017 at 10:46 AM.

  6. #6
    The macro goes through the message and processes each found item - here as the content of a message box as I didn't know what you wanted to do with the found word. However you can only select one word at a time, so much depends on what you want to do with the word you have found. You can however process the range oWord as you wish each time it is found without selecting it.

    If the word only appears once (or you want the last occurrence) you can change the msgBox reference
    Do While .Execute(findText:=strText, MatchCase:=True) 
          Set oWord = oRng.Words(1) 
          MsgBox oWord.Text 
          oRng.collapse 0 
    Loop
    to
    Do While .Execute(findText:=strText, MatchCase:=True) 
          Set oWord = oRng.Words(1) 
          oWord.Select 
          oRng.collapse 0 
    Loop
    and that will select the last instance of the word in the message. If you want to select the first instance then change oRng.collapse 0 for Exit Do and that will stop the loop after the first find.
    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
    Hi Graham,

    Here is what I am trying to accomplish, with the backstory...

    I am assisting someone who has little use of his arms. For the past several years, he has been using Dragon Professional: speech recognition software.

    Out of the box, Dragon "recognizes" about 250,000 words, which is a very large number when you consider that well-educated and well-read native English speakers use "only" between 20,000 and 35,000 words.

    When any of the 250,000 words appear within the viewport, he can easily copy them to the clipboard by saying "copy [word]." For example, to copy the second word in this sentence, he could say "copy example."

    But he needs to copy non-English words that appear somewhere -- not necessarily at the top -- of Outlook email messages. (Then he pastes the words into a different application.)

    But Dragon does not recognize any of these words, as they are outside of Dragon's base vocabulary. (Although it's possible to add words to Dragon's dictionary, this approach is not practical in this case.)

    Dragon supports several methods for selecting and copying words that are outside of its base vocabulary, but these methods are complex, time-consuming, and error-prone. However, I have developed a way for him to zero in on any word by taking advantage of the fact that almost every non-English word he encounters has two unique consecutive letters. For example:

    Krokermann
    Parmahanse
    Aadama

    Each of these words has several unique letter pairs. For the first: KR, RM, NN, etc. For the second: PA, HA, AN, SE, etc. For the third: the most obvious pair is AA.

    So I created a custom Dragon command called "Next [character][character]." The command searches through the text, and selects AND copies the found word. For example, to copy the first word, he might say "Next K R." To copy the third word, he would say "Next AA."

    The method works brilliantly: it takes but a second to select and copy a word, compared to 10 or 20 seconds using standard methods.

    Right now, my Dragon script performs the actions via Outlook's user interface, but it's somewhat unreliable. The UI method works about 90% of the time, which I would like to boost to 100% by doing the heavy lifting programmatically.

    So to make this Dragon script work, I really need two Outlook macros:

    The first macro obtains the two letters from Dragon. Then...

    1. Start searching forward from the current cursor position -- not from the top.
    2. If the search string does not appear anywhere in the message, quit.
    3. If the search string is found, select the word and copy it to the clipboard.

    The second macro is for situations when the two letters appear more than once within the viewport. So the second macro is a mechanism for locating the next instance of the two letters, but without the need to re-input them.

    (So if this were a Word macro, I imagine I would need to specify the variable that holds the search string as Public... not sure how to do this in Outlook, yet!)

    I hope it's not too much to ask for help with this project... If his guy needed to select the words in Word rather than in Outlook, then I could script the VBA myself!

  8. #8
    Outlook works with public variables also. In fact once you have identified to the macro that you are working in the Word editor, the code is very similar to that of Word.

    I have annotated the following macros. Each time you run the TestFunction macro, it looks for the string (here 'an') in the message body from the cursor position. It copies the word containing the string to the clipboard, reports the word in a message box and sets the cursor position immediately after the word. If the string is not found the message box will be empty.

    Run the macro again to repeat the search from the new position.

    Hopefully that helps?

    Sub TestFunction()
    MsgBox FindAndCopy("an")
    End Sub
    
    Function FindAndCopy(strText As String) As String
        Dim oDoc As Object
        Dim oRng As Object
        Dim oWord As Object
        'On Error GoTo ErrHandler
        If TypeName(ActiveWindow) = "Inspector" Then
            If ActiveInspector.IsWordMail And ActiveInspector.EditorType = olEditorWord Then
                'set a variable to the document body
                Set oDoc = ActiveInspector.WordEditor
                'set a range to the cursor position
                Set oRng = oDoc.Application.Selection.Range
                'move the end of the range to the end of the document
                oRng.End = oDoc.Range.End
                'Look for the string in the range
                With oRng.Find
                    'if the string is found
                    Do While .Execute(findText:=strText, MatchCase:=True)
                        'set the range to the word containing the string
                        Set oWord = oRng.Words(1)
                        FindAndCopy = oWord 'output the word from the function
                        'copy the word to the clipboard
                        oWord.Copy
                        'collapse the range to the end of the word
                        oWord.collapse 0
                        'Put the cursor at the end of the word
                        oWord.Select
                        'and stop looking
                        Exit Do
                    Loop
                End With
            End If
        End If
    lbl_Exit:
        Set oDoc = Nothing
        Set oRng = Nothing
        Set oWord = Nothing
        Exit Function
    ErrHandler:
        Beep
        Resume lbl_Exit
    End Function
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

Posting Permissions

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