Worksheet.HPageBreaks property (Excel)

Returns an HPageBreaks collection that represents the horizontal page breaks on the sheet. Read-only.

Syntax

expression.HPageBreaks

expression A variable that represents a Worksheet object.

Remarks

There is a limit of 1,026 horizontal page breaks per sheet.

Example

The following code example displays the number of full-screen and print-area horizontal page breaks.

For Each pb in Worksheets(1).HPageBreaks 
    If pb.Extent = xlPageBreakFull Then 
        cFull = cFull + 1 
    Else 
        cPartial = cPartial + 1 
    End If 
Next 
MsgBox cFull & " full-screen page breaks, " & cPartial & _ 
    " print-area page breaks"

The following code example adds a page break when the value of a cell in column A changes.

Sub AddPageBreaks() 
    StartRow = 2 
    FinalRow = Range("A65536").End(xlUp).Row 
    LastVal = Cells(StartRow, 1).Value 
    For i = StartRow To FinalRow 
    ThisVal = Cells(i, 1).Value 
    If Not ThisVal = LastVal Then 
    ActiveSheet.HPageBreaks.Add before:=Cells(i, 1) 
    End If 
    LastVal = ThisVal 
    Next i 
End Sub

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.