Range.Row 屬性 (Excel)

會傳回範圍中第一個區域中的第一列的列號。 唯讀的 Long

語法

運算式

expression 代表 Range 物件的變數。

範例

本範例會將 Sheet1 上其他每一列的資料列高度設定為 4

For Each rw In Worksheets("Sheet1").Rows 
    If rw.Row Mod 2 = 0 Then 
        rw.RowHeight = 4 
    End If 
Next rw

此範例會使用 BeforeDoubleClick 工作表事件,將一列資料從一張工作表複製到另一張工作表。 若要執行此程式碼,目標工作表的名稱必須位於資料行 A 中。當您按兩下包含資料的儲存格時,此範例會從資料行 A 取得目標工作表名稱,並將整個資料列複製到目標工作表上的下一個可用資料列。 此範例會使用 Target 關鍵字來存取使用中 資料 列。

Private Sub Worksheet_BeforeDoubleClick(ByVal Target As Range, Cancel As Boolean)
    'If the double click occurs on the header row or an empty cell, exit the macro.
    If Target.Row = 1 Then Exit Sub
    If Target.Row > ActiveSheet.UsedRange.Rows.Count Then Exit Sub
    If Target.Column > ActiveSheet.UsedRange.Columns.Count Then Exit Sub
    
    'Override the default double-click behavior with this function.
    Cancel = True
    
    'Declare your variables.
    Dim wks As Worksheet, xRow As Long
    
    'If an error occurs, use inline error handling.
    On Error Resume Next
    
    'Set the target worksheet as the worksheet whose name is listed in the first cell of the current row.
    Set wks = Worksheets(CStr(Cells(Target.Row, 1).Value))
    'If there is an error, exit the macro.
    If Err > 0 Then
        Err.Clear
        Exit Sub
    'Otherwise, find the next empty row in the target worksheet and copy the data into that row.
    Else
        xRow = wks.Cells(wks.Rows.Count, 1).End(xlUp).Row + 1
        wks.Range(wks.Cells(xRow, 1), wks.Cells(xRow, 7)).Value = _
        Range(Cells(Target.Row, 1), Cells(Target.Row, 7)).Value
    End If
End Sub

本範例會從選取範圍中刪除空白的資料列。

Sub Delete_Empty_Rows()
    'The range from which to delete the rows.
    Dim rnSelection As Range
    
    'Row and count variables used in the deletion process.
    Dim lnLastRow As Long
    Dim lnRowCount As Long
    Dim lnDeletedRows As Long
    
    'Initialize the number of deleted rows.
    lnDeletedRows = 0
    
    'Confirm that a range is selected, and that the range is contiguous.
    If TypeName(Selection) = "Range" Then
        If Selection.Areas.Count = 1 Then
            
            'Initialize the range to what the user has selected, and initialize the count for the upcoming FOR loop.
            Set rnSelection = Application.Selection
            lnLastRow = rnSelection.Rows.Count
        
            'Start at the bottom row and work up: if the row is empty then
            'delete the row and increment the deleted row count.
            For lnRowCount = lnLastRow To 1 Step -1
                If Application.CountA(rnSelection.Rows(lnRowCount)) = 0 Then
                    rnSelection.Rows(lnRowCount).Delete
                    lnDeletedRows = lnDeletedRows + 1
                End If
            Next lnRowCount
        
            rnSelection.Resize(lnLastRow - lnDeletedRows).Select
         Else
            MsgBox "Please select only one area.", vbInformation
         End If
    Else
        MsgBox "Please select a range.", vbInformation
    End If
    
    'Turn screen updating back on.
    Application.ScreenUpdating = True

End Sub

支援和意見反應

有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應