印刷余白の設定

にメンテナンス済み

Excel で資料を印刷する際、余白の設定は見栄えや読みやすさに大きく影響します。手動で設定することも可能ですが、複数のシートやブックに対して統一した余白を設定したい場合、VBA を使用すると効率的に処理できます。本記事では、PageSetupオブジェクトを使用して印刷余白を設定する方法を詳しく解説します。

印刷余白設定が必要となる場面

VBA で印刷余白を設定する機能は、以下のような場面で特に有用です。

  • 社内テンプレートの標準化:全社で使用するレポートや帳票の余白を統一したい場合
  • 複数シートの一括設定:ブック内のすべてのシートに同じ余白を適用したい場合
  • 印刷プレビュー後の微調整:プログラムで動的に余白を調整する場合
  • 定型業務の自動化:毎日・毎週発生する印刷作業を自動化する場合

手動で余白を設定する場合、「ページレイアウト」タブから「余白」を選択して設定しますが、シートが多い場合は非常に手間がかかります。VBA を使えば、数行のコードで一括設定が可能です。

PageSetup オブジェクトの基本

Excel VBA で印刷設定を行うには、PageSetupオブジェクトを使用します。このオブジェクトはWorksheetオブジェクトのプロパティとしてアクセスできます。

'___基本的なアクセス方法
Worksheets("Sheet1").PageSetup

余白に関するプロパティ

PageSetupオブジェクトには、余白設定に関する以下のプロパティがあります。

プロパティ説明
LeftMargin左余白
RightMargin右余白
TopMargin上余白
BottomMargin下余白
HeaderMarginヘッダー余白(上端から)
FooterMarginフッター余白(下端から)
ポイント

余白のプロパティはすべてポイント単位で指定します。センチメートルやインチで指定したい場合は、変換関数を使用します。

単位変換の方法

VBA では、余白の値をポイント単位で指定する必要があります。センチメートルやインチで指定したい場合は、以下の変換関数を使用します。

'___インチからポイントへ変換
Application.InchesToPoints(1)  '___1インチ = 72ポイント

'___センチメートルからポイントへ変換
Application.CentimetersToPoints(1)  '___1センチメートル ≈ 28.35ポイント

基本的な余白設定のコード例

単一シートの余白を設定

最も基本的な使い方として、特定のシートの余白を設定する例を示します。

Sub SetMarginsSingleSheet()
    With Worksheets("Sheet1").PageSetup
        '___左右の余白を1センチメートルに設定
        .LeftMargin = Application.CentimetersToPoints(1)
        .RightMargin = Application.CentimetersToPoints(1)

        '___上下の余白を2センチメートルに設定
        .TopMargin = Application.CentimetersToPoints(2)
        .BottomMargin = Application.CentimetersToPoints(2)

        '___ヘッダーとフッターの余白を0.5センチメートルに設定
        .HeaderMargin = Application.CentimetersToPoints(0.5)
        .FooterMargin = Application.CentimetersToPoints(0.5)
    End With
End Sub

インチ単位で設定する場合

インチ単位で余白を設定する場合は、InchesToPoints関数を使用します。

Sub SetMarginsInInches()
    With ActiveSheet.PageSetup
        '___左右の余白を0.5インチに設定
        .LeftMargin = Application.InchesToPoints(0.5)
        .RightMargin = Application.InchesToPoints(0.5)

        '___上下の余白を0.75インチに設定
        .TopMargin = Application.InchesToPoints(0.75)
        .BottomMargin = Application.InchesToPoints(0.75)
    End With
End Sub

ポイント単位で直接指定

ポイント単位で直接指定することも可能です。1 インチ = 72 ポイントとして計算します。

Sub SetMarginsInPoints()
    With ActiveSheet.PageSetup
        '___36ポイント(0.5インチ)に設定
        .LeftMargin = 36
        .RightMargin = 36
        .TopMargin = 36
        .BottomMargin = 36
    End With
End Sub

複数シートへの一括設定

ブック内のすべてのシートに適用

