Skip to content

Commit

Permalink
Merge pull request #15 from VBA-tools/indexing
Browse files Browse the repository at this point in the history
Fix indexing for keys and items
  • Loading branch information
timhall committed Jan 21, 2016
2 parents 5b4908c + ab92556 commit 0213d98
Show file tree
Hide file tree
Showing 2 changed files with 56 additions and 18 deletions.
20 changes: 12 additions & 8 deletions Dictionary.cls
Expand Up @@ -274,9 +274,10 @@ Private Sub dict_AddKeyValue(dict_Key As Variant, dict_Value As Variant, Optiona
Dim dict_FormattedKey As String
dict_FormattedKey = dict_GetFormattedKey(dict_Key)

If dict_Index > 0 And dict_Index <= dict_pKeyValues.Count Then
If dict_Index >= 0 And dict_Index < dict_pKeyValues.Count Then
' Shift keys/items after + including index into empty last slot
Dim dict_i As Long
For dict_i = UBound(dict_pKeys) To dict_Index Step -1
For dict_i = UBound(dict_pKeys) To dict_Index + 1 Step -1
dict_pKeys(dict_i) = dict_pKeys(dict_i - 1)
If VBA.IsObject(dict_pItems(dict_i - 1)) Then
Set dict_pItems(dict_i) = dict_pItems(dict_i - 1)
Expand All @@ -285,15 +286,18 @@ Private Sub dict_AddKeyValue(dict_Key As Variant, dict_Value As Variant, Optiona
End If
Next dict_i

dict_pKeys(dict_Index - 1) = dict_Key
' Add key/item at index
dict_pKeys(dict_Index) = dict_Key
If VBA.IsObject(dict_Value) Then
Set dict_pItems(dict_Index - 1) = dict_Value
Set dict_pItems(dict_Index) = dict_Value
Else
dict_pItems(dict_Index - 1) = dict_Value
dict_pItems(dict_Index) = dict_Value
End If

dict_pKeyValues.Add Array(dict_FormattedKey, dict_Key, dict_Value), dict_FormattedKey, Before:=dict_Index
' Add key-value at proper index
dict_pKeyValues.Add Array(dict_FormattedKey, dict_Key, dict_Value), dict_FormattedKey, Before:=dict_Index + 1
Else
' Add key-value as last item
If VBA.IsObject(dict_Key) Then
Set dict_pKeys(UBound(dict_pKeys)) = dict_Key
Else
Expand Down Expand Up @@ -326,11 +330,10 @@ Private Sub dict_RemoveKeyValue(dict_KeyValue As Variant, Optional ByVal dict_In
Dim dict_i As Long
If dict_Index = -1 Then
dict_Index = dict_GetKeyIndex(dict_KeyValue(1))
Else
dict_Index = dict_Index - 1
End If

If dict_Index >= 0 And dict_Index <= UBound(dict_pKeys) Then
' Shift keys/items after index down
For dict_i = dict_Index To UBound(dict_pKeys) - 1
dict_pKeys(dict_i) = dict_pKeys(dict_i + 1)

Expand All @@ -341,6 +344,7 @@ Private Sub dict_RemoveKeyValue(dict_KeyValue As Variant, Optional ByVal dict_In
End If
Next dict_i

' Resize keys/items to remove empty slot
If UBound(dict_pKeys) = 0 Then
Erase dict_pKeys
Erase dict_pItems
Expand Down
54 changes: 44 additions & 10 deletions specs/Specs.bas
Expand Up @@ -101,27 +101,61 @@ Public Function Specs() As SpecSuite
.Expect(Dict("D")).ToBeEmpty
End With

With Specs.It("should let/set item by key")
With Specs.It("should let item by key")
Set Dict = CreateDictionary(UseNative)

Dict.Add "A", 123
Dict("A") = 456

Dict.Add "B", 3.14
Dict.Add "C", "ABC"

Dict.Item("D") = True
Dict("C") = "DEF"
' Let + New
Dict("D") = True

' Let + Replace
Dict("A") = 456
Dict("B") = 3.14159

' Should have correct values
.Expect(Dict("A")).ToEqual 456
.Expect(Dict("B")).ToEqual 3.14159
.Expect(Dict("C")).ToEqual "ABC"
.Expect(Dict("D")).ToEqual True

Set Dict.Item("B") = CreateDictionary(UseNative)
Dict.Item("B").Add "key", "B"
' Should have correct order
.Expect(Dict.Keys()(0)).ToEqual "A"
.Expect(Dict.Keys()(1)).ToEqual "B"
.Expect(Dict.Keys()(2)).ToEqual "C"
.Expect(Dict.Keys()(3)).ToEqual "D"
End With

With Specs.It("should set item by key")
Set Dict = CreateDictionary(UseNative)

Dict.Add "A", 123
Dict.Add "B", 3.14
Dict.Add "C", "ABC"

' Set + New
Set Dict("D") = CreateDictionary(UseNative)
Dict("D").Add "key", "D"

' Set + Replace
Set Dict("A") = CreateDictionary(UseNative)
Dict("A").Add "key", "A"

Set Dict("B") = CreateDictionary(UseNative)
Dict("B").Add "key", "B"

' Should have correct values
.Expect(Dict.Item("A")("key")).ToEqual "A"
.Expect(Dict.Item("B")("key")).ToEqual "B"
.Expect(Dict.Item("C")).ToEqual "DEF"
.Expect(Dict.Item("D")).ToEqual True
.Expect(Dict.Item("C")).ToEqual "ABC"
.Expect(Dict.Item("D")("key")).ToEqual "D"

' Should have correct order
.Expect(Dict.Keys()(0)).ToEqual "A"
.Expect(Dict.Keys()(1)).ToEqual "B"
.Expect(Dict.Keys()(2)).ToEqual "C"
.Expect(Dict.Keys()(3)).ToEqual "D"
End With

With Specs.It("should change key")
Expand Down

0 comments on commit 0213d98

Please sign in to comment.