Collectionオブジェクト

にメンテナンス済み

VBA で複数のデータを管理する方法として、配列以外に Collection オブジェクトという選択肢があります。Collection は配列よりも柔軟で、データの追加・削除が簡単に行える便利なデータ構造です。

この記事では、Collection オブジェクトの基本的な使い方から、Dictionary との違い、実践的な活用例まで詳しく解説します。

Collection オブジェクトとは

Collection オブジェクトは、VBA の組み込みオブジェクトで、複数のアイテムを順序付きで格納できるデータ構造です。配列と似ていますが、より動的で柔軟な操作が可能です。

Collection の特徴

  • 動的なサイズ変更: 要素数を事前に宣言する必要がない
  • 異なるデータ型: 文字列、数値、オブジェクトなど、異なる型のデータを混在できる
  • 順序の保持: 追加した順序でデータが保持される
  • キー指定: オプションでキーを指定してデータを管理できる
  • 参照設定不要: VBA の標準機能なので追加の設定が不要

配列との比較

機能Collection配列
サイズ変更○ 動的△ ReDim 必要
データ型の混在○ 可能× 不可
要素の追加○ 簡単△ 面倒
要素の削除○ 簡単△ 面倒
インデックス1 から開始0 から開始*
パフォーマンス△ やや遅い○ 高速

*配列は Option Base や宣言方法で変更可能

Collectionのインデックス

Collectionのインデックスは常に1から始まります。配列のように0から始まることはありません。

Collection の基本的な使い方

インスタンスの作成

Collection オブジェクトは New キーワードで作成します。

Collectionの作成
Dim myCollection As Collection
Set myCollection = New Collection

' 以下のように1行で書くこともできます
Dim myCollection As New Collection

Add メソッド - 要素の追加

Collection に要素を追加するには Add メソッドを使用します。

要素の追加
Dim fruits As New Collection

' 要素を追加
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

Debug.Print fruits.Count  ' => 3

キーを指定して追加

要素を追加する際に、オプションでキーを指定できます。

キー付きで追加
Dim prices As New Collection

' 第1引数:値, 第2引数:キー
prices.Add Item:=100, Key:="apple"
prices.Add 150, "banana"
prices.Add 120, "orange"

' キーを使って値を取得
Debug.Print prices("apple")   ' => 100
Debug.Print prices("banana")  ' => 150
キーの重複に注意

同じキーで要素を追加しようとすると「既に関連付けられています」というエラーが発生します。キーは一意である必要があります。

位置を指定して追加

Before または After パラメータを使用して、特定の位置に要素を追加できます。

位置指定での追加
Dim items As New Collection

items.Add "First"
items.Add "Third"

' "First"の後に追加
items.Add "Second", After:=1

' 結果: "First", "Second", "Third"

Item プロパティ - 要素の取得

インデックスまたはキーを指定して要素を取得します。

要素の取得
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

' インデックスで取得(1から開始)
Debug.Print fruits.Item(1)  ' => apple
Debug.Print fruits(1)       ' Itemは省略可能

' キーで取得(キーを指定して追加した場合)
Dim prices As New Collection
prices.Add 100, "apple"

Debug.Print prices("apple")  ' => 100

Remove メソッド - 要素の削除

インデックスまたはキーを指定して要素を削除します。

要素の削除
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

' インデックスで削除
fruits.Remove 2  ' "banana"が削除される

' キーで削除
Dim prices As New Collection
prices.Add 100, "apple"
prices.Add 150, "banana"

prices.Remove "apple"  ' キーで削除

Debug.Print prices.Count  ' => 1
削除時のインデックス変更

要素を削除すると、それ以降の要素のインデックスが自動的に詰められます。ループ内で削除する場合は、後ろから削除するか注意が必要です。

Count プロパティ - 要素数の取得

Collection に格納されている要素の数を取得します。

要素数の取得
Dim items As New Collection
items.Add "Item1"
items.Add "Item2"
items.Add "Item3"

Debug.Print "要素数: " & items.Count  ' => 3

' 要素が空かチェック
If items.Count = 0 Then
    Debug.Print "Collectionは空です"
End If

Collection のループ処理

For Each ループ(推奨)

Collection の要素を処理する最も一般的な方法です。

ForEachループ
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

Dim fruit As Variant
For Each fruit In fruits
    Debug.Print fruit
Next fruit
' => apple, banana, orange

For ループ

インデックスを使用したループ処理も可能です。

Forループ
Dim fruits As New Collection
fruits.Add "apple"
fruits.Add "banana"
fruits.Add "orange"

