Results 1 to 20 of 20

Thread: Determine if page has a footnote

  1. #1

    Determine if page has a footnote

    Is there a way to check if a given page has any footnotes on it?

  2. #2
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    You can check easily enough whether it has a footnote reference, but that's not the same as saying the footnote's text all appears on that page. I have one document with about 1.5 pages of text in a single footnote. Obviously, only part of that is going to fit on the same page as the footnote reference.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  3. #3
    Thanks, this is my first attempt based upon your suggestion. I still have to deal with footnotes that flow over to another page.
    It seems to work, but I would appreciate your professional opinion.
    [VBA]Function DoesPageHaveFootnote(PageNo As Single) As Boolean
    Dim oRng As Range
    Dim i As Long
    ActiveDocument.ComputeStatistics wdStatisticPages
    Selection.GoTo What:=wdGoToPage, Name:=PageNo
    Set oRng = Selection.Bookmarks("\page").Range
    oRng.Collapse wdCollapseStart
    With oRng.Find
    .Text = Chr(2)
    While .Execute And oRng.InRange(ActiveDocument.Bookmarks("\Page").Range)
    i = i + 1
    Wend
    End With
    If i > 1 Then
    DoesPageHaveFootnote = True
    Else
    DoesPageHaveFootnote = False
    End If
    i = 0
    End Function[/VBA]

    Thanks again

  4. #4

  5. #5
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    Your function could be reduced to either of:
    [vba]Function DoesPageHaveFootnote(PageNo As Long) As Boolean
    Dim oRng As Range
    Selection.GoTo What:=wdGoToPage, Name:=PageNo
    Set oRng = Selection.Bookmarks("\page").Range
    DoesPageHaveFootnote = (oRng.Footnotes.Count > 0)
    End Function[/vba]
    or, to return the count:
    [vba]Function DoesPageHaveFootnote(PageNo As Long) As Long
    Dim oRng As Range
    Selection.GoTo What:=wdGoToPage, Name:=PageNo
    Set oRng = Selection.Bookmarks("\page").Range
    DoesPageHaveFootnote = oRng.Footnotes.Count
    End Function[/vba]
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  6. #6
    Any ideas how to tell if the page has an "overflowed" footnote?

  7. #7
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  8. #8
    Thank you, but that will only tell if a footnote overflowed, but not if the page has an overflowed footnote.

    Unless there's a way to get the page number that a footnote's reference is on, check the footnote and if it over flows then the we know that next page has a footnote.

  9. #9
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    You could easily enough derive that by testing the last preceding footnote ...
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  10. #10
    Can I trouble you for a sample?

  11. #11
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    Try:
    [vba]Sub Test()
    Dim oRng As Range, StrStats As String, i As Long
    StrStats = GetFootnoteStats(ActiveDocument, 2)
    i = Split(StrStats, ",")(0)
    If i > 1 Then
    i = i - 1
    End If
    MsgBox "Does the first bookmark start on the previous page? A: " & _
    fFootNoteIsSplit(i, ActiveDocument)
    i = Split(StrStats, ",")(1)
    MsgBox "Does the last bookmark end on the next page? A: " & _
    fFootNoteIsSplit(i, ActiveDocument)
    End Sub
    '
    Function GetFootnoteStats(wdDoc As Document, PageNo As Long) As String
    Dim oRng As Range, i As Long, j As Long
    GetFootnoteStats = "0,0"
    Set oRng = wdDoc.GoTo(What:=wdGoToPage, Name:=PageNo)
    Set oRng = oRng.Bookmarks("\page").Range
    If oRng.Footnotes.Count > 0 Then
    i = oRng.Footnotes(1).Index
    End If
    If oRng.Footnotes.Count > 0 Then
    j = oRng.Footnotes(oRng.Footnotes.Count).Index
    End If
    GetFootnoteStats = i & "," & j
    End Function
    '
    Public Function fFootNoteIsSplit(ByRef lngFootnote As Long, _
    Optional oDoc As Document) As Boolean
    Dim oPage As Page
    Dim oRec As Rectangle
    Dim oFN As Footnote
    Dim oFNStart As Word.Range
    Dim oFNEnd As Word.Range
    Dim bStartonPage As Boolean
    Dim bEndonPage As Boolean
    Dim lngView As Long
    If oDoc Is Nothing Then Set oDoc = ActiveDocument
    lngView = oDoc.ActiveWindow.ActivePane.View.Type
    If lngView <> wdPrintView Then
    oDoc.ActiveWindow.ActivePane.View.Type = wdPrintView
    End If
    Set oFN = oDoc.Footnotes(lngFootnote)
    Set oFNStart = oFN.Range
    oFNStart.Collapse wdCollapseStart
    Set oFNEnd = oFN.Range
    oFNEnd.Collapse wdCollapseEnd
    Set oPage = oDoc.ActiveWindow.ActivePane.Pages(oFN.Range.Information(wdActiveEndPageNum ber))
    bStartonPage = False
    bEndonPage = False
    For Each oRec In oPage.Rectangles
    If oFNStart.InRange(oRec.Range) Then
    bStartonPage = True
    Exit For
    End If
    Next oRec
    For Each oRec In oPage.Rectangles
    If oFNEnd.InRange(oRec.Range) Then
    bEndonPage = True
    Exit For
    End If
    Next oRec
    If bStartonPage And bEndonPage Then
    fFootNoteIsSplit = False
    Else
    fFootNoteIsSplit = True
    End If
    oDoc.ActiveWindow.ActivePane.View.Type = lngView
    End Function[/vba]
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  12. #12
    Whats the point of
    [VBA]If i > 1 Then
    i = i - 1
    End If[/VBA]

  13. #13
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    Try the code without it on the first footnote in a document and what do you suppose would happen?
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  14. #14
    I tried the code both with and without it on all pages, and it always returned the same results.

  15. #15
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    Put it this way - there is no such thing as ActiveDocument.Footnotes(0). Trying to reference it (eg MsgBox ActiveDocument.Footnotes(0).Index) will cause an error.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  16. #16
    Sorry my bad, I also removed the i = i - 1 line. I see what you are saying.

  17. #17
    Based on all the help received in this thread this is my proposed solution. Comments are welcome.

    [VBA]Option Explicit

    Dim colPagesWithFootnotes As New Collection

    Sub Test()
    Dim varItem As Variant
    LoopAllPages
    For Each varItem In colPagesWithFootnotes
    Debug.Print varItem
    Next varItem
    Debug.Print fIsInCollection(colPagesWithFootnotes, 1)
    End Sub

    Sub LoopAllPages()
    Dim oRng As Range
    Dim i As Integer
    Dim lngPgNo As Long
    With ActiveDocument
    For i = 1 To ActiveDocument.BuiltInDocumentProperties(wdPropertyPages)
    Set oRng = .GoTo(What:=wdGoToPage, Name:=i)
    Set oRng = oRng.GoTo(What:=wdGoToBookmark, Name:="\page")
    lngPgNo = oRng.Information(wdActiveEndPageNumber)
    If oRng.Footnotes.Count > 0 Then
    If fIsInCollection(colPagesWithFootnotes, lngPgNo) = False Then
    colPagesWithFootnotes.Add lngPgNo
    End If
    If fDoesPageHaveOverflowingFootnote(i) Then
    If fIsInCollection(colPagesWithFootnotes, lngPgNo + 1) = False Then
    colPagesWithFootnotes.Add lngPgNo + 1
    End If
    End If
    End If
    Next i
    End With
    End Sub

    Public Function fIsInCollection(col As Collection, Item As Variant) As Boolean
    Dim var As Variant
    On Error GoTo ERROR_TRAP
    fIsInCollection = True
    var = col(Item)
    Exit Function
    ERROR_TRAP:
    fIsInCollection = False
    End Function

    Function fDoesPageHaveOverflowingFootnote(PageNo As Integer, Optional wdDoc As Document) As String
    Dim oRng As Range, i As Long
    If wdDoc Is Nothing Then Set wdDoc = ActiveDocument
    Set oRng = Selection.GoTo(What:=wdGoToPage, Name:=PageNo)
    Set oRng = oRng.Bookmarks("\page").Range
    If oRng.Footnotes.Count > 0 Then
    i = oRng.Footnotes(oRng.Footnotes.Count).Index
    fDoesPageHaveOverflowingFootnote = fFootNoteIsSplit(i)
    Else
    fDoesPageHaveOverflowingFootnote = False
    End If
    End Function

    Public Function fFootNoteIsSplit(ByRef lngFootnote As Long, _
    Optional oDoc As Document) As Boolean
    Dim oPage As Page
    Dim oRec As Rectangle
    Dim oFN As Footnote
    Dim oFNStart As Word.Range
    Dim oFNEnd As Word.Range
    Dim bStartonPage As Boolean
    Dim bEndonPage As Boolean
    Dim lngView As Long
    If oDoc Is Nothing Then Set oDoc = ActiveDocument
    lngView = oDoc.ActiveWindow.ActivePane.View.Type
    If lngView <> wdPrintView Then
    oDoc.ActiveWindow.ActivePane.View.Type = wdPrintView
    End If
    Set oFN = oDoc.Footnotes(lngFootnote)
    Set oFNStart = oFN.Range
    oFNStart.Collapse wdCollapseStart
    Set oFNEnd = oFN.Range
    oFNEnd.Collapse wdCollapseEnd
    Set oPage = oDoc.ActiveWindow.ActivePane.Pages(oFN.Range.Information(wdActiveEndPageNum ber))
    bStartonPage = False
    bEndonPage = False
    For Each oRec In oPage.Rectangles
    If oFNStart.InRange(oRec.Range) Then
    bStartonPage = True
    Exit For
    End If
    Next oRec
    For Each oRec In oPage.Rectangles
    If oFNEnd.InRange(oRec.Range) Then
    bEndonPage = True
    Exit For
    End If
    Next oRec
    If bStartonPage And bEndonPage Then
    fFootNoteIsSplit = False
    Else
    fFootNoteIsSplit = True
    End If
    oDoc.ActiveWindow.ActivePane.View.Type = lngView
    End Function
    [/VBA]

  18. #18
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    I've just had occasion to revisit this.

    Instead of:
    Set oRng = oRng.Bookmarks("\page").Range
    Use:
    Set oRng = oRng.GoTo(What:=wdGoToBookmark, Name:="\page")

    There also seem to be some issues with the fFootNoteIsSplit function, but I don't have time to delve into that right now.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  19. #19
    Thank you, I would appreciate any input on the fFootNoteIsSplit function if and when you have time. So far it seems to work, but I'm interested to see what you can dig up.

  20. #20
    VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,273
    Location
    One issue I've found is that the code changes the selection. That's easily fixed by changing:
    Set oRng = Selection.GoTo(What:=wdGoToPage, Name:=PageNo)
    Set oRng = oRng.Bookmarks("\page").Range
    in the 'fDoesPageHaveOverflowingFootnote' function to:
    Set oRng = wdDoc.GoTo(What:=wdGoToPage, Name:=PageNo)
    Set oRng = oRng.GoTo(What:=wdGoToBookmark, Name:="\page")
    (note that this incorporates the change referred to in my previous post)

    Another issue is that it doesn't seem to report the pages spanned by the identified footnotes. I have a copy of an academic book, where one footnote spans two page breaks. For some code to retrieve the page #s on which the footnote references to split footnotes occur, try:
    Sub GetSplitFtNtPages()
    Dim oRng As Range, i As Long, wdDoc As Document, StrPages As String, StrOut As String
    Set wdDoc = ActiveDocument
    With wdDoc
      For i = 1 To .ComputeStatistics(wdStatisticPages)
        If fDoesPageHaveOverflowingFootnote(i, wdDoc) Then
          StrPages = StrPages & i & " "
        End If
      Next
    End With
    StrPages = Trim(StrPages)
    StrPages = Replace(StrPages, " ", ", ", 1, UBound(Split(StrPages, " ")) - 1)
    StrPages = Left(StrPages, InStrRev(StrPages, " ")) & "& " & _
      Right(StrPages, Len(StrPages) - InStrRev(StrPages, " "))
    MsgBox "Split footnotes begin on pages: " & StrPages
    End Sub
    Note: I've converted your Integer variables to Long
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

Posting Permissions

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