ブック内のすべてのワークシートに同じ余白設定を適用する例です。

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 "すべてのシートの余白を設定しました。", vbInformation
End Sub

選択したシートのみに適用

ユーザーが選択したシートにのみ余白設定を適用する場合です。

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 "選択したシートの余白を設定しました。", vbInformation
End Sub
注意点

PageSetupオブジェクトへのアクセスは比較的時間がかかる処理です。大量のシートに対して設定を行う場合は、Application.ScreenUpdating = Falseを設定して画面更新を停止することで、処理速度を向上させることができます。

処理速度の最適化

PageSetupオブジェクトへのアクセスは処理に時間がかかるため、大量のシートを処理する場合は以下のように最適化します。

Sub SetMarginsOptimized()
    Dim ws As Worksheet
    Dim leftMargin As Double
    Dim rightMargin As Double
    Dim topMargin As Double
    Dim bottomMargin As Double

    '___余白の値を事前に計算
    leftMargin = Application.CentimetersToPoints(1)
    rightMargin = Application.CentimetersToPoints(1)
    topMargin = Application.CentimetersToPoints(2)
    bottomMargin = Application.CentimetersToPoints(2)

    '___画面更新と自動計算を一時停止
    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:
    '___設定を元に戻す
    Application.ScreenUpdating = True
    Application.Calculation = xlCalculationAutomatic
    Exit Sub

ErrorHandler:
    MsgBox "エラーが発生しました: " & Err.Description, vbCritical
    Resume Cleanup
End Sub

実務での活用例

活用例 1: 印刷用テンプレートの自動設定

新しいシートを作成する際に、自動的に印刷設定を適用する例です。

Sub CreatePrintReadySheet()
    Dim newSheet As Worksheet

    '___新しいシートを追加
    Set newSheet = ThisWorkbook.Worksheets.Add

    With newSheet
        '___シート名を設定
        .Name = "レポート_" & Format(Date, "yyyymmdd")

        '___印刷設定
        With .PageSetup
            '___余白設定
            .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)

            '___その他の印刷設定
            .Orientation = xlLandscape  '___横向き
            .PaperSize = xlPaperA4      '___A4サイズ
            .Zoom = False               '___拡大縮小率をオフ
            .FitToPagesWide = 1         '___横1ページに収める
            .FitToPagesTall = False     '___縦は自動
            .CenterHorizontally = True  '___水平方向に中央揃え
        End With
    End With

    MsgBox "印刷設定済みの新しいシートを作成しました。", vbInformation
End Sub

活用例 2: 余白設定を初期化する

余白設定を Excel の既定値に戻す関数です。

Sub ResetMarginsToDefault()
    '___Excelの既定の余白値(インチ単位)
    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 "余白を既定値に戻しました。", vbInformation
End Sub

活用例 3: 余白設定をユーザー入力で指定

ユーザーに余白の値を入力させて設定する対話型のマクロです。

Sub SetMarginsInteractive()
    Dim leftVal As Variant
    Dim rightVal As Variant
    Dim topVal As Variant
    Dim bottomVal As Variant

    '___ユーザーから余白の値を取得(センチメートル単位)
    leftVal = InputBox("左余白を入力してください(cm):", "余白設定", "1.5")
    If leftVal = "" Then Exit Sub

    rightVal = InputBox("右余白を入力してください(cm):", "余白設定", "1.5")
    If rightVal = "" Then Exit Sub

    topVal = InputBox("上余白を入力してください(cm):", "余白設定", "2")
    If topVal = "" Then Exit Sub

    bottomVal = InputBox("下余白を入力してください(cm):", "余白設定", "2")
    If bottomVal = "" Then Exit Sub

    '___入力値の検証
    If Not IsNumeric(leftVal) Or Not IsNumeric(rightVal) Or _
       Not IsNumeric(topVal) Or Not IsNumeric(bottomVal) Then
        MsgBox "数値を入力してください。", vbExclamation
        Exit Sub
    End If

    '___余白を設定
    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 "余白を設定しました。", vbInformation