Dim i As Long
For i = 1 To fruits.Count
    Debug.Print fruits(i)
Next i
For Eachが推奨

特別な理由がない限り、For Eachループの使用をお勧めします。コードが簡潔で、インデックスの管理も不要です。

後ろから削除する

ループ内で要素を削除する場合は、後ろから処理します。

後ろからループ
Dim items As New Collection
items.Add "keep"
items.Add "delete"
items.Add "keep"
items.Add "delete"

' 後ろから削除
Dim i As Long
For i = items.Count To 1 Step -1
    If items(i) = "delete" Then
        items.Remove i
    End If
Next i

' 結果: "keep", "keep"のみ残る

Dictionary との違いと使い分け

Collection と Dictionary の比較

機能CollectionDictionary
参照設定不要推奨(なしも可)
キーの存在確認× 不可○ Exists メソッド
キーの取得× 不可○ Keys メソッド
値の更新× 不可(削除 → 追加)○ 簡単
データの順序○ 保持△ 保証なし*
用途順序重視検索・更新重視

*Dictionary は追加順を保持しますが、仕様上保証されていません

Collection が適している場合

Collectionが適している例
' 例1: 順序が重要な場合
Dim tasks As New Collection
tasks.Add "タスク1"
tasks.Add "タスク2"
tasks.Add "タスク3"

' 順序通りに処理
For Each task In tasks
    Debug.Print task
Next task

' 例2: オブジェクトのリスト
Dim workbooks As New Collection
workbooks.Add Workbooks.Open("C:\file1.xlsx")
workbooks.Add Workbooks.Open("C:\file2.xlsx")

' 例3: 一時的なデータの保持
Dim tempData As New Collection
tempData.Add Range("A1").Value
tempData.Add Range("A2").Value

Dictionary が適している場合

Dictionaryが適している例
' 例1: キーによる検索が多い場合
Dim prices As Object
Set prices = CreateObject("Scripting.Dictionary")
prices.Add "apple", 100
prices.Add "banana", 150

If prices.Exists("apple") Then
    Debug.Print prices("apple")
End If

' 例2: データの更新が頻繁な場合
prices("apple") = 120  ' 簡単に更新できる

' 例3: キーの一覧が必要な場合
Dim keys As Variant
keys = prices.Keys
Dictionaryオブジェクト
VBAのDictionaryオブジェクトは、キーと値のペアでデータを管理できる強力なデータ構造です。この記事では、Dictionaryの基本的な使い方から実践的な活用方法まで、初心者にもわかりやすく解説します。

実践的な活用例

例 1: シート名のリストを作成

シート名のリスト
Sub GetSheetNames()
    Dim sheetNames As New Collection

    Dim ws As Worksheet
    For Each ws In ThisWorkbook.Worksheets
        sheetNames.Add ws.Name
    Next ws

    ' シート名を出力
    Dim sheetName As Variant
    For Each sheetName In sheetNames
        Debug.Print sheetName
    Next sheetName
End Sub

例 2: セル範囲の値を Collection に格納

セル範囲からCollection
Sub RangeTollection()
    Dim values As New Collection

    Dim rng As Range
    Set rng = Range("A1:A10")

    ' セルの値をCollectionに追加
    Dim cell As Range
    For Each cell In rng
        If cell.Value <> "" Then
            values.Add cell.Value
        End If
    Next cell

    Debug.Print "格納された値の数: " & values.Count
End Sub

例 3: フィルタ処理

データのフィルタリング
Sub FilterData()
    Dim allData As New Collection
    allData.Add 10
    allData.Add 25
    allData.Add 30
    allData.Add 15
    allData.Add 40

    ' 20以上の値のみ抽出
    Dim filteredData As New Collection

    Dim value As Variant
    For Each value In allData
        If value >= 20 Then
            filteredData.Add value
        End If
    Next value

    ' 結果: 25, 30, 40
    For Each value In filteredData
        Debug.Print value
    Next value
End Sub

例 4: オブジェクトのコレクション管理

オブジェクトのコレクション
' カスタムクラス(Person)の例
' クラスモジュール: Person
Public Name As String
Public Age As Long

' 標準モジュール
Sub ManagePersons()
    Dim persons As New Collection

    ' Personオブジェクトを作成して追加
    Dim person1 As New Person
    person1.Name = "山田太郎"
    person1.Age = 30
    persons.Add person1

    Dim person2 As New Person
    person2.Name = "佐藤花子"
    person2.Age = 25
    persons.Add person2

    ' すべての人を出力
    Dim person As Person
    For Each person In persons
        Debug.Print person.Name & " (" & person.Age & "歳)"
    Next person
