Consulting

Results 1 to 11 of 11

Thread: Using VBA to Format between two specific paragraphs

  1. #1
    VBAX Regular
    Joined
    Oct 2016
    Posts
    7
    Location

    Exclamation Using VBA to Format between two specific paragraphs

    Hello Everyone, my name is Kody. I am very new to coding with VBA. Let me explain my situation as simply as possible.

    I have some text in a word document. I need to format paragraph 1 (Top Line/Paragraph) until paragraph 2 (Bottom Line/Paragraph) and every paragraph in-between paragraph 1 and 2. The top line always starts with "WARNING" and the Bottom Line will always have this format "WG002.a 04-15-91" containing numbers and text.

    I need the code to automatically scan the active document for these paragraphs and format accordingly. I have wrote code where I manually select/highlight the test and the run the subroutine to format the paragraphs as I wish. See below, I have included it.
    Another problem I have is asking vba to search for paragraph the contains text and numbers (like paragraph 2) especially when I do not know what the numbers will be.

    This is how the text in the active document would look like:

    WARNING (First Paragraph I need to Format)
    Text/wording (second Paragraph I need to format)
    .... (Format paragraph)
    .... (Format Paragraph)
    .... (Format Paragraph)
    ... (Format Paragraph)
    WG002.A 04-15-91 (Last line I need to format)


    My code:
    Dim WarningParagraphs as New ParagraphFormat
    WarningParagraphs.Alignment = wdAlignParagraphLeft
    WarningParagraphs.Borders.OutsideLineStyle = True
    Selection.Paragraphs.Format = WarningParagraphs
    With Selection
    .Font.Name = "Times New Roman"
    .Font.Size = 12
    .Collapse Direction:=wdCollapseStart
    .InsertBefore "Warning:"
    .Font.Color = RGB (200,0,0)
    .InsertParagraphBefore
    .Font.Bold = True
    End With

  2. #2
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,335
    Location
    You should create a style to apply to the text. This does that for you:

    Sub ScratchMacro()
    'A basic Word macro coded by Greg Maxey
    Dim oRng As Range, oTextRng As Range
    Dim oParStyle As Style, oChrStyle As Style
      On Error Resume Next
      Set oParStyle = ActiveDocument.Styles("Warnings")
      If Err.Number <> 0 Then
        Set oParStyle = ActiveDocument.Styles.Add("Warnings", 1)
        With oParStyle
          With .ParagraphFormat
            .Alignment = wdAlignParagraphLeft
            .Borders.OutsideLineStyle = True
          End With
          With .Font
            .Name = "Times New Roman"
            .Size = 12
          End With
        End With
        Err.Clear
      End If
      Set oChrStyle = ActiveDocument.Styles("Warning")
      If Err.Number <> 0 Then
        Set oChrStyle = ActiveDocument.Styles.Add("Warning", 2)
        With oChrStyle
          .Font.Color = RGB(200, 0, 0)
          .Font.Bold = True
        End With
        Err.Clear
      End If
      Set oRng = ActiveDocument.Range
      With oRng.Find
        .Text = "WARNING*WG[0-9]{1,}"
        .MatchWildcards = True
        While .Execute
          With oRng
            .MoveEndUntil Chr(13)
            .MoveEnd wdCharacter, 1
            .Style = "Warnings"
            Set oTextRng = .Paragraphs(1).Range
            oTextRng.End = oTextRng.End - 1
            oTextRng.Style = "Warning"
            .Collapse wdCollapseEnd
          End With
        Wend
      End With
    lbl_Exit:
      Exit Sub
    End Sub
    Greg

    Visit my website: http://gregmaxey.com

  3. #3
    VBAX Regular
    Joined
    Oct 2016
    Posts
    7
    Location
    Thanks gmaxey, give me a second please. I am going to try it out.

  4. #4
    VBAX Regular
    Joined
    Oct 2016
    Posts
    7
    Location
    gmaxey, I tried your solution. No text was formatted or changed . I also didn't get any errors when I ran your subroutine.

  5. #5
    VBAX Regular
    Joined
    Oct 2016
    Posts
    7
    Location
    I am also using Word 2013 Version

  6. #6
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,335
    Location
    If you run it on the sample text you provided it will change. That is all that I did here:
    Attached Images Attached Images
    Last edited by gmaxey; 10-01-2016 at 08:20 PM.
    Greg

    Visit my website: http://gregmaxey.com

  7. #7
    VBAX Regular
    Joined
    Oct 2016
    Posts
    7
    Location
    Alright, give me a second. I am going to look at it again.

  8. #8
    VBAX Regular
    Joined
    Oct 2016
    Posts
    7
    Location
    I copied your code exactly and it doesn't modify any text . It seems to be never entering your first with statement.

  9. #9
    VBAX Regular
    Joined
    Oct 2016
    Posts
    7
    Location
    Can you provide any comments with your code?

  10. #10
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,335
    Location
    Not now. It is nearly midnight. The attached file has some of your sample text and the code works with it.
    Attached Files Attached Files
    Greg

    Visit my website: http://gregmaxey.com

  11. #11
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,335
    Location
    Code with comments.

    Note if you document doesn't contain something like:

    WARNING
    blah, blah
    blah, blah
    WG0 ...

    Then nothing will be found

    Sub ScratchMacro()
    'A basic Word macro coded by Greg Maxey
    Dim oRng As Range, oTextRng As Range
    Dim oParStyle As Style, oChrStyle As Style
      On Error Resume Next
      'Get a paragraph style you created named Warnings.
      Set oParStyle = ActiveDocument.Styles("Warnings")
      If Err.Number <> 0 Then
        'If you didn't create that style or if it has since been deleted. Create it.
        Set oParStyle = ActiveDocument.Styles.Add("Warnings", 1)
        With oParStyle
          With .ParagraphFormat
            .Alignment = wdAlignParagraphLeft
            .Borders.OutsideLineStyle = True
          End With
          With .Font
            .Name = "Times New Roman"
            .Size = 12
          End With
        End With
        Err.Clear
      End If
      'Get a character style you created named Warning.
      Set oChrStyle = ActiveDocument.Styles("Warning")
      If Err.Number <> 0 Then
        'If you didn't create that style or if it has since been deleted. Create it.
        Set oChrStyle = ActiveDocument.Styles.Add("Warning", 2)
        With oChrStyle
          .Font.Color = RGB(200, 0, 0)
          .Font.Bold = True
        End With
        Err.Clear
      End If
      'Start searching the document.
      Set oRng = ActiveDocument.Range
      With oRng.Find
        'Find "WARNING then any and all text up to an including and instance of
        'WG followed by one or more numbers.
        .Text = "WARNING*WG[0-9]{1,}"
        .MatchWildcards = True
        While .Execute
          With oRng
            'Extend the found range to include the paragraph mark
            .MoveEndUntil Chr(13)
            .MoveEnd wdCharacter, 1
            'Apply the "Warnings" style
            .Style = "Warnings"
            'Apply the Warning character style to the text in first paragraph.
            Set oTextRng = .Paragraphs(1).Range
            oTextRng.End = oTextRng.End - 1
            oTextRng.Style = "Warning"
            .Collapse wdCollapseEnd
          End With
        Wend
      End With
    lbl_Exit:
      Exit Sub
    End Sub
    Greg

    Visit my website: http://gregmaxey.com

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
  •