Print Margins
When printing documents in Excel, margin settings significantly affect the appearance and readability. While you can set them manually, using VBA allows you to efficiently process multiple sheets or workbooks when you want to apply uniform margins. This article explains in detail how to set print margins using the PageSetup object.
When Print Margin Settings Are Needed
VBA print margin settings are particularly useful in the following situations:
- Standardizing company templates: When you want to unify margins for reports and forms used company-wide
- Bulk settings for multiple sheets: When you want to apply the same margins to all sheets in a workbook
- Fine-tuning after print preview: When dynamically adjusting margins programmatically
- Automating routine tasks: When automating daily or weekly printing tasks
When setting margins manually, you select “Margins” from the “Page Layout” tab, but this is very time-consuming when you have many sheets. With VBA, you can do bulk settings with just a few lines of code.
PageSetup Object Basics
To configure print settings in Excel VBA, use the PageSetup object. This object can be accessed as a property of the Worksheet object.
'___Basic access method
Worksheets("Sheet1").PageSetup
Margin-Related Properties
The PageSetup object has the following properties related to margin settings:
| Property | Description |
|---|---|
LeftMargin | Left margin |
RightMargin | Right margin |
TopMargin | Top margin |
BottomMargin | Bottom margin |
HeaderMargin | Header margin (from top edge) |
FooterMargin | Footer margin (from bottom edge) |
All margin properties are specified in points. If you want to specify in centimeters or inches, use conversion functions.
Unit Conversion Methods
In VBA, margin values must be specified in points. To specify in centimeters or inches, use the following conversion functions:
'___Convert inches to points
Application.InchesToPoints(1) '___1 inch = 72 points
'___Convert centimeters to points
Application.CentimetersToPoints(1) '___1 centimeter ≈ 28.35 points
Basic Margin Setting Code Examples
Setting Margins for a Single Sheet
Here’s an example of the most basic usage—setting margins for a specific sheet.
Sub SetMarginsSingleSheet()
With Worksheets("Sheet1").PageSetup
'___Set left and right margins to 1 centimeter
.LeftMargin = Application.CentimetersToPoints(1)
.RightMargin = Application.CentimetersToPoints(1)
'___Set top and bottom margins to 2 centimeters
.TopMargin = Application.CentimetersToPoints(2)
.BottomMargin = Application.CentimetersToPoints(2)
'___Set header and footer margins to 0.5 centimeters
.HeaderMargin = Application.CentimetersToPoints(0.5)
.FooterMargin = Application.CentimetersToPoints(0.5)
End With
End Sub
Setting in Inches
When setting margins in inches, use the InchesToPoints function.
Sub SetMarginsInInches()
With ActiveSheet.PageSetup
'___Set left and right margins to 0.5 inches
.LeftMargin = Application.InchesToPoints(0.5)
.RightMargin = Application.InchesToPoints(0.5)
'___Set top and bottom margins to 0.75 inches
.TopMargin = Application.InchesToPoints(0.75)
.BottomMargin = Application.InchesToPoints(0.75)
End With
End Sub
Specifying Directly in Points
You can also specify directly in points. Calculate as 1 inch = 72 points.
Sub SetMarginsInPoints()
With ActiveSheet.PageSetup
'___Set to 36 points (0.5 inches)
.LeftMargin = 36
.RightMargin = 36
.TopMargin = 36
.BottomMargin = 36
End With
End Sub
Bulk Settings for Multiple Sheets
Applying to All Sheets in a Workbook
Here’s an example of applying the same margin settings to all worksheets in a workbook.
Sub SetMarginsAllSheets()
Dim ws As Worksheet
For Each ws In ThisWorkbook.Worksheets
With ws.PageSetup
.LeftMargin = Application.CentimetersToPoints(1.5)
.RightMargin = Application.CentimetersToPoints(1.5)
.TopMargin = Application.CentimetersToPoints(2)
.BottomMargin = Application.CentimetersToPoints(2)
.HeaderMargin = Application.CentimetersToPoints(1)
.FooterMargin = Application.CentimetersToPoints(1)
End With
Next ws
MsgBox "Margins have been set for all sheets.", vbInformation
End Sub
Applying Only to Selected Sheets
When applying margin settings only to user-selected sheets.
Sub SetMarginsSelectedSheets()
Dim ws As Object
For Each ws In ActiveWindow.SelectedSheets
With ws.PageSetup
.LeftMargin = Application.CentimetersToPoints(1)
.RightMargin = Application.CentimetersToPoints(1)
.TopMargin = Application.CentimetersToPoints(1.5)
.BottomMargin = Application.CentimetersToPoints(1.5)
End With
Next ws
MsgBox "Margins have been set for selected sheets.", vbInformation
End Sub
Accessing the PageSetup object is a relatively slow process. When applying settings to many
sheets, you can improve processing speed by setting Application.ScreenUpdating = False to stop
screen updates.
Processing Speed Optimization
Since accessing the PageSetup object takes time, optimize as follows when processing many sheets.
Sub SetMarginsOptimized()
Dim ws As Worksheet
Dim leftMargin As Double
Dim rightMargin As Double
Dim topMargin As Double
Dim bottomMargin As Double
'___Pre-calculate margin values
leftMargin = Application.CentimetersToPoints(1)
rightMargin = Application.CentimetersToPoints(1)
topMargin = Application.CentimetersToPoints(2)
bottomMargin = Application.CentimetersToPoints(2)
'___Temporarily pause screen updates and auto-calculation
Application.ScreenUpdating = False
Application.Calculation = xlCalculationManual
On Error GoTo ErrorHandler
For Each ws In ThisWorkbook.Worksheets
With ws.PageSetup
.LeftMargin = leftMargin
.RightMargin = rightMargin
.TopMargin = topMargin
.BottomMargin = bottomMargin
End With
Next ws
Cleanup:
'___Restore settings
Application.ScreenUpdating = True
Application.Calculation = xlCalculationAutomatic
Exit Sub
ErrorHandler:
MsgBox "An error occurred: " & Err.Description, vbCritical
Resume Cleanup
End Sub
Practical Use Cases
Use Case 1: Auto-Setting Print Templates
An example of automatically applying print settings when creating a new sheet.
Sub CreatePrintReadySheet()
Dim newSheet As Worksheet
'___Add a new sheet
Set newSheet = ThisWorkbook.Worksheets.Add
With newSheet
'___Set sheet name
.Name = "Report_" & Format(Date, "yyyymmdd")
'___Print settings
With .PageSetup
'___Margin settings
.LeftMargin = Application.CentimetersToPoints(2)
.RightMargin = Application.CentimetersToPoints(2)
.TopMargin = Application.CentimetersToPoints(2.5)
.BottomMargin = Application.CentimetersToPoints(2.5)
.HeaderMargin = Application.CentimetersToPoints(1)
.FooterMargin = Application.CentimetersToPoints(1)
'___Other print settings
.Orientation = xlLandscape '___Landscape
.PaperSize = xlPaperA4 '___A4 size
.Zoom = False '___Turn off zoom
.FitToPagesWide = 1 '___Fit to 1 page wide
.FitToPagesTall = False '___Height is automatic
.CenterHorizontally = True '___Center horizontally
End With
End With
MsgBox "A new sheet with print settings has been created.", vbInformation
End Sub
Use Case 2: Reset Margin Settings
A function to reset margin settings to Excel’s default values.
Sub ResetMarginsToDefault()
'___Excel's default margin values (in inches)
Const DEFAULT_TOP As Double = 0.75
Const DEFAULT_BOTTOM As Double = 0.75
Const DEFAULT_LEFT As Double = 0.7
Const DEFAULT_RIGHT As Double = 0.7
Const DEFAULT_HEADER As Double = 0.3
Const DEFAULT_FOOTER As Double = 0.3
With ActiveSheet.PageSetup
.TopMargin = Application.InchesToPoints(DEFAULT_TOP)
.BottomMargin = Application.InchesToPoints(DEFAULT_BOTTOM)
.LeftMargin = Application.InchesToPoints(DEFAULT_LEFT)
.RightMargin = Application.InchesToPoints(DEFAULT_RIGHT)
.HeaderMargin = Application.InchesToPoints(DEFAULT_HEADER)
.FooterMargin = Application.InchesToPoints(DEFAULT_FOOTER)
End With
MsgBox "Margins have been reset to default values.", vbInformation
End Sub
Use Case 3: Set Margins with User Input
An interactive macro that lets users input margin values.
Sub SetMarginsInteractive()
Dim leftVal As Variant
Dim rightVal As Variant
Dim topVal As Variant
Dim bottomVal As Variant
'___Get margin values from user (in centimeters)
leftVal = InputBox("Enter left margin (cm):", "Margin Settings", "1.5")
If leftVal = "" Then Exit Sub
rightVal = InputBox("Enter right margin (cm):", "Margin Settings", "1.5")
If rightVal = "" Then Exit Sub
topVal = InputBox("Enter top margin (cm):", "Margin Settings", "2")
If topVal = "" Then Exit Sub
bottomVal = InputBox("Enter bottom margin (cm):", "Margin Settings", "2")
If bottomVal = "" Then Exit Sub
'___Validate input values
If Not IsNumeric(leftVal) Or Not IsNumeric(rightVal) Or _
Not IsNumeric(topVal) Or Not IsNumeric(bottomVal) Then
MsgBox "Please enter numeric values.", vbExclamation
Exit Sub
End If
'___Set margins
With ActiveSheet.PageSetup
.LeftMargin = Application.CentimetersToPoints(CDbl(leftVal))
.RightMargin = Application.CentimetersToPoints(CDbl(rightVal))
.TopMargin = Application.CentimetersToPoints(CDbl(topVal))
.BottomMargin = Application.CentimetersToPoints(CDbl(bottomVal))
End With
MsgBox "Margins have been set.", vbInformation
End Sub
Use Case 4: Get and Display Current Margin Settings
A macro to check the current sheet’s margin settings.
Sub ShowCurrentMargins()
Dim msg As String
With ActiveSheet.PageSetup
msg = "[Current Margin Settings]" & vbCrLf & vbCrLf
msg = msg & "Left margin: " & Format(.LeftMargin / 28.35, "0.00") & " cm" & vbCrLf
msg = msg & "Right margin: " & Format(.RightMargin / 28.35, "0.00") & " cm" & vbCrLf
msg = msg & "Top margin: " & Format(.TopMargin / 28.35, "0.00") & " cm" & vbCrLf
msg = msg & "Bottom margin: " & Format(.BottomMargin / 28.35, "0.00") & " cm" & vbCrLf
msg = msg & "Header: " & Format(.HeaderMargin / 28.35, "0.00") & " cm" & vbCrLf
msg = msg & "Footer: " & Format(.FooterMargin / 28.35, "0.00") & " cm"
End With
MsgBox msg, vbInformation, "Margin Settings"
End Sub
To convert from points to centimeters, divide the point value by 28.35. For more precision, you
can also divide by the value of Application.CentimetersToPoints(1).
Combining Margin Settings with Other Print Settings
Margin settings can be used more effectively when combined with other print settings.
Sub CompletePrintSetup()
With ActiveSheet.PageSetup
'___Margin settings
.LeftMargin = Application.CentimetersToPoints(1.5)
.RightMargin = Application.CentimetersToPoints(1.5)
.TopMargin = Application.CentimetersToPoints(2)
.BottomMargin = Application.CentimetersToPoints(2)
.HeaderMargin = Application.CentimetersToPoints(1)
.FooterMargin = Application.CentimetersToPoints(1)
'___Paper settings
.PaperSize = xlPaperA4
.Orientation = xlPortrait '___Portrait
'___Print area
.PrintArea = "A1:G50"
'___Title rows and columns
.PrintTitleRows = "$1:$2" '___Print rows 1 and 2 on each page
.PrintTitleColumns = "" '___No column repetition
'___Header and footer
.LeftHeader = "&D" '___Date
.CenterHeader = "Monthly Report"
.RightHeader = ""
.LeftFooter = ""
.CenterFooter = "&P / &N" '___Page number / Total pages
.RightFooter = ""
'___Other settings
.CenterHorizontally = True
.CenterVertically = False
.PrintGridlines = False
.BlackAndWhite = False
End With
End Sub
Common Errors and Solutions
Error 1: Margins Too Large
An error occurs when the total margins exceed the paper size.
Sub SafeSetMargins()
On Error Resume Next
With ActiveSheet.PageSetup
.LeftMargin = Application.CentimetersToPoints(5)
.RightMargin = Application.CentimetersToPoints(5)
End With
If Err.Number <> 0 Then
MsgBox "Failed to set margins. The values may be too large.", vbExclamation
Err.Clear
End If
End Sub
Error 2: Sheet Is Protected
On protected sheets, you may not be able to change PageSetup.
Sub SetMarginsWithProtection()
Dim ws As Worksheet
Set ws = ActiveSheet
'___Temporarily unprotect if the sheet is protected
If ws.ProtectContents Then
ws.Unprotect Password:="password" '___If password is required
End If
With ws.PageSetup
.LeftMargin = Application.CentimetersToPoints(1)
.RightMargin = Application.CentimetersToPoints(1)
End With
'___Re-protect (if needed)
ws.Protect Password:="password"
End Sub
Summary
This article explained how to set print margins using VBA. By using the margin-related properties of the PageSetup object, you can efficiently manage print settings.
Here are the key points:
- Margins are specified in points; use
InchesToPointsandCentimetersToPointsfunctions for conversion - Set four-sided margins with
LeftMargin,RightMargin,TopMargin,BottomMargin - Set header and footer margins with
HeaderMargin,FooterMargin - Use
For Eachloop for bulk settings across multiple sheets - Temporarily turn off
ScreenUpdatingto improve processing speed
Use this knowledge to streamline your printing tasks.