End Sub

例 5: ユニークな値の抽出

ユニークな値の抽出
Sub GetUniqueValues()
    ' 元データ
    Dim data As Variant
    data = Array("apple", "banana", "apple", "orange", "banana", "grape")

    Dim uniqueValues As New Collection

    ' 重複チェックしながら追加
    Dim i As Long
    For i = LBound(data) To UBound(data)
        Dim alreadyExists As Boolean
        alreadyExists = False

        Dim existingValue As Variant
        For Each existingValue In uniqueValues
            If existingValue = data(i) Then
                alreadyExists = True
                Exit For
            End If
        Next existingValue

        If Not alreadyExists Then
            uniqueValues.Add data(i)
        End If
    Next i

    ' 結果: "apple", "banana", "orange", "grape"
    Dim value As Variant
    For Each value In uniqueValues
        Debug.Print value
    Next value
End Sub
Dictionaryの方が効率的

ユニークな値の抽出には、Dictionaryオブジェクトを使用する方が効率的です。上記はCollectionの使用例として示しています。

例 6: ワークブックの一括管理

複数ワークブックの管理
Sub ManageWorkbooks()
    Dim openedWorkbooks As New Collection

    ' 複数のワークブックを開いてCollectionに格納
    Dim filePaths As Variant
    filePaths = Array("C:\file1.xlsx", "C:\file2.xlsx", "C:\file3.xlsx")

    Dim i As Long
    For i = LBound(filePaths) To UBound(filePaths)
        Dim wb As Workbook
        Set wb = Workbooks.Open(filePaths(i))
        openedWorkbooks.Add wb
    Next i

    ' 全ワークブックに対して処理
    Dim workbook As Workbook
    For Each workbook In openedWorkbooks
        Debug.Print workbook.Name
        ' ここに処理を記述
    Next workbook

    ' 全ワークブックを保存して閉じる
    For Each workbook In openedWorkbooks
        workbook.Close SaveChanges:=True
    Next workbook
End Sub

例 7: エラーログの収集

エラーログの収集
Sub CollectErrors()
    Dim errors As New Collection

    ' データ検証処理
    Dim ws As Worksheet
    Set ws = ThisWorkbook.Sheets("データ")

    Dim lastRow As Long
    lastRow = ws.Cells(ws.Rows.Count, 1).End(xlUp).Row

    Dim i As Long
    For i = 2 To lastRow
        ' 年齢が0-150の範囲外ならエラー
        Dim age As Long
        age = ws.Cells(i, 2).Value

        If age < 0 Or age > 150 Then
            errors.Add "行" & i & ": 不正な年齢 (" & age & ")"
        End If

        ' 空白チェック
        If ws.Cells(i, 1).Value = "" Then
            errors.Add "行" & i & ": 名前が空白"
        End If
    Next i

    ' エラーを表示
    If errors.Count > 0 Then
        Dim errorMsg As String
        errorMsg = "以下のエラーが見つかりました:" & vbCrLf & vbCrLf

        Dim errItem As Variant
        For Each errItem In errors
            errorMsg = errorMsg & errItem & vbCrLf
        Next errItem

        MsgBox errorMsg, vbExclamation
    Else
        MsgBox "エラーはありませんでした", vbInformation
    End If
End Sub

Collection の高度な使い方

ネストした Collection

Collection の要素として別の Collection を格納できます。

ネストしたCollection
Sub NestedCollection()
    Dim departments As New Collection

    ' 営業部のメンバー
    Dim salesTeam As New Collection
    salesTeam.Add "山田"
    salesTeam.Add "佐藤"
    salesTeam.Add "鈴木"

    ' 開発部のメンバー
    Dim devTeam As New Collection
    devTeam.Add "田中"
    devTeam.Add "高橋"

    ' 部署にチームを追加
    departments.Add salesTeam, "営業部"
    departments.Add devTeam, "開発部"

    ' データの取得
    Dim member As Variant
    For Each member In departments("営業部")
        Debug.Print "営業部: " & member
    Next member
End Sub

Collection を関数の戻り値に

関数の戻り値
Function GetFilteredData(minValue As Long) As Collection
    Dim result As New Collection

    Dim ws As Worksheet
    Set ws = ThisWorkbook.Sheets("データ")

    Dim lastRow As Long
    lastRow = ws.Cells(ws.Rows.Count, 1).End(xlUp).Row

    Dim i As Long
    For i = 2 To lastRow
        Dim value As Long
        value = ws.Cells(i, 1).Value

        If value >= minValue Then
            result.Add value
        End If
    Next i

    Set GetFilteredData = result
