Consulting

Results 1 to 11 of 11

Thread: Word VBA count all cross references in main body of the document

  1. #1
    VBAX Regular
    Joined
    Mar 2019
    Posts
    9
    Location

    Lightbulb Word VBA count all cross references in main body of the document

    Hi all

    New to word VBA, I need a macro that can all all cross reference (field codes) in a word document with a message box of the numbers.

    Is this possible, if so, how.

    Thanks in advance.

    E.

  2. #2
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    Please clarify: Do you need a count of all fields, or only of cross-reference fields?
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  3. #3
    VBAX Regular
    Joined
    Mar 2019
    Posts
    9
    Location

    Word VBA count all cross references in main body of the document

    Quote Originally Posted by macropod View Post
    Please clarify: Do you need a count of all fields, or only of cross-reference fields?
    Need a count of all the cross reference fields.

    Thanks

  4. #4
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    You can get that without VBA, by pressing Alt-F9 to expose field codes in the document, then using Find with:
    Find = ^d REF
    and/or
    Find = ^d PAGEREF
    The first will return a count of cross references to the referenced text; the second will return a count of cross references to their pages.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  5. #5
    VBAX Regular
    Joined
    Mar 2019
    Posts
    9
    Location
    Quote Originally Posted by macropod View Post
    You can get that without VBA, by pressing Alt-F9 to expose field codes in the document, then using Find with:
    Find = ^d REF
    and/or
    Find = ^d PAGEREF
    The first will return a count of cross references to the referenced text; the second will return a count of cross references to their pages.
    Thanks for this, however, I have about 400 documents that I need to count the number of cross references in. Ideally, I would like to enter the file path of the documents and get an excel spreadsheet with the document name in one column and the number of Xrefs in another column.
    I am not sure what the best approach for this.

    Thanks for your help.
    E

  6. #6
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    Your first post referred only to:
    cross reference (field codes) in a word document with a message box of the numbers
    not in "about 400 documents". Kindly provide full details of what you require - doubtless not 400 message boxes - before someone wastes time coding for something different.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  7. #7
    VBAX Regular
    Joined
    Mar 2019
    Posts
    9
    Location
    Apologies for the changes in the actual request. This is a developing request and I now have the full requirement for the VBA. Need to be able to count the number of cross references in documents without actually opening them.

    Scenario - documents saved in a folder, insert the folder name in the code, code loops through all document and create a table either in word or Excel with the document name and the number of Xrefs found.

    I am open to any suggestions of how to get this done.

    Hope this makes sense.

    Once again, my apologies.
    E

  8. #8
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    Try the following Excel macro. It includes a folder browser so you can select the folder to process.
    Sub GetDocRefs()
    'Note: this code requires a reference to the Word object model.
    'See under the VBE's Tools|References.
    Application.ScreenUpdating = False
    Dim wdApp As New Word.Application, wdDoc As Word.Document
    Dim strFolder As String, strFile As String, f As Long, i As Long, r As Long
    strFolder = GetFolder: If strFolder = "" Then GoTo ErrExit
    strFile = Dir(strFolder & "\*.doc", vbNormal)
    While strFile <> ""
      Set wdDoc = wdApp.Documents.Open(FileName:=strFolder & "\" & strFile, AddToRecentFiles:=False, Visible:=False)
      r = r + 1: i = 0
      With wdDoc
        For f = 1 To .Fields.Count
          Select Case .Fields(f).Type
            Case wdFieldPageRef, wdFieldRef: i = i + 1
          End Select
        Next
        .Close SaveChanges:=False
      End With
      ActiveSheet.Range("A" & r).Value = strFile
      ActiveSheet.Range("B" & r).Value = i
      strFile = Dir()
    Wend
    wdApp.Quit
    Set wdDoc = Nothing: Set wdApp = Nothing
    Application.ScreenUpdating = True
    End Sub
     
    Function GetFolder() As String
        Dim oFolder As Object
        GetFolder = ""
        Set oFolder = CreateObject("Shell.Application").BrowseForFolder(0, "Choose a folder", 0)
        If (Not oFolder Is Nothing) Then GetFolder = oFolder.Items.Item.Path
        Set oFolder = Nothing
    End Function
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  9. #9
    VBAX Regular
    Joined
    Mar 2019
    Posts
    9
    Location
    Thanks, this works perfectly.

  10. #10
    VBAX Regular
    Joined
    Mar 2019
    Posts
    9
    Location
    Hi there, is it possible to add another column to count number number of pages.

    Thanks

  11. #11
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    To do that, you might change:
        .Close SaveChanges:=False
      End With
      ActiveSheet.Range("A" & r).Value = strFile
      ActiveSheet.Range("B" & r).Value = i
    to:
        ActiveSheet.Range("A" & r).Value = strFile
        ActiveSheet.Range("B" & r).Value = i
        ActiveSheet.Range("C" & r).Value = .ComputeStatistics(wdStatisticPages)
        .Close SaveChanges:=False
      End With
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

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
  •