End Sub

活用例 4: 現在の余白設定を取得して表示

現在のシートの余白設定を確認するためのマクロです。

Sub ShowCurrentMargins()
    Dim msg As String

    With ActiveSheet.PageSetup
        msg = "【現在の余白設定】" & vbCrLf & vbCrLf
        msg = msg & "左余白: " & Format(.LeftMargin / 28.35, "0.00") & " cm" & vbCrLf
        msg = msg & "右余白: " & Format(.RightMargin / 28.35, "0.00") & " cm" & vbCrLf
        msg = msg & "上余白: " & Format(.TopMargin / 28.35, "0.00") & " cm" & vbCrLf
        msg = msg & "下余白: " & Format(.BottomMargin / 28.35, "0.00") & " cm" & vbCrLf
        msg = msg & "ヘッダー: " & Format(.HeaderMargin / 28.35, "0.00") & " cm" & vbCrLf
        msg = msg & "フッター: " & Format(.FooterMargin / 28.35, "0.00") & " cm"
    End With

    MsgBox msg, vbInformation, "余白設定"
End Sub
ヒント

ポイントからセンチメートルへの変換は、ポイント値を28.35で割ることで計算できます。より正確にはApplication.CentimetersToPoints(1)の値で割る方法もあります。

余白設定と他の印刷設定の組み合わせ

余白設定は、他の印刷設定と組み合わせることで、より効果的に活用できます。

Sub CompletePrintSetup()
    With ActiveSheet.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)

        '___用紙設定
        .PaperSize = xlPaperA4
        .Orientation = xlPortrait  '___縦向き

        '___印刷範囲
        .PrintArea = "A1:G50"

        '___タイトル行・列の設定
        .PrintTitleRows = "$1:$2"  '___1行目と2行目を各ページに印刷
        .PrintTitleColumns = ""     '___列の繰り返しなし

        '___ヘッダー・フッター
        .LeftHeader = "&D"         '___日付
        .CenterHeader = "月次レポート"
        .RightHeader = ""
        .LeftFooter = ""
        .CenterFooter = "&P / &N"  '___ページ番号 / 総ページ数
        .RightFooter = ""

        '___その他の設定
        .CenterHorizontally = True
        .CenterVertically = False
        .PrintGridlines = False
        .BlackAndWhite = False
    End With
End Sub

よくあるエラーと対処法

エラー 1: 余白が大きすぎる

余白の合計が用紙サイズを超えると、エラーが発生します。

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 "余白の設定に失敗しました。値が大きすぎる可能性があります。", vbExclamation
        Err.Clear
    End If
End Sub

エラー 2: シートが保護されている

保護されたシートではPageSetupの変更ができない場合があります。

Sub SetMarginsWithProtection()
    Dim ws As Worksheet
    Set ws = ActiveSheet

    '___シートが保護されている場合は一時的に解除
    If ws.ProtectContents Then
        ws.Unprotect Password:="password"  '___パスワードが必要な場合
    End If

    With ws.PageSetup
        .LeftMargin = Application.CentimetersToPoints(1)
        .RightMargin = Application.CentimetersToPoints(1)
    End With

    '___保護を再設定(必要に応じて)
    ws.Protect Password:="password"
End Sub

まとめ

VBA を使用して印刷余白を設定する方法について解説しました。PageSetupオブジェクトの余白関連プロパティを使用することで、効率的に印刷設定を管理できます。

重要なポイントをまとめると以下の通りです。

  • 余白はポイント単位で指定し、InchesToPointsCentimetersToPoints関数で変換可能
  • LeftMarginRightMarginTopMarginBottomMarginで四辺の余白を設定
  • HeaderMarginFooterMarginでヘッダー・フッターの余白を設定
  • 複数シートへの一括設定にはFor Eachループを使用
  • 処理速度を向上させるにはScreenUpdatingを一時的にオフにする

これらの知識を活用して、印刷業務の効率化に役立ててください。

#Excel VBA #印刷 #PageSetup #余白 #ワークシート