配列を利用する:Excel VBA入門 |
スポンサードリンク | |
2021/06/13
配列を利用する | 定数を利用する | セルの値を配列に読み込む |
データ型 | 配列を初期化する(Erase) |
Sub rei_701() Dim I As Integer Dim A(5) As Integer For I = 0 To 5 A(I) = I Next I For I = 0 To 5 Cells(I + 1, 1).Value = A(I) * 10 'Range("A" & I + 1).Value = A(I) * 10 Next I End Sub |
Option Base 1 Sub rei_701() Dim I As Integer Dim A(5) As Integer For I = 1 To 5 A(I) = I Next I For I = 1 To 5 Cells(I, 1).Value = A(I) * 10 'Range("A" & I).Value = A(I) * 10 Next I End Sub |
Sub rei_701() Dim I As Integer Dim A(3 To 5) As Integer For I = 3 To 5 A(I) = I Next I For I = 3 To 5 Cells(I, 1).Value = A(I) * 10 'Range("A" & I).Value = A(I) * 10 Next I End Sub |
Sub rei_701() Dim I As Integer Dim A(3 To 5) As Integer For I = LBound(A) To UBound(A) A(I) = I Next I For I = LBound(A) To UBound(A) Cells(I, 1).Value = A(I) * 10 'Range("A" & I).Value = A(I) * 10 Next I End Sub |
Sub rei_701() Dim I As Integer Dim B As Variant B = Array(0, 1, 2, 3, 4, 5) For I = LBound(B) To UBound(B) Cells(I + 1, 1).Value = B(I) * 10 'Range("A" & I).Value = B(I) * 10 Next I End Sub |
Sub rei_701() Dim I As Integer Dim lRow As Integer Dim C() As Integer lRow = Cells(Rows.Count, 1).End(xlUp).Row 'A列の最終行番号を求めています ReDim C(lRow) For I = 1 To lRow C(I) = Cells(I, 1).Value * 10 Next I For I = 1 To lRow Cells(I, 2).Value = C(I) Next I End Sub |
Sub rei_701() Dim I As Integer Dim lRow As Integer, lRow2 As Integer Dim C() As Integer lRow = Cells(Rows.Count, 1).End(xlUp).Row ReDim C(lRow) For I = 1 To lRow C(I) = Cells(I, 1).Value * 10 Next I Cells(lRow + 1, 1).Value = 50 Cells(lRow + 2, 1).Value = 60 ' lRow2 = Cells(Rows.Count, 1).End(xlUp).Row ReDim Preserve C(lRow2) ' For I = lRow + 1 To lRow2 C(I) = Cells(I, 1).Value * 10 Next I For I = 1 To lRow2 Cells(I, 2).Value = C(I) Next I End Sub |
Sub rei_701() Dim I As Integer Dim lRow As Integer, lRow2 As Integer Dim C() As Integer lRow = Cells(Rows.Count, 1).End(xlUp).Row ReDim C(lRow) For I = 1 To lRow C(I) = Cells(I, 1).Value * 10 Next I Cells(lRow + 1, 1).Value = 50 Cells(lRow + 2, 1).Value = 60 ' lRow2 = Cells(Rows.Count, 1).End(xlUp).Row ReDim C(lRow2) ' For I = lRow + 1 To lRow2 C(I) = Cells(I, 1).Value * 10 Next I For I = 1 To lRow2 Cells(I, 2).Value = C(I) Next I End Sub |
Sub rei_702() Dim I As Integer Const Zei As Single = 0.05 For I = 2 To 5 Cells(I, 2).Value = Int(Cells(I, 1).Value * Zei) Next I End Sub |
Sub rei_705() Dim A As Variant A = Range("A1:B5").Value Range("D1:E5").Value = A End Sub |
Sub sample_data() Dim i As Long Dim j As Long Dim cn As Long For j = 1 To 12 For i = 1 To 5000 cn = cn + 1 Cells(i + (j - 1) * 5000, 1).Value = i Cells(i + (j - 1) * 5000, 2).Value = cn Next i Next j |
Sub sample2() Dim myData(1 To 60000, 1 To 2) Dim i As Long Dim j As Long Dim cn As Long For j = 1 To 12 For i = 1 To 5000 cn = cn + 1 myData(i + (j - 1) * 5000, 1) = i myData(i + (j - 1) * 5000, 2) = cn Next i Next j Range("A1:B60000").Value = myData End Sub |
Sub rei_706() Dim i As Long, myCnt As Long For i = 1 To 60000 If Range("A" & i).Value = 5000 Then myCnt = myCnt + 1 Range("D" & myCnt).Value = Range("B" & i).Value End If Next i End Sub |
Sub rei_707() Dim c As Range, myCnt As Long Dim myTime For Each c In Range("A1:A60000") If c.Value = 5000 Then myCnt = myCnt + 1 Range("D" & myCnt).Value = c.Offset(0, 1).Value End If Next c End Sub |
Sub rei_708() Dim A As Variant Dim i As Long, myCnt As Long A = Range("A1:B60000").Value For i = 1 To 60000 If A(i, 1) = 5000 Then myCnt = myCnt + 1 Range("D" & myCnt).Value = A(i, 2) End If Next i End Sub |
表記 | 意味 | 型宣言文字 | データ範囲 | Byte数 |
Byte | バイト型 | 0〜255 | 1 | |
Boolean | ブール型 | TrueまたはFalse | 2 | |
Integer | 整数型 | % | -32,768 〜 32,767 | 2 |
Long | 長整数型 | & | -2,147,483,648 〜 2,147,483,647 | 4 |
Currency | 通貨型 | @ | -922,337,203,685,477.5808〜 922,337,203,685,477.5807 |
8 |
Single | 単精度浮動小数点型 | ! | -3.402823E38〜-1.401298E-45(負の値) 1.401298E-45〜3.402823E38(正の値) |
4 |
Double | 倍精度浮動小数点型 | # | -1.79769313486232E308〜-4.94065645841247E-324(負の値) 4.94065645841247E-324〜1.79769313486232E308(正の値) |
8 |
Date | 日付型 | 西暦1900年1月1日〜西暦9999年12月31日 | 8 | |
String | 固定長文字列型 | $ | 0〜約64KB | 1L+2L |
可変長文字列型 | 0〜2GB | 10+L | ||
Variant | バリアント型 | 数値(Double) 文字列(可変長文字列) |
16 22+L |
|
Object | オブジェクト型 | オブジェクトを参照する | 4 | |
Decimal | 10進 | 14 |
配列の型 | Erase ステートメントの実行結果 |
静的数値配列 | 要素はすべて0に設定されます |
静的文字列配列 (可変長) | 要素はすべて長さ0の文字列「""」に設定されます |
静的文字列配列 (固定長) | 要素はすべて0に設定されます |
静的バリアント型 (Variant) | 配列要素はすべてEmpty値に設定されます |
ユーザー定義型配列 | 各要素は、別個の変数として設定されます |
オブジェクト配列 | 要素はすべて特別な値Nothingに設定されます |
スポンサードリンク
PageViewCounter
Since2006/2/27