End Function

' 使用例
Sub UseFilteredData()
    Dim data As Collection
    Set data = GetFilteredData(100)

    Dim item As Variant
    For Each item In data
        Debug.Print item
    Next item
End Sub

Collection のクリア(全削除)

Collection には Clear メソッドがないため、工夫が必要です。

Collectionのクリア
Sub ClearCollection(col As Collection)
    ' 方法1: 後ろから削除
    Do While col.Count > 0
        col.Remove col.Count
    Loop

    ' 方法2: 新しいCollectionを作成
    Set col = New Collection
End Sub

' 使用例
Sub TestClear()
    Dim items As New Collection
    items.Add "Item1"
    items.Add "Item2"
    items.Add "Item3"

    Debug.Print "クリア前: " & items.Count  ' => 3

    ClearCollection items

    Debug.Print "クリア後: " & items.Count  ' => 0
End Sub

パフォーマンスの考慮事項

Collection vs 配列のパフォーマンス

パフォーマンス比較
Sub PerformanceTest()
    Dim startTime As Double

    ' Collection
    startTime = Timer
    Dim col As New Collection
    Dim i As Long
    For i = 1 To 10000
        col.Add i
    Next i
    Debug.Print "Collection: " & Format(Timer - startTime, "0.000") & "秒"

    ' 配列
    startTime = Timer
    Dim arr() As Long
    ReDim arr(1 To 10000)
    For i = 1 To 10000
        arr(i) = i
    Next i
    Debug.Print "配列: " & Format(Timer - startTime, "0.000") & "秒"
End Sub
パフォーマンス特性

一般的に配列の方が高速ですが、Collection は柔軟性が高いため、データの追加・削除が頻繁な場合や要素数が不確定な場合に適しています。

よくある質問とトラブルシューティング

Q1: キーが存在するか確認したい

Collection には Exists メソッドがないため、エラー処理で対応します。

キーの存在確認
Function CollectionKeyExists(col As Collection, key As String) As Boolean
    On Error Resume Next

    Dim temp As Variant
    temp = col(key)

    CollectionKeyExists = (Err.Number = 0)

    On Error GoTo 0
End Function

' 使用例
Sub TestKeyExists()
    Dim items As New Collection
    items.Add "Value1", "Key1"

    If CollectionKeyExists(items, "Key1") Then
        Debug.Print "Key1は存在します"
    Else
        Debug.Print "Key1は存在しません"
    End If
End Sub

Q2: Collection をコピーしたい

Collection には Clone メソッドがないため、ループで複製します。

Collectionのコピー
Function CloneCollection(original As Collection) As Collection
    Dim newCol As New Collection

    Dim item As Variant
    For Each item In original
        newCol.Add item
    Next item

    Set CloneCollection = newCol
End Function

Q3: Collection を配列に変換したい

Collectionを配列に変換
Function CollectionToArray(col As Collection) As Variant
    If col.Count = 0 Then
        CollectionToArray = Array()
        Exit Function
    End If

    Dim arr() As Variant
    ReDim arr(1 To col.Count)

    Dim i As Long
    For i = 1 To col.Count
        arr(i) = col(i)
    Next i

    CollectionToArray = arr
End Function

' 使用例
Sub TestConversion()
    Dim col As New Collection
    col.Add "apple"
    col.Add "banana"
    col.Add "orange"

    Dim arr As Variant
    arr = CollectionToArray(col)

    Dim i As Long
    For i = LBound(arr) To UBound(arr)
        Debug.Print arr(i)
    Next i
End Sub

まとめ

Collection オブジェクトは、VBA で動的なデータ管理を行うための便利なツールです。主な特徴をまとめると:

  1. 動的なサイズ: 要素数を事前に決める必要がない
  2. 柔軟性: 異なるデータ型を混在できる
  3. 簡単な操作: 要素の追加・削除が簡単
  4. 順序の保持: データの順序が重要な場合に適している
  5. 参照設定不要: VBA の標準機能

Collection は配列よりも柔軟で、Dictionary よりもシンプルです。データの順序が重要で、頻繁な検索や更新が不要な場合に最適な選択肢となります。

ぜひ実際のプロジェクトで Collection を活用して、より効率的で保守性の高いコードを書いてみてください。

#VBA #Collection #データ構造 #オブジェクト指向