Excel VBA 逆引き集 | 分割Dictionary

Excel VBA
スポンサーリンク

分割Dictionary(キーごとに複数値を管理)

通常の Dictionary は「キー → 値」のペアを管理しますが、値に 配列や別Dictionary を入れることで「分割Dictionary」的な使い方ができます。これにより「顧客コード → 複数の購入商品」「カテゴリ → 複数の属性」など、キーごとに複数の情報をまとめて扱えるようになります。初心者向けに、コード例やテンプレートをかみ砕いて説明します。


基本の考え方

  • 分割Dictionaryとは?
    1つのキーに対して「複数の値」を持たせる仕組み。
  • 方法:
    • 値に配列を格納する。
    • 値に別Dictionaryを格納する(入れ子構造)。
  • 用途:
    • 顧客ごとの購入商品一覧。
    • 商品カテゴリごとの属性。
    • 複数条件での集計。

テンプレ1:キーごとに配列を格納(顧客→購入商品)

Sub SplitDict_Array()
    Dim dict As Object: Set dict = CreateObject("Scripting.Dictionary")

    ' 顧客ごとに購入商品を配列で格納
    dict("顧客A") = Array("りんご", "みかん")
    dict("顧客B") = Array("バナナ", "ぶどう", "もも")

    ' 出力
    Dim cust As Variant, arr As Variant, i As Long
    For Each cust In dict.Keys
        Debug.Print "顧客=" & cust
        arr = dict(cust)
        For i = LBound(arr) To UBound(arr)
            Debug.Print "  商品=" & arr(i)
        Next i
    Next cust
End Sub
VB
  • 結果: 顧客=顧客A 商品=りんご 商品=みかん 顧客=顧客B 商品=バナナ 商品=ぶどう 商品=もも

テンプレ2:キーごとに別Dictionaryを格納(カテゴリ→商品→数量)

Sub SplitDict_Dict()
    Dim dictOuter As Object: Set dictOuter = CreateObject("Scripting.Dictionary")
    Dim dictInner As Object

    ' フルーツカテゴリ
    Set dictInner = CreateObject("Scripting.Dictionary")
    dictInner("りんご") = 10
    dictInner("みかん") = 20
    dictOuter("フルーツ") = dictInner

    ' 野菜カテゴリ
    Set dictInner = CreateObject("Scripting.Dictionary")
    dictInner("にんじん") = 15
    dictInner("キャベツ") = 25
    dictOuter("野菜") = dictInner

    ' 出力
    Dim cat As Variant, item As Variant
    For Each cat In dictOuter.Keys
        Debug.Print "カテゴリ=" & cat
        For Each item In dictOuter(cat).Keys
            Debug.Print "  商品=" & item, "数量=" & dictOuter(cat)(item)
        Next item
    Next cat
End Sub
VB
  • 結果: カテゴリ=フルーツ 商品=りんご 数量=10 商品=みかん 数量=20 カテゴリ=野菜 商品=にんじん 数量=15 商品=キャベツ 数量=25

テンプレ3:シートデータを分割Dictionaryに格納(顧客→商品リスト)

Sub SplitDict_FromSheet()
    Dim ws As Worksheet: Set ws = Worksheets("Data")
    Dim rg As Range: Set rg = ws.Range("A2:C20") ' A=顧客, B=商品, C=数量
    Dim v As Variant: v = rg.Value

    Dim dict As Object: Set dict = CreateObject("Scripting.Dictionary")
    Dim r As Long, cust As String, prod As String

    For r = 1 To UBound(v, 1)
        cust = v(r, 1)
        prod = v(r, 2) & "(" & v(r, 3) & ")" ' 商品(数量)

        Dim arr As Variant
        If dict.Exists(cust) Then
            arr = dict(cust)
            ReDim Preserve arr(LBound(arr) To UBound(arr) + 1)
            arr(UBound(arr)) = prod
            dict(cust) = arr
        Else
            dict(cust) = Array(prod)
        End If
    Next r

    ' 出力
    Dim k As Variant, i As Long
    For Each k In dict.Keys
        Debug.Print "顧客=" & k, "商品リスト=" & Join(dict(k), ", ")
    Next k
End Sub
VB
  • ポイント:
    • 顧客ごとに購入商品をまとめて配列化。
    • ReDim Preserve で配列を拡張。

テンプレ4:分割Dictionaryで集計(カテゴリ別合計)

Sub SplitDict_Aggregate()
    Dim ws As Worksheet: Set ws = Worksheets("Data")
    Dim rg As Range: Set rg = ws.Range("A2:C20") ' A=カテゴリ, B=商品, C=数量
    Dim v As Variant: v = rg.Value

    Dim dictOuter As Object: Set dictOuter = CreateObject("Scripting.Dictionary")
    Dim dictInner As Object
    Dim r As Long, cat As String, item As String

    For r = 1 To UBound(v, 1)
        cat = v(r, 1)
        item = v(r, 2)

        If dictOuter.Exists(cat) Then
            Set dictInner = dictOuter(cat)
        Else
            Set dictInner = CreateObject("Scripting.Dictionary")
            dictOuter(cat) = dictInner
        End If

        If dictInner.Exists(item) Then
            dictInner(item) = dictInner(item) + v(r, 3)
        Else
            dictInner(item) = v(r, 3)
        End If
    Next r

    ' 出力
    Dim k As Variant, j As Variant
    For Each k In dictOuter.Keys
        Debug.Print "カテゴリ=" & k
        For Each j In dictOuter(k).Keys
            Debug.Print "  商品=" & j, "数量=" & dictOuter(k)(j)
        Next j
    Next k
End Sub
VB

例題で練習

'例1:キーごとに配列を格納
Sub Example1()
    SplitDict_Array
End Sub

'例2:キーごとに別Dictionaryを格納
Sub Example2()
    SplitDict_Dict
End Sub

'例3:シートデータを分割Dictionaryに格納
Sub Example3()
    SplitDict_FromSheet
End Sub

'例4:分割Dictionaryで集計
Sub Example4()
    SplitDict_Aggregate
End Sub
VB

初心者向けポイント

  • 分割Dictionaryは「キーごとに複数値」 → 配列や入れ子Dictionaryを活用。
  • 配列なら順序付きリスト → 顧客ごとの購入商品など。
  • 入れ子Dictionaryなら集計に強い → カテゴリ別・商品別の数量管理。
  • シートデータも高速処理 → Rangeを配列に読み込んで分割Dictionaryに格納。
  • 実務で便利 → 顧客別購入履歴、カテゴリ別集計、複数条件でのデータ管理に応用可能。

👉 この「分割Dictionaryテンプレ」を覚えておけば、Excel VBAで 複数値をキーごとにまとめる処理 を柔軟に実現できます。

タイトルとURLをコピーしました