セル範囲の取得


操作の対象セル範囲が不定の場合


A1A1:C3VBA


RangeClearContents使A1:D5
Sub Sample1()
    Range("A1:D5").ClearContents
End Sub

A1D5Excel

A調調1調
Sub Sample2()
    Dim r As Long, c As Long, i As Long, LastCellAddress As String
    For i = 2 To 100
        If Cells(i, 1) = "" Then
            r = i
            Exit For
        End If
    Next i
    For i = 2 To 100
        If Cells(1, i) = "" Then
            c = i
            Exit For
        End If
    Next i
    LastCellAddress = Chr(64 + c) & r
    Range("A1:" & LastCellAddress & "").ClearContents
End Sub

For NextExit ForChr""()6000Excel

Excel


A1:D5[Delete]
Sub Macro1()
    Range("A1:D5").Select
    Selection.ClearContents
End Sub

A1:D5A1


(一)A1  
(二)[Ctrl][Shift][End]  
(三)A1:D5[Delete]


Sub Macro2()
    Range(Selection, ActiveCell.SpecialCells(xlLastCell)).Select
    Selection.ClearContents
End Sub

Excel[Shift]Excel[Ctrl][End]使使(A1)[Ctrl][Shift][End]使VBAExcelExcelVBAExcelExcelVBA

Excel[Ctrl][Shift][*]A1
Sub Macro3()
    Selection.CurrentRegion.Select
    Selection.ClearContents
End Sub

SpecialCellsCurrentRegion調UsedRange


()



(一)
任意のセル.CurrentRegion

 


Range("B2").CurrentRegionA1:D5Range("C8").CurrentRegionC8:F12[Ctrl][Shift][*]

 

(二)  
Range(任意のセル, ActiveCell.SpecialCells(xlLastCell))

 




 

 Range(, )

 

   使

 

   

    ActiveCell.SpecialCells(xlLastCell)

 

SpecialCells[F5][][][]

 



xlLastCell[]""使""SpecialCellsActiveCell.SpecialCells

 

使()F12

 

   

    F12

 

使A1

 


(三)使
ワークシート.UsedRange

 



UsedRange使使A1""A1UsedRange使

 

 ActiveSheet.UsedRange

 

  Sheets("Sheet1").UsedRange

 



1




 Range()

 Cells(, )

Range使

 Range("A5:D5")





A""
Sub Sample1()
    Dim i As Long
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Cells(i, 1).Select
            Exit For
        End If
    Next i
End Sub

A5A5:D5

便Range(Cells, Cells)

 Range(, )

使

Rnage(Range("A1"), Range("D5"))A1:D5


A1D5Range("A1:D5")(D)
Sub Sample1()
    Dim i As Long
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Cells(i, 1).Select
            Exit For
        End If
    Next i
End Sub

""

   Cells(i, 1)

(i)D

   Cells(i, 4)

""AD
Sub Sample1()
    Dim i As Long
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Range(Cells(i, 1), Cells(i, 4)).Select
            Exit For
        End If
    Next i
End Sub


Select2))(^^;


Sub Sample1()
    Dim i As Long
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Range(Cells(i, 1), Cells(i, 4)).Font.ColorIndex = 3
            Exit For
        End If
    Next i
End Sub


Sub Sample1()
    Dim i As Long
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Range(Cells(i, 1), Cells(i, 4)).Copy Sheets("Sheet2").Range("A1")
            Exit For
        End If
    Next i
End Sub

()使Resize使
Sub Sample1()
    Dim i As Long
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Cells(i, 1).Resize(1, 4).Select
            Exit For
        End If
    Next i
End Sub

ResizeResize使ResizeRange(Cells, Cells)


Sub Sample1()
    Dim i As Long
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Range("A" & i & ":D" & i).Select
            Exit For
        End If
    Next i
End Sub

DE":D"Range(Cells, Cells)Resize
Sub Sample1()
    Dim i As Long
    Const LastColumn As Long = 4    ''拡張する列の位置
    For i = 2 To 5
        If Cells(i, 1) =『土屋』Then
            Range(Cells(i, 1), Cells(i, LastColumn)).Select
            Exit For
        End If
    Next i
End Sub