Introduction | Example | Tutorial | Applications
Introduction - Save Pages as Separate PDFs
Save each page in your MS Word document as a separate PDF with this VBA macro. The flexible VBA script let’s you save each page or a subset range of pages as PDFs in a user-specified directory. Complete with robust error-checking.
Example - Save Pages as Separate PDFs
Save As Separate PDFs
Option Explicit
Sub SaveAsSeparatePDFs()
'---------------------------------------------------------------------------------------------------
'---Script: SaveAsSeparatePDFs----------------------------------------------------------------------
'---Created by: Ryan Wells--------------------------------------------------------------------------
'---Date: 03/2015-----------------------------------------------------------------------------------
'---Description: This subroutine saves MS Word document pages as separate PDFs with file names------
'----------------formatted like Page_x.pdf.---------------------------------------------------------
'---------------------------------------------------------------------------------------------------
Dim strDirectory As String, strTemp As String
Dim ipgStart As Integer, ipgEnd As Integer
Dim iPDFnum As Integer, i As Integer
Dim vMsg As Variant, bError As Boolean
1:
strDirectory = InputBox("Directory to save individual PDFs? " & _
vbNewLine & "(ex: C:\Users\Public)")
If strDirectory = "" Then Exit Sub
If Dir(strDirectory, vbDirectory) = "" Then
vMsg = MsgBox("Please enter a valid directory.", vbOKCancel, "Invalid Directory")
If vMsg = 1 Then
GoTo 1
Else
Exit Sub
End If
End If
2:
strTemp = InputBox("Begin saving PDFs starting with page __? " & _
vbNewLine & "(ex: 32)")
bError = bErrorF(strTemp)
If bError = True Then GoTo 2
ipgStart = CInt(strTemp)
3:
strTemp = InputBox("Save PDFs until page __?" & vbNewLine & "(ex: 37)")
bError = bErrorF(strTemp)
If bError = True Then GoTo 3
ipgEnd = CInt(strTemp)
iPDFnum = ipgStart
On Error GoTo 4:
For i = ipgStart To ipgEnd
ActiveDocument.ExportAsFixedFormat OutputFileName:= _
strDirectory & "\Page_" & iPDFnum & ".pdf", ExportFormat:=wdExportFormatPDF, _
OpenAfterExport:=False, OptimizeFor:=wdExportOptimizeForPrint, Range:= _
wdExportFromTo, From:=i, To:=i, Item:=wdExportDocumentContent, _
IncludeDocProps:=False, KeepIRM:=False, CreateBookmarks:= _
wdExportCreateHeadingBookmarks, DocStructureTags:=True, _
BitmapMissingFonts:=False, UseISO19005_1:=False
iPDFnum = iPDFnum + 1
Next i
End
4:
vMsg = MsgBox("Unknown error encountered while creating PDFs." & vbNewLine & vbNewLine & _
"Aborting", vbCritical, "Error Encountered")
End Sub
Private Function bErrorF(strTemp As String) As Boolean
Dim i As Integer, vMsg As Variant
bErrorF = False
If strTemp = "" Then
End
ElseIf IsNumeric(strTemp) = True Then
i = CInt(strTemp)
If i > ActiveDocument.BuiltInDocumentProperties(wdPropertyPages) Or i <= 0 Then
Call msgS(bErrorF)
End If
Else
Call msgS(bErrorF)
End If
End Function
Private Sub msgS(bMsg As Boolean)
Dim vMsg As Variant
vMsg = MsgBox("Please enter a valid integer." & vbNewLine & vbNewLine & _
"Integer must be > 0 and < total pages in the document (" & _
ActiveDocument.BuiltInDocumentProperties(wdPropertyPages) & ")", vbOKCancel, "Invalid Integer")
If vMsg = 1 Then
bMsg = True
Else
End
End If
End Sub
Make powerful macros with our free VBA Developer Kit Tutorials like this can be complicated. That’s why we created our free VBA Developer Kit and our Big Book of Excel VBA Macros to supplement this tutorial. Grab them below and you’ll be writing powerful macros in no time.
Tutorial - Save Pages as Separate PDFs
This example is pretty plug-and-play. You won’t have to do much, if any, tweaking. However, there are a few places you may want to customize.
To get started, all you have to do is paste SaveAsSeparatePDFs into “ThisDocument” under the “Normal” Microsoft Word Objects Project of your VBA Editor. Alt+F11 opens the Editor.
Paste VBA Code Example Here
Pasting the VBA code example here allows you to save your MS Word document with its native *.doc or *.docx file extension, i.e., you won’t have to save it as a macro-enabled document. A second perk is that it makes the macro accessible across all Word documents.
Like most programs, the bulk of SaveAsSeparatePDFs is error-checking. The meat and potatoes can be accomplished with a handful of lines. I included the rest to make your implementation painless. For example, the program confirms your designated directory is an actual directory and your page numbers are actually numeric. I’m not a big fan of the word “actually” so I’m actually going to stop using it for the remainder of this post. Ehh, too much?
Okay, here’s what you need to know. The VBA code issues 3 prompts:
1. Enter the directory where you want to save your PDFs.
2. Enter the page number in your Word document where you want to begin saving individual pages as PDFs.
3. Enter the page number in your Word document where you want to stop saving individual pages as PDFs.
Submitting a blank string at any of the prompts will abort the script. Hey, it’s easier than reaching for your mouse and pressing Cancel.
SaveAsSeparatePDFs will save each page in your page range with file names following the naming convention
For you non-believers, I submit evidence showing the PDFs in the destination folder:
If you don’t like the default naming convention, search for
Remember the error checks we discussed earlier? On the warning prompt for an invalid page number, I included a handy feature:
Total page count of your Word document
See it? The total page count of your current Microsoft Word document is presented in the parentheses. This helps you in case you want to save every page in your file. Some of you may wish to put this on your actual Page prompts. To do that, paste ActiveDocument.BuiltInDocumentProperties(wdPropertyPages)
into your desired InputBox
code.
Application Ideas - Save Pages as Separate PDFs
My coworkers and I produce a lot of design calculations in our nuclear engineering jobs. The body of the design calculations are prepared in MS Word but the attachments are assembled from many different files in many different file formats. The body and all the attachments must be compiled into a single PDF. This script lets us make cover pages for each attachment and save them as separate PDFs for final compilation of the master design calculation.
I’m spitballing here, but other potential uses include:
- Extracting individual PDF forms from a Master Word Document.
- Emailing separate PDFs to different recipients based on the content of page.
- Pulling monthly reports from a yearly summary Word document.
That’s all for this tutorial. When you’re ready to take your VBA to the next level, subscribe using the form below.