PDA

View Full Version : [SOLVED:] Counting pages within sections and printing this as text



ceilidh
08-24-2012, 11:19 AM
Hello,

I'm having trouble getting some VBA code to work, and have been searching for inspiration. I'm hoping someone here could help. I am using Word 2010.

I have a document with several sections. Within each section are several pages with a page break at the end of each page, except for the last page in each section which has a section break at the end.

I have a "Page X of N" in the top right corner where N is the last page of the whole document, and X is the current page of the whole document. This is fine.

However, I also need another "Page x of n" where n is the last page of the section and x is the current page of the section. I can't use SECTIONPAGES since I'm already using NUMPAGES for the "Page X of N". So, I thought I would write a macro to produce a text "Page x of n" and imprint that text on each page. (I know this wouldn't be dynamic but since every page has either a page break or a section break on it, the document isn't dynamic when it comes to the pages shifting anyway)

So I'm trying to do this:

Loop through the document finding each section (using text="^b") and then doing this for every section:
(a) compute the total number of pages in the section
(b) loop through "i = 1 to the <total number of pages in the section> " and within this loop do this:
(bb) Create a text string "Page x of n" using i to populate the x bit, and using <total number of pages in the section> to populate the n bit. Then print this as non-dynamic text on the bottom left/center/right of the page.

Maybe I am trying to nest too many loops and running into trouble there, but my code does not work. It seems like this should be quite easy - am I wrong there? I'll be grateful for any help anyone could offer.

Thanks!

Frosty
08-24-2012, 12:00 PM
There are numerous threads about the concept of pages in Word. Rather than rehash these discussions, especially for a first time poster, can you do the following:

1. Make sure any cross-posts you've done are adequately documented (asked this question at multiple forums? Then post links at each and every forum you've posted the question to all the other forums you've posted the question at-- so that you don't have multiple people all trying to help you)

2. Post the code you're attempting to use thus far.

Thanks!

Frosty
08-24-2012, 12:02 PM
Oh, and it's actually not an easy task, this "how many pages in my document" question, even though it seems like it should be. There are multiple strategies involved. But you should do some searches on this forum (and others) and then show us what strategy you're currently attempting to implement.

Also -- use of manual page breaks is not a recommended way of breaking pages. You will end up with blank pages. Look at the paragraph formatting option of "Page Break Before" for a better way of creating a new page.

ceilidh
08-24-2012, 12:22 PM
Frosty,

Thanks. I haven't cross-posted anywhere. This is my only post about this.

Also, I've googled page numbering and read all kinds of posts and webpages about it because I was hoping to avoid having to ask. I haven't come across anyone who has posted about within-section numbering of a multi-section document, and printing that page numbering as text. If you know where I could find that kind of code, I'll go read up on it...

Also, I don't have a choice about the manual page breaks, they are already there in the document. I'm working with existing documents.

Here's my code. It's a mess. I've been tweaking and trying different things!

Sub Page_Numbering_Within_Sections()
Dim Pgs As Long
Dim PageNumber As Long
Dim Cnt As Long
With ActiveDocument
'Go to start of doc
Selection.HomeKey Unit:=wdStory
PageNumber = 0
With Selection.Find
Do While .Execute(FindText:="^b", Forward:=True) = True
' resize to NOT include Section break
.MoveEnd Unit:=wdCharacter, Count:=-1
' get number of pages
Pgs = .ComputeStatistics(wdStatisticPages)
'print page numbers as text
'do i = 1 to Pgs
PageNumber = PageNumber + 1
Selection.EndKey Unit:=wdStory
ActiveDocument.Content.InsertAfter (("Page" & PageNumber) "of " & Pgs)
Cnt = Len(Trim("Page " & PageNumber)) "of " & Pgs)
Selection.MoveRight Unit:=wdCharacter, Count:=Cnt, Extend:=wdExtend
Selection.Style = ActiveDocument.Styles("Normal")
Selection.Font.Color = wdColorBlack
Loop
End With
End With
End Sub

Frosty
08-24-2012, 02:03 PM
Here's a link to peruse
EDIT: removed one, as it's not helpful

http://www.vbaexpress.com/forum/showthread.php?t=42008

Also, check out using the VBA tags, to bracket your code so it's a little more readable...


Sub MySub
'some comments
Debug.Print ActiveDocument.FullName
End SuB

Frosty
08-24-2012, 02:39 PM
Hmm, this is actually a bit of a brain teaser.

I'm going to simplify what you want, suppose a 2 section, 10 page document. 5 Pages in each section.

You want to have "real" page 6 have both...
Page 6 of 10 ("real page" and "total pages")
And
Page 1 of 5 ("page number in section" and "total pages in this section")

on the same page?

I don't think the problem is sorting out total pages and number of pages in section... I don't think you can have two different page number formats displayed.

Am I articulating your problem accurately?

gmaxey
08-24-2012, 02:41 PM
I think I have your situation covered here: http://gregmaxey.mvps.org/word_tip_pages/page_numbering.html

Frosty
08-24-2012, 02:44 PM
And, incidentally... there are no problems with using NUMPAGES and SECTIONPAGES... the problem is there is only one PAGE field. And that displays a number which reflects the real page number or the relative page number.

While you can change that per section, you can not have two values (in my understanding) within a single section.

So you can get your hypothetical page 6 from the above post to show...
Page 6(PAGE) of 10(NUMPAGES), Page 6(PAGE) of 5(SECTIONPAGES)
OR
Page 1(PAGE) of 10(NUMPAGES), Page 1(PAGE) of 5(SECTIONPAGES)

Have you looked at some alternate way of formatting... utilization of the Chapter formatting option (requires using heading styles, etc).

Unless someone else has some ideas, I think you're going to need to explain more about the overall architecture of the document you're trying to create, and why this is a design requirement, so maybe we can help you brainstorm a way of getting what you want to get...

Frosty
08-24-2012, 02:45 PM
OR... you could follow Greg Maxey's link, which is fantastic.

:-D

Perfect, Greg...

ceilidh
08-24-2012, 03:09 PM
Hmm, this is actually a bit of a brain teaser.

I'm going to simplify what you want, suppose a 2 section, 10 page document. 5 Pages in each section.

You want to have "real" page 6 have both...
Page 6 of 10 ("real page" and "total pages")
And
Page 1 of 5 ("page number in section" and "total pages in this section")

on the same page?

I don't think the problem is sorting out total pages and number of pages in section... I don't think you can have two different page number formats displayed.

Am I articulating your problem accurately?

Yes, that is it exactly.

I can't use PAGE, NUMPAGES, SECTIONPAGE, because of the problem with PAGE - I could start numbering from 1 for each new section or from the start of the doc, but not both.

As for the document architecture... which you asked about in a subsequent post. It's difficult to describe without breaching confidentiality. This is research, and the documents go to the government. I'll try and describe it without giving too much away, and you'll have to tell me if I'm being obscure.

Each document runs to thousands of pages. They consist of tables. One table per page. The tables are grouped according to subject, so for example the tables presenting data about A are all collected into Section 1. The tables presenting data about B are all collected into Section 2. The tables presenting data about C are all collected into Section 3. And so on. The number of sections fluctuates but depends on whether we present data for A to F, meaning 6 sections, or whether we present data for A to P, meaning 16 sections, and so on.

Section 1 could be 100 pages long consisting of 100 tables (1 per page). Section 2 could be 300 pages long, consisting of 300 tables, (1 per page). Section 3 could be 50 pages long.... These are not short documents with short sections. This is why the page numbering within section is wanted in addition to the overall page numbering of the entire document. The overall page numbering tells the government that they're looking at Page 500 of a 1020 page document. And the within section numbering tells the government that they're looking at Page 50 of a section that consists of a total 200 pages (tables) of data about A (or B or C).

Basically given the size of these docs, we need to know how many pages of data we have about A, and B, and C, in addition to how many pages we have overall.

Does that help at all?

I'm going to go read the link you posted for me now. I already looked at Greg's link, but that looks like a manual solution - these docs are too large for a manual solution.

This is why I thought the best way to do it is to leave PAGE and NUMPAGE to give us the overall X of N, but then make a text/character string saying "page x of n" and just stamp that on the bottom of each page, to give us the within-section numbering.

Frosty
08-24-2012, 03:38 PM
Well, the length of the document doesn't really matter... it's the architecture that matters. You can't have different text on every page of a document unless 1) each page of the document is a separate section (with the Same As Previous link broken) or 2) the text which is different is within a field (like PAGE).

I wouldn't bother reading my link... it's not going to help you, now that I understand the problem.

Know that all solutions are manual... all VBA can do is speed up a manual process. It doesn't provide you functionality that doesn't exist.

Greg's solution will work, it's just a question of using VBA to make it a very fast "manual" solution... but ultimately you're going to need to have derived values contained in a field based on perviously derived values.

And what you want is functionality that doesn't exist.

However, since you're dealing with all these tables... you probably have some sort of bookmark or reference fields which refer to a table title or something. Have you looked at the PAGEREF field? Because that seems to me to be the area where we could find a solution. However, you may be able to reference some existing bookmarks.

{PAGE} of {SECTIONPAGE} gives you the internal number.

The "real" numbering has to use some combination of PAGEREF and a built up value in the vein of Greg's solution.

Can you try out Greg's solution for a couple of sections and see if it will work?

Do you already know about bookmarks and how to use them?

Frosty
08-24-2012, 05:22 PM
A bit of a brain teaser, as I said.

This is breakable, but this may service as a demo. This has three major components:

1. A function which gets page numbers of a given section
2. A function which puts dummy text into every primary header, unlinking that header and making sure page numbers start at 1 for that header
3. A function which replaces the bits of dummy text with the appropriate fields, with a "special case" scenario for inserting a nested field.

This is basically a coded version of Greg's solution (using a formula field to display both the current page number of the section + the total number of pages of the previous sections thus far).

Major problem (besides what I've articulated in the fGetPageNumbers function, from the other thread I linked to) is that this is a hard-coded number. It is not dynamic. So if you add a page to section 2, you'll need to re-run this macro.

No matter what scenario (using a PageRef or a hard-coded number of pages), you're going to run into problems of breakability (deleted bookmarks vs. non-dynamic page numbering) and accuracy of page numbering. So... caveat emptor.


Public Sub DemoPageNumbersANDSectionNumbers()
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lCurPageCount As Integer
Set oDoc = ActiveDocument
For Each oSec In ActiveDocument.Sections
'replace with the "right" header?
With oSec.Headers(wdHeaderFooterPrimary)
'turn off link to previous
.LinkToPrevious = False
'make sure we're starting our page numbers for this section at 1
.PageNumbers.StartingNumber = 1
'create some dummy placeholder text
'X = PAGE, Y = SECTIONPAGES, A = REALPAGES, B = NUMPAGES
.Range.text = "Section Page [*X*] of [*Y*]" & vbCr & _
"Document Page [*A*] of [*B*]"
'now replace our placeholders
ReplacePlaceHolderWithField .Range, "[*X*]", "PAGE"
ReplacePlaceHolderWithField .Range, "[*Y*]", "SECTIONPAGES"
ReplacePlaceHolderWithField .Range, "[*B*]", "NUMPAGES"
'the tricky one
ReplacePlaceHolderWithField .Range, "[*A*]", "= ( {PAGE} + " & lCurPageCount & ")"
End With
'get the page numbers
lSecPageNums = fGetPageNumbers(oSec.index)
'get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
End Sub

'replace a place holder with a field code
Public Sub ReplacePlaceHolderWithField(rngHF As Range, sPlaceHolder As String, sFieldText As String)
Dim rngWorking As Range
Dim oField As Field
Dim oField2 As Field
Set rngWorking = rngHF.Duplicate
If rngWorking.Find.Execute(FindText:=sPlaceHolder, MatchCase:=True) Then
Set oField = rngWorking.Fields.Add(rngWorking, , sFieldText, False)
End If
'special case for our nested field
If InStr(sFieldText, "{PAGE}") > 0 Then
Set rngWorking = rngHF.Duplicate
rngWorking.Collapse wdCollapseStart
Set oField2 = rngWorking.Fields.Add(rngWorking, , "PAGE", False)
oField2.Cut
oField.ShowCodes = True
If rngWorking.Find.Execute(FindText:="{PAGE}") Then
rngWorking.Paste
End If
oField.Update
End If
End Sub

'return the total number of page numbers of the passed section number
'NOTE: this methodology fails to give accurate page numbers in several scenarios:
'hidden text, continuous section breaks, a variety of print drivers on long documents, etc
Public Function fGetPageNumbers(iSecNum As Integer) As Integer
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer
'functions should generally have error trapping
On Error GoTo l_err
With ActiveDocument
'get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'and the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function

EDITS: better explanation, a change of the place holder text, since "[ B ]" (no spaces, no quotes) was made lower-case by the BB software, think it was a "bold" code.

Frosty
08-24-2012, 05:45 PM
Coding solution aside (and the above is just a proof-of-concept, I still think Greg's methodology would provide you better dynamism), there are some problems in either approach.

Accurate page counting in Word is tricky at best, even on the simpler side.

The *best* way to do what you're doing would be to separate out each of your sections into separate documents, and use a PAGE/SECTIONPAGES/PAGE + #/NUMPAGES solution, where you build the documents in order, print the document to a .pdf file, and then build the next file, replacing the # with the actual number of pages of the previous .pdf.

And the at the end of the process, you would combine all of these .pdfs into a single .pdf when you were ready to publish the document.

Other than that, almost any scenario will give you bad or inaccurate page numbers at times (the link I provided goes into more detail regarding printer drivers and the way the page numbers are calculated).

However, if the proof-of-concept above seems to work on a copy of one of your typical documents, then we could probably tweak it a bit to go from proof-of-concept to a "will work the majority of the time when you press the button" kind of macro.

ceilidh
08-24-2012, 07:49 PM
Whoa - I think I was definitely trying to bite off more than I could chew, then!

I have to admit, I'm not even a VBA programmer. I'm a lot of things but just winging VBA. (I didn't want to be reduced to typing Page x of n on every page which is why I'm trying to figure out some VBA now...)

These documents are always in the same format - they are produced as the end product of a software program where multiple tables get exported into Word documents.

I can't use PDF. They have to be Word. I really don't have much/any flexibility when it comes to these documents ... they are standardized and have to follow a template.

I should mention, for the Page X of N (overall paging) this is in the top right corner of the doc, in the first header. The Page x of n (within section paging) is supposed to be bottom center of the page. (I was trying bottom right in my code though.) There are varying numbers of footnotes - one section might only have 1 footnote while another section has 10... so I was trying to put the bottom center page x of n underneath the last footer.

It's very late in my day now, but I will copy your code and try it out on one of the documents. Thanks for taking this time... I really had no idea it would be this complex. I'll get back to you tomorrow and report how the code works on a document. I think I'm going to have to step through it and watch what is happening, to understand what it is doing...

gmaxey
08-25-2012, 10:00 AM
Jason,

Bright fellow!! One change:


Make sure we're starting our page numbers for this section at 1
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With



A bit of a brain teaser, as I said.

This is breakable, but this may service as a demo. This has three major components:

1. A function which gets page numbers of a given section
2. A function which puts dummy text into every primary header, unlinking that header and making sure page numbers start at 1 for that header
3. A function which replaces the bits of dummy text with the appropriate fields, with a "special case" scenario for inserting a nested field.

This is basically a coded version of Greg's solution (using a formula field to display both the current page number of the section + the total number of pages of the previous sections thus far).

Major problem (besides what I've articulated in the fGetPageNumbers function, from the other thread I linked to) is that this is a hard-coded number. It is not dynamic. So if you add a page to section 2, you'll need to re-run this macro.

No matter what scenario (using a PageRef or a hard-coded number of pages), you're going to run into problems of breakability (deleted bookmarks vs. non-dynamic page numbering) and accuracy of page numbering. So... caveat emptor.


Public Sub DemoPageNumbersANDSectionNumbers()
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lCurPageCount As Integer
Set oDoc = ActiveDocument
For Each oSec In ActiveDocument.Sections
'replace with the "right" header?
With oSec.Headers(wdHeaderFooterPrimary)
'turn off link to previous
.LinkToPrevious = False
'make sure we're starting our page numbers for this section at 1
.PageNumbers.StartingNumber = 1
'create some dummy placeholder text
'X = PAGE, Y = SECTIONPAGES, A = REALPAGES, B = NUMPAGES
.Range.text = "Section Page [*X*] of [*Y*]" & vbCr & _
"Document Page [*A*] of [*B*]"
'now replace our placeholders
ReplacePlaceHolderWithField .Range, "[*X*]", "PAGE"
ReplacePlaceHolderWithField .Range, "[*Y*]", "SECTIONPAGES"
ReplacePlaceHolderWithField .Range, "[*B*]", "NUMPAGES"
'the tricky one
ReplacePlaceHolderWithField .Range, "[*A*]", "= ( {PAGE} + " & lCurPageCount & ")"
End With
'get the page numbers
lSecPageNums = fGetPageNumbers(oSec.index)
'get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
End Sub

'replace a place holder with a field code
Public Sub ReplacePlaceHolderWithField(rngHF As Range, sPlaceHolder As String, sFieldText As String)
Dim rngWorking As Range
Dim oField As Field
Dim oField2 As Field
Set rngWorking = rngHF.Duplicate
If rngWorking.Find.Execute(FindText:=sPlaceHolder, MatchCase:=True) Then
Set oField = rngWorking.Fields.Add(rngWorking, , sFieldText, False)
End If
'special case for our nested field
If InStr(sFieldText, "{PAGE}") > 0 Then
Set rngWorking = rngHF.Duplicate
rngWorking.Collapse wdCollapseStart
Set oField2 = rngWorking.Fields.Add(rngWorking, , "PAGE", False)
oField2.Cut
oField.ShowCodes = True
If rngWorking.Find.Execute(FindText:="{PAGE}") Then
rngWorking.Paste
End If
oField.Update
End If
End Sub

'return the total number of page numbers of the passed section number
'NOTE: this methodology fails to give accurate page numbers in several scenarios:
'hidden text, continuous section breaks, a variety of print drivers on long documents, etc
Public Function fGetPageNumbers(iSecNum As Integer) As Integer
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer
'functions should generally have error trapping
On Error GoTo l_err
With ActiveDocument
'get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'and the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function

EDITS: better explanation, a change of the place holder text, since "[ B ]" (no spaces, no quotes) was made lower-case by the BB software, think it was a "bold" code.

gmaxey
08-25-2012, 11:26 AM
Jason,

I developed the method posted back in the day when I worked for the same government that our OP is working for now. At the time I thought I had exhausted all automated approaches and shelved my attempt to build the nested fields on the fly. Your posting here has caused me to dust it off and try again:


Option Explicit
Dim lCurPageCount As Integer
Dim oRng As Word.Range

Public Sub DemoPageNumbersANDSectionNumbers()
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lngCount As Long
Set oDoc = ActiveDocument
Application.ScreenUpdating = False
ActiveWindow.View.ShowFieldCodes = True
For Each oSec In ActiveDocument.Sections
'replace with the "right" header?
For lngCount = 1 To 3
With oSec.Headers(lngCount)
'Turn off link to previous
.LinkToPrevious = False
'Make sure we're starting our page numbers for this section at 1
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With
InsertNestedFieldsOnTheFlyI oSec, lngCount
InsertNestedFieldsOnTheFlyII oSec, lngCount
End With
Next lngCount
'Get the page numbers
lSecPageNums = fGetPageNumbers(oSec.Index)
'Get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub

Public Function fGetPageNumbers(iSecNum As Integer) As Integer
'Return the total number of page numbers of the passed section number
'NOTE: This methodology fails to give accurate page numbers in several scenarios:
'Hhidden text, continuous section breaks, a variety of print drivers on long documents, etc
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer
'Functions should generally have error trapping
On Error GoTo l_err
With ActiveDocument
'Get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'And the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'Black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function

Sub InsertNestedFieldsOnTheFlyI(ByRef oSec As Section, lngType As Long)
'Builds the Page of Section Pages text and fields
'Insert dummy para at end of document
ActiveDocument.Range.InsertAfter vbCr
Set oRng = ActiveDocument.Range
oRng.Collapse wdCollapseEnd
'Insert nested field
With oRng
.InsertAfter "Page "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldPage, PreserveFormatting:=False
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.InsertAfter " of "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldSectionPages, PreserveFormatting:=False
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.InsertAfter " Section Pages"
End With
'Cut field, delete dummy para mark, and paste field into footer
Set oRng = ActiveDocument.Paragraphs.Last.Range
oRng.MoveEnd Unit:=wdCharacter, Count:=-1
oRng.Cut
ActiveDocument.Paragraphs.Last.Range.Delete
Set oRng = oSec.Footers(lngType).Range
'oRng.Collapse wdCollapseEnd
oRng.Paste
End Sub

Sub InsertNestedFieldsOnTheFlyII(ByRef oSec As Section, lngType As Long)
'Builds the Page of NumPages fields.
'Insert dummy para at end of document
ActiveDocument.Range.InsertAfter vbCr
Set oRng = ActiveDocument.Range
oRng.Collapse wdCollapseEnd
'Insert nested field
With oRng
.InsertAfter "Page "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "= ("
.MoveEnd Unit:=wdCharacter, Count:=1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "PAGE"
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "+ " & lCurPageCount & ")"
.End = ActiveDocument.Range.End
.InsertAfter " of "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldNumPages, PreserveFormatting:=False
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.InsertAfter " Document Pages"
End With
'Cut field, delete dummy para mark, and paste field into header
Set oRng = ActiveDocument.Paragraphs.Last.Range
oRng.MoveEnd Unit:=wdCharacter, Count:=-1
oRng.Cut
ActiveDocument.Paragraphs.Last.Range.Delete
Set oRng = oSec.Headers(lngType).Range
'oRng.Collapse wdCollapseEnd
oRng.Paste
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub

Your fGetPageNumbers was the missing key to the kingdom. Thanks!!


Coding solution aside (and the above is just a proof-of-concept, I still think Greg's methodology would provide you better dynamism), there are some problems in either approach.

Accurate page counting in Word is tricky at best, even on the simpler side.

The *best* way to do what you're doing would be to separate out each of your sections into separate documents, and use a PAGE/SECTIONPAGES/PAGE + #/NUMPAGES solution, where you build the documents in order, print the document to a .pdf file, and then build the next file, replacing the # with the actual number of pages of the previous .pdf.

And the at the end of the process, you would combine all of these .pdfs into a single .pdf when you were ready to publish the document.

Other than that, almost any scenario will give you bad or inaccurate page numbers at times (the link I provided goes into more detail regarding printer drivers and the way the page numbers are calculated).

However, if the proof-of-concept above seems to work on a copy of one of your typical documents, then we could probably tweak it a bit to go from proof-of-concept to a "will work the majority of the time when you press the button" kind of macro.

gmaxey
08-25-2012, 03:11 PM
That is ok. I'll post a correction.

ceilidh
08-25-2012, 06:04 PM
Hi Frosty,

I tried your code on one of my documents. It does work for the numbering - I get both the overall page x of n, and also the within-section page x of n.

However... the original headers of the document are wiped during this process. Instead of the original headers I have "Section Page 1 of 70" on the first header line (left-justified) and "Document Page 1 of 841" on the second header line (left-justified).

Originally I had the document name/path (left justified) and the Page 1 of 841 (right justified) on the first header line, and I had "Table 1 - xxxx" on the second header line (where xxxx is confidential text).

Ideally I'd like to have the headers left alone, and have the "Section Page 1 of 70" bit appear in the page below the footers. I'm guessing this is not possible....?

But the pagination definitely works... I went through the doc (took me nearly an hour!) and couldn't find a wrong page number. If it works for this one it should work for all as they are all the same format. So I guess it's just a case of asking if it's possible to re-locate the Section Page number... at all?

Thanks so much for the help.

I'll copy Greg's code now and try that too.

ceilidh
08-25-2012, 06:14 PM
I get an error when running Greg's code - Run-time error 5251. "This is not a valid action for the end of a row".

Its on the line .InsertAfter "Page " in the Sub InsertFieldsOnTheFly(ByRef oSec As Section, lngType As Long)

gmaxey
08-25-2012, 07:22 PM
ceilidh,

You must have a table (perhaps you can't see its borders) in the headers or footers.

The code is running fine here.

This is a very complex task to automate. You can put you {Pages} of {SectionPages} field codes whereever you like and actaully you can remove the code Jason and I have provided to for them since that are basically just field codes. However, as Jason has explained, the "Page" part of {Page} of {NumPages} will have to be calculated and written to a target range. Right now that range is the header range which as you have observed wipes it out. I you had a table in the header (2 rows, with row 1 split into 2 columns) then we could probably write to a cell range.

Also, code for your particular case could be simplified if we knew you page layout. Do you use only the primary header in these sections or do we need to worry about different first page and different odd and even.

gmaxey
08-25-2012, 07:52 PM
Ok. If I can assume that your header contains a table with two rows. Row 1 is split into 2 columns, row 2 is a single column

R1C1__ R1C2 __
R2C1__________

R1C1 has the file name and path field
R2C1 has your table data.

Your footers can remain linked to previous so all you need to do is enter the
{Page} of {SectionPages} in the first footer.

Running this code should put the "Page" of "Numpages" information in R1C2:

Option Explicit
Dim lCurPageCount As Integer
Dim oRng As Word.Range
Public Sub DemoPageNumbersANDSectionNumbers()
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lngCount As Long
Set oDoc = ActiveDocument
lCurPageCount = 0
lSecPageNums = 0
For Each oSec In ActiveDocument.Sections
With oSec.Headers(wdHeaderFooterPrimary)
'Turn off link to previous
.LinkToPrevious = False
'Make sure we're starting our page numbers for this section at 1
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With
InsertNestedFieldsOnTheFly oSec
.Range.Fields.Update
End With
'Get the page numbers
lSecPageNums = fGetPageNumbers(oSec.Index)
'Get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
ActiveDocument.ActiveWindow.View.SeekView = wdSeekPrimaryHeader
ActiveDocument.ActiveWindow.View.SeekView = wdSeekMainDocument
End Sub
Public Function fGetPageNumbers(iSecNum As Integer) As Integer
'Return the total number of page numbers of the passed section number
'NOTE: This methodology fails to give accurate page numbers in several scenarios:
'Hhidden text, continuous section breaks, a variety of print drivers on long documents, etc
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer

'Functions should generally have error trapping
On Error GoTo l_err
With ActiveDocument
'Get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'And the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'Black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function
Sub InsertNestedFieldsOnTheFly(ByRef oSec As Section)
Dim oCell As Word.Cell

Application.ScreenUpdating = False
ActiveWindow.View.ShowFieldCodes = True
Set oCell = oSec.Headers(wdHeaderFooterPrimary).Range.Tables(1).Cell(1, 2)
Set oRng = oCell.Range 'oSec.Headers(wdHeaderFooterPrimary).Range.Tables(1).Cell(1, 2).Range
oRng.Delete
'Insert nested field
With oRng
.InsertAfter "Page "
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "= ("
.MoveEnd Unit:=wdCharacter, Count:=1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "PAGE"
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "+ " & lCurPageCount & ")"
.End = oCell.Range.End - 1
.InsertAfter " of "
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldNumPages, PreserveFormatting:=False
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
.InsertAfter " Document Pages"
End With
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub

gmaxey
08-26-2012, 09:35 AM
Jason,

Let me try that again:

Option Explicit
Dim lCurPageCount As Integer
Dim oRng As Word.Range
Public Sub DemoPageNumbersANDSectionNumbers()
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lngCount As Long
Set oDoc = ActiveDocument
Application.ScreenUpdating = False
ActiveWindow.View.ShowFieldCodes = True
lCurPageCount = 0
lSecPageNums = 0
For Each oSec In ActiveDocument.Sections
For lngCount = 1 To 3
With oSec.Headers(lngCount)
'Turn off link to previous
.LinkToPrevious = False
'Make sure we're starting our page numbers for this section at 1
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With
InsertNestedFieldsOnTheFly oSec, lngCount
.Range.Fields.Update
End With
With oSec.Footers(lngCount)
.LinkToPrevious = False
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With
InsertFieldsOnTheFly oSec, lngCount
.Range.Fields.Update
End With

Next lngCount
'Get the page numbers
lSecPageNums = fGetPageNumbers(oSec.Index)
'Get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
ActiveWindow.View.SeekView = wdSeekPrimaryHeader
ActiveWindow.View.SeekView = wdSeekMainDocument
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub
Public Function fGetPageNumbers(iSecNum As Integer) As Integer
'Return the total number of page numbers of the passed section number
'NOTE: This methodology fails to give accurate page numbers in several scenarios:
'Hhidden text, continuous section breaks, a variety of print drivers on long documents, etc
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer

'Functions should generally have error trapping
On Error GoTo l_err
With ActiveDocument
'Get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'And the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'Black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function
Sub InsertFieldsOnTheFly(ByRef oSec As Section, lngType As Long)
'Builds the Page of Section Pages text and fields
Set oRng = oSec.Footers(lngType).Range
oRng.Delete
'Insert fields
With oRng
.InsertAfter "Page "
.End = oSec.Footers(lngType).Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldPage, PreserveFormatting:=False
.End = oSec.Footers(lngType).Range.End
.Collapse wdCollapseEnd
.InsertAfter " of "
.End = oSec.Footers(lngType).Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldSectionPages, PreserveFormatting:=False
.End = oSec.Footers(lngType).Range.End
.Collapse wdCollapseEnd
.InsertAfter " Section Pages"
End With
End Sub

Sub InsertNestedFieldsOnTheFly(ByRef oSec As Section, lngType As Long)
'Builds the Page of NumPages fields.

Set oRng = oSec.Headers(lngType).Range
oRng.Delete
'Insert nested field
With oRng
.InsertAfter "Page "
.End = oSec.Headers(lngType).Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "= ("
.MoveEnd Unit:=wdCharacter, Count:=1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "PAGE"
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "+ " & lCurPageCount & ")"
.End = oSec.Headers(lngType).Range.End
.InsertAfter " of "
.End = oSec.Headers(lngType).Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldNumPages, PreserveFormatting:=False
.End = oSec.Headers(lngType).Range.End
.Collapse wdCollapseEnd
.InsertAfter " Document Pages"
End With
End Sub




Jason,

I developed the method posted back in the day when I worked for the same government that our OP is working for now. At the time I thought I had exhausted all automated approaches and shelved my attempt to build the nested fields on the fly. Your posting here has caused me to dust it off and try again:

Option Explicit
Dim lCurPageCount As Integer
Dim oRng As Word.Range
Public Sub DemoPageNumbersANDSectionNumbers()
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lngCount As Long

Set oDoc = ActiveDocument
Application.ScreenUpdating = False
ActiveWindow.View.ShowFieldCodes = True
For Each oSec In ActiveDocument.Sections
'replace with the "right" header?
For lngCount = 1 To 3
With oSec.Headers(lngCount)
'Turn off link to previous
.LinkToPrevious = False
'Make sure we're starting our page numbers for this section at 1
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With
InsertNestedFieldsOnTheFlyI oSec, lngCount
InsertNestedFieldsOnTheFlyII oSec, lngCount
End With
Next lngCount
'Get the page numbers
lSecPageNums = fGetPageNumbers(oSec.Index)
'Get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub
Public Function fGetPageNumbers(iSecNum As Integer) As Integer
'Return the total number of page numbers of the passed section number
'NOTE: This methodology fails to give accurate page numbers in several scenarios:
'Hhidden text, continuous section breaks, a variety of print drivers on long documents, etc
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer

'Functions should generally have error trapping
On Error GoTo l_err
With ActiveDocument
'Get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'And the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'Black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function
Sub InsertNestedFieldsOnTheFlyI(ByRef oSec As Section, lngType As Long)
'Builds the Page of Section Pages text and fields
'Insert dummy para at end of document
ActiveDocument.Range.InsertAfter vbCr
Set oRng = ActiveDocument.Range
oRng.Collapse wdCollapseEnd
'Insert nested field
With oRng
.InsertAfter "Page "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldPage, PreserveFormatting:=False
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.InsertAfter " of "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldSectionPages, PreserveFormatting:=False
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.InsertAfter " Section Pages"
End With
'Cut field, delete dummy para mark, and paste field into footer
Set oRng = ActiveDocument.Paragraphs.Last.Range
oRng.MoveEnd Unit:=wdCharacter, Count:=-1
oRng.Cut
ActiveDocument.Paragraphs.Last.Range.Delete
Set oRng = oSec.Footers(lngType).Range
'oRng.Collapse wdCollapseEnd
oRng.Paste
End Sub
Sub InsertNestedFieldsOnTheFlyII(ByRef oSec As Section, lngType As Long)
'Builds the Page of NumPages fields.

'Insert dummy para at end of document
ActiveDocument.Range.InsertAfter vbCr
Set oRng = ActiveDocument.Range
oRng.Collapse wdCollapseEnd
'Insert nested field
With oRng
.InsertAfter "Page "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "= ("
.MoveEnd Unit:=wdCharacter, Count:=1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "PAGE"
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "+ " & lCurPageCount & ")"
.End = ActiveDocument.Range.End
.InsertAfter " of "
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldNumPages, PreserveFormatting:=False
.End = ActiveDocument.Range.End
.Collapse wdCollapseEnd
.InsertAfter " Document Pages"
End With
'Cut field, delete dummy para mark, and paste field into header
Set oRng = ActiveDocument.Paragraphs.Last.Range
oRng.MoveEnd Unit:=wdCharacter, Count:=-1
oRng.Cut
ActiveDocument.Paragraphs.Last.Range.Delete
Set oRng = oSec.Headers(lngType).Range
'oRng.Collapse wdCollapseEnd
oRng.Paste
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub

Your fGetPageNumbers was the missing key to the kingdom. Thanks!!

ceilidh
08-26-2012, 01:06 PM
ceilidh,

You must have a table (perhaps you can't see its borders) in the headers or footers.

The code is running fine here.

This is a very complex task to automate. You can put you {Pages} of {SectionPages} field codes whereever you like and actaully you can remove the code Jason and I have provided to for them since that are basically just field codes. However, as Jason has explained, the "Page" part of {Page} of {NumPages} will have to be calculated and written to a target range. Right now that range is the header range which as you have observed wipes it out. I you had a table in the header (2 rows, with row 1 split into 2 columns) then we could probably write to a cell range.

Also, code for your particular case could be simplified if we knew you page layout. Do you use only the primary header in these sections or do we need to worry about different first page and different odd and even.


Hi Greg, would it help if I posted a page or two, even though there'd be no info in the pages... I would have to wipe all the data and titles and footnotes, so all there'd be would be the empty skeleton so to speak. But would that help...?

Edited to add - I don't use different first page or different odd and even, no.

Edited again... I just prepared 10 pages, that are 2 sections. I deleted a lot of pages in those 2 sections to cut the size down, just kept the first few pages and the last page in each section. I've XXXX'd data in the header (titles) but left the PAGE of NUMPAGES bit as that's not confidential. You can see the structure of the header, anyway. Also the footers. The body of the doc shows the table - I deleted all the data in the table so it is just the empty outline.

Basically, all the docs look like this. They're produced by software and won't change.

One thing occurs to me though looking at the docs... I have a section break between every section, but on the last page (end of the last section) there isn't one of course, since that's the end of the document. Is that going to affect PAGE of SECTIONPAGE for the last section, though?

Ummm... I'm probably being stupid here, but how do I post the document... to this forum...?

ceilidh
08-26-2012, 02:56 PM
Greg, my first line of my header actually has 3 cells, not 2. The "Page x of N" (overall pagination) is in the 3rd cell. I just edited your code from 2 to 3 for that.

I just ran your code on one of my docs. There was no cosmetic change to the doc. I still have the "Page X of N" showing at the top right (which is good as that's what I wanted) but I don't see the "page x of n" section count anywhere in the doc. Am I supposed to put PAGE of SECTIONPAGES in the footnote first before I run the VBA code? Is it looking for that text? It seemed so from looking at the code BWDIK....

Edited to add - I just re ran one big doc, putting in the PAGE of SECTIONPAGES in addition to the PAGE of NUMPAGES. I put the PAGE of SECTIONPAGES into a new footnote at the bottom of each page. As expected the PAGE was screwy ... then I ran your VBA code and it works!!! The PAGE of SECTIONPAGES re-set, and I now show correct section numbering in addition to correct overall page numbering. THANK YOU!!!!!!!!!!!

gmaxey
08-26-2012, 04:33 PM
ceilidh,

Yes is the last code I sent, I stripped out the part that automatically added the {Page} of {SectionPages} part because once you set each section to restart numbering with 1 then all you need to od is add those fields manually.

Glad I could help. Be careful with this code though, as Jason has pointe out, it it not really that robust and could croak with other print drivers, continous breaks, etc.

Frosty
08-27-2012, 10:04 AM
I just caught up... and I second what Greg says (especially since he was quoting me, hehe): if it's working for this particular set of documents, great. But don't rely on it in too many scenarios without really checking again.

Here are the following scenarios (off the top of my head) where this currently-working code could break without any change to this code:
1. Your computers producing the documents get upgraded (new Operating System)
2. The printers you're using get upgraded (newer/different printer drivers)
3. The print servers you might be using get upgraded (which might use different print drivers-- and you might not know about it).
4. You get a different version of Word (obviously)
5. The software producing these documents gets updated (just because the documents are all the same, doesn't mean the software vendor won't do something to change it on you-- many a "transparent" change has not been quite so).

Best of luck to you Ceilidh!

Jason aka Frosty

ceilidh
08-28-2012, 03:12 AM
Thanks Frosty!

I've been reading some more threads on this forum actually. Trying to learn some more VBA now - strikes me that it might come in useful.

ceilidh
09-07-2012, 09:57 AM
back again...

For some reason, the code seems to have stopped working for me today. It's really odd... was working beautifully and now is not. The overall page numbering is being re-set to start at 1 at the beginning of each new section instead of being left alone.

I went back to check on an older document that I had run the macro on previously. At that time the overall page numbering was correct. However, when I opened it and looked at it today, (just opened and looked - didn't re-run the macro on it or make any changes to it), the overall page numbering has gone wrong in this one too - it's also being re-set to 1 for each new section.

What would cause this to happen?

Editing to add a clarification. The {NUMPAGES} is still presenting correctly. It's the {PAGE} bit that is associated with the {NUMPAGES} which is being reset to 1 for each new section.

The {SECTIONPAGES} is also still correct. So is the {PAGE} that is associated with the {SECTIONPAGES}.


This is the code I was/am using:


Public Sub DemoPageNumbersANDSectionNumbers()
Dim lCurPageCount As Integer
Dim oRng As Word.Range
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lngCount As Long
Set oDoc = ActiveDocument
lCurPageCount = 0
lSecPageNums = 0
For Each oSec In ActiveDocument.Sections
With oSec.Headers(wdHeaderFooterPrimary)
'Turn off link to previous
.LinkToPrevious = False
'Make sure we're starting our page numbers for this section at 1
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With
InsertNestedFieldsOnTheFly oSec
.Range.Fields.Update
End With
'Get the page numbers
lSecPageNums = fGetPageNumbers(oSec.Index)
'Get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
ActiveDocument.ActiveWindow.View.SeekView = wdSeekPrimaryHeader
ActiveDocument.ActiveWindow.View.SeekView = wdSeekMainDocument
End Sub
Public Function fGetPageNumbers(iSecNum As Integer) As Integer
'Return the total number of page numbers of the passed section number
'NOTE: This methodology fails to give accurate page numbers in several scenarios:
'Hhidden text, continuous section breaks, a variety of print drivers on long documents, etc
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer

'Functions should generally have error trapping
On Error GoTo l_err
With ActiveDocument
'Get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'And the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'Black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function
Sub InsertNestedFieldsOnTheFly(ByRef oSec As Section)
Dim lCurPageCount As Integer
Dim oRng As Word.Range
Dim oCell As Word.Cell

Application.ScreenUpdating = False
ActiveWindow.View.ShowFieldCodes = True
Set oCell = oSec.Headers(wdHeaderFooterPrimary).Range.Tables(1).Cell(1, 2)
Set oRng = oCell.Range 'oSec.Headers(wdHeaderFooterPrimary).Range.Tables(1).Cell(1, 2).Range
oRng.Delete
'Insert nested field
With oRng
.InsertAfter "Page "
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "= ("
.MoveEnd Unit:=wdCharacter, Count:=1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "PAGE"
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "+ " & lCurPageCount & ")"
.End = oCell.Range.End - 1
.InsertAfter " of "
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldNumPages, PreserveFormatting:=False
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
'.InsertAfter " Document Pages"
End With
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub

Frosty
09-07-2012, 11:14 AM
Sorry, ceilidh, but the code you posted would have never worked. You've modified it slightly from what was working to what it is now, but it is a critical modification. This is both a concept issue (the concept of "Scope") as well as a troubleshooting lesson.

I can give you the answer, but I'd rather teach you how to solve this yourself, if that's okay.

1. ALT + F9 is the "Show Field Codes" toggle function. If you use that on your document, I think you'll see that in each case, the field (which is really a couple of nested fields) will show the following code:
{ = ( { PAGE } + 0 ) }

What that means is that it is taking the page count (which we have coded to start at 1 for each section), so that your section numbering will work) and adds a number to it. That number is the number we should be able to get accurately (hopefully) from the fGetPageNumbers function.

2. Since the number is 0, we have to ask why is that number 0? If you look at your NestedFieldsOnTheFly function, you will see that you have dimmed (created a memory space, or "dimensioned") the variable lCurPageCount As Integer.

When new variables are created, they always have a default value. Number variables will begin their life as a zero (no judgement here! *grin*), string variables will begin their life as an empty string (""), and other variables begin their respective lives as other default states (Null, Nothing, etc). But most of the variables you'll work with as you learn VBA will generally be a 0 or a ""

3. Now we get into the scope issue. In your main routine DemoPageNumbersANDSectionNumbers, you are also creating variables... lSecPageNums and lCurPageCount. But since they are dimmed within the routine, that is their "scope" -- other routines cannot "see" the values in those variables, regardless of whether you name them the same. This allows us to re-use a "counter" variable like "i" in many subroutines without the values being cross-pollenated, as it were.

There are 3 types of scope:
1. Subroutine only (Dim X as Integer, within a procedure)
2. Module only (Private X as Integer, at the top of the module)
3. Entire project (Public X as Integer, at the top of the module)

For your InsertNestedFieldsOnTheFly to have a value of other than 0 for the lCurPageCount, you need to do one of two things:
1. Use a variable it can see (whether public or module-level)
2. Pass it a parameter with a value (the way you pass oSec As Section)

Reasonable people can disagree on the best way to do this-- Greg's method used a private module variable to "hold" the value between separate subroutines.

I prefer to pass parameters.

4. Debugging the code. Instead of running the routine and seeing what happens, use F8 to "step through" the code, and you can get a better idea of what it is actually doing.

If the above doesn't make sense, and you just need the answer... it is easy to provide. Just let me know. But since you've expressed interest in learning, I thought I'd give you the chance to work it out on your own, using the information above.

- Jason aka Frosty

Frosty
09-07-2012, 11:19 AM
One last thing on the scope concept.

In addition to when a variable can be "seen" by other subroutines, it's also important to know when those variables will "fall out of scope" (i.e., get "reset" to their default values).

Look up "Scope" in the VBA help file. The article is called "Understanding Scope and Visibility" -- probably better to let the experts explain, than an old hack like me :)

Also, look up the "Understanding the Lifetime of Variables" article in the help file...

ceilidh
09-07-2012, 02:29 PM
Thanks Frosty! I only just got back to the forum now, to find your reply. Yes, if I can fix it myself I'm game... I'll pull out my computer again after dinner tonight and have a go.

The macro was working previously. I was tinkering with it a bit today, you're right... :)

gmaxey
09-07-2012, 02:43 PM
Would like to add 1 thing:

There are 3 types of scope:
1. Subroutine only (Dim X as Integer, within a procedure)
2. Module only (Private X as Integer, at the top of the module)
3. Entire project (Public X as Integer, at the top of the module)

3. ould be written

3. Entire project(Public X as Integer, at the top of any module in the project)

Frosty
09-07-2012, 04:42 PM
Good point, Greg. I think I can sum it up quickly by saying
1. Procedural scope = variable dimmed inside a Sub or Function, initialized when the Sub is called, "destroyed" when the Sub(or function) ends.

2. Module scope = variable at the top of a module, created using "Dim" or "Private" ("Private" is better, although functionally the same, it makes it more clear). Variable initialized when any Sub/Function in that module is called, variable "destroyed" (or reset) only when Word is closed (or the document/template containing the code is closed/unloaded). Variable is able to be used (and whatever its current value is) by any Sub/Function within that module ONLY.

3. Public scope. Same as Module Scope, except that the variable can be seen by any sub/function in any module of the project.

There are exceptions to the above when you're dealing with UserForm modules and Class modules, or if you use the Static variable. But I'd stay away from use of Static and exceptions within Class/UserForm modules will be pretty apparent when you run into them.

fumei
09-07-2012, 09:57 PM
An excellent description of Scope. I also agree with the use of Private versus Dim for modular scope. It is clearer. That was what I taught my students.

Frosty
09-08-2012, 10:07 AM
One addition to when a variable falls out of scope or ends its lifetime (i.e., gets reset) --

When the "End" command is invoked (not End Sub or Exit Sub, but just "End" on its own).
When you have an untrapped error which displays the VBA debug window, and you choose "End"

Neither of the above scenarios should happen in a well-written routine. The End command is considered by many (including me) to be bad practice, and untrapped errors are generally not something you want to allow to happen on "top" level routines (i.e., something which an end-user can invoke by pressing a button).

ceilidh
09-09-2012, 12:50 PM
Hi again,

It's working now! Here's the edits I made - I highlighted the 2 lines I edited in red:

Sub DemoPageNumbersANDSectionNumbers()
Dim lCurPageCount As Integer
Dim oRng As Word.Range
Dim oDoc As Document
Dim oSec As Section
Dim lSecPageNums As Integer
Dim lngCount As Long
Set oDoc = ActiveDocument
lCurPageCount = 0
lSecPageNums = 0
For Each oSec In ActiveDocument.Sections
With oSec.Headers(wdHeaderFooterPrimary)
'Turn off link to previous
.LinkToPrevious = False
'Make sure we're starting our page numbers for this section at 1
With .PageNumbers
.RestartNumberingAtSection = True
.StartingNumber = 1
End With
InsertNestedFieldsOnTheFly oSec, oRng, lCurPageCount
.Range.Fields.Update
End With
'Get the page numbers
lSecPageNums = fGetPageNumbers(oSec.Index)
'Get the current page count
lCurPageCount = lCurPageCount + lSecPageNums
Next
ActiveDocument.ActiveWindow.View.SeekView = wdSeekPrimaryHeader
ActiveDocument.ActiveWindow.View.SeekView = wdSeekMainDocument
End Sub
Public Function fGetPageNumbers(iSecNum As Integer) As Integer
'Return the total number of page numbers of the passed section number
'NOTE: This methodology fails to give accurate page numbers in several scenarios:
'Hhidden text, continuous section breaks, a variety of print drivers on long documents, etc
Dim iNumPages As Integer
Dim iNumPagesPrevSec As Integer
Dim iRet As Integer

'Functions should generally have error trapping
On Error Goto l_err
With ActiveDocument
'Get the number of pages of the current section
iNumPages = .Sections(iSecNum).Range.Information(wdActiveEndPageNumber)
If iSecNum = 1 Then
iRet = iNumPages
Else
'And the number of pages from the previous section, if we're dealing with a section other than 1
iNumPagesPrevSec = .Sections(iSecNum - 1).Range.Information(wdActiveEndPageNumber)
iRet = iNumPages - iNumPagesPrevSec
End If
End With
l_exit:
fGetPageNumbers = iRet
Exit Function
l_err:
'Black box-- any errors we return 0
iRet = 0
Resume l_exit
End Function
Sub InsertNestedFieldsOnTheFly(ByRef oSec As Section, oRng As Word.Range, lCurPageCount As Integer)
'Dim lCurPageCount As Integer
'Dim oRng As Word.Range
Dim oCell As Word.Cell

Application.ScreenUpdating = False
ActiveWindow.View.ShowFieldCodes = True
Set oCell = oSec.Headers(wdHeaderFooterPrimary).Range.Tables(1).Cell(1, 2)
Set oRng = oCell.Range 'oSec.Headers(wdHeaderFooterPrimary).Range.Tables(1).Cell(1, 2).Range
oRng.Delete
'Insert nested field
With oRng
.InsertAfter "Page "
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "= ("
.MoveEnd Unit:=wdCharacter, Count:=1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldEmpty, PreserveFormatting:=False
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "PAGE"
.MoveEnd Unit:=wdCharacter, Count:=2
.InsertAfter "+ " & lCurPageCount & ")"
.End = oCell.Range.End - 1
.InsertAfter " of "
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
.Fields.Add Range:=oRng, Type:=wdFieldNumPages, PreserveFormatting:=False
.End = oCell.Range.End - 1
.Collapse wdCollapseEnd
'.InsertAfter " Document Pages"
End With
ActiveWindow.View.ShowFieldCodes = False
Application.ScreenUpdating = True
End Sub


That hint about resetting the variables to zero was what I needed. I'm not a VBA programmer, but I am a programmer. I'm now reading the references you gave me. I can't pretend that I understand a lot of VBA yet, but some of it seems to follow the same rules I'm familiar with.

I'm actually attempting to add a little menu to this - so I can select where (which table/row) to write the overall "Page x of y" without needing to step into the code and find the line to do this. Will keep you posted on my progress. Or lack....

ceilidh
09-09-2012, 01:10 PM
I edited my post to highlight the lines I've edited, in red, by the way - thought that might be more helpful. The second line doesn't all appear in red though... some words are in blue. But you can still ID that line as one I've edited.

Frosty
09-10-2012, 09:39 AM
Passing the lCurPageCount is the way I would approach it too. I'm not sure why you're passing a range, however. You don't set it in the top-level routine, so you're simply passing an empty parameter, which you subsequently set in the called routine.

So that parameter could go away.

I'm not sure why you're using the .SeekView method... I'm assuming that was a hold over from some code you got by recording a macro.

I'd recommend commenting your code more, especially when you're dropping in code from a recorded macro. If you comment what you *want* to be doing (and why), then posting the code with the modifications will give others a chance to comment on a better methodology (regarding .SeekView -- I don't think you should need those lines of code at all, since you're no longer using the selection object... and even if you were, there is a better way to do what you would want to be doing than using .SeekView)

Frosty
09-10-2012, 09:46 AM
Another thought-- adding a user interface to this is going to be tricky.

I would suggest simply setting up a constant at the top of your module to pick where you're going to put the code in...
Public Const INSERT_CELL_COLUMN As Integer = 1
Public Const INSERT_CELL_ROW As Integer = 2

That allows your line of code to change to...
Set oCell = oSec.Headers(wdHeaderFooterPrimary).Range.Tables(1).Cell(INSERT_CELL_COLUMN , INSERT_CELL_ROW)

Or, I'd suggest just checking out the InputBox as a quick and dirty way of setting a value outside of your actual code. But I think you're rapidly going to get into trouble trying to add a "slickness" to this routine, which is a) pretty breakable and b) jumping into the wacky area of tables when we've already established that your tables may be created in a "bad" way by the external process... may cause some headaches.

I figured you were a programmer, just unfamiliar with VBA. The concepts (I believe) are generally true between a lot of the languages. There are some critical defaults which apply in some languages and not in others... but I'm primarily a VBA/VB programmer, so I couldn't really begin to list them for you.

ceilidh
09-11-2012, 03:20 AM
I'm not sure what the Seekview refers to, myself. I think I'll try commenting those 2 lines out and rerunning just to see what happens.

I should say, "remming" them out not "commenting" them out. I'm a SQL programmer...

Thanks for the comment on the range - that's true, the range isn't set at all till the subroutine so I could just dim it there instead of passing it through when it's empty.

I did manage to make a little user interface. and it's working nicely. My code is on my work laptop so I'll get it and post it later on today.

Frosty
09-11-2012, 08:39 AM
Well, those two SeekView lines are basically the equivalent of double-clicking in the header area, to "activate" the header/footer from the main document and then double-clicking into the main body of the document to activate that.