Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
An Array v's A Dictionary
#1
I've just recently come across a Dictionary as an alternative to an Array. Doesn't appear that QB64PE supports Dictionaries. Does anyone who codes in languages which do use Dictionaries find them the same as using an Array or better than an Array or offering a completely different manipulation of data than an Array?
Reply
#2
Dictionary's use a different "index" system, keys are used instead of integers and value(s) are associated with each key eg
a dictionionary of Colors the key is a color name and the value could be RGB values

Like with a regular dictionary the keys are the words and the definitions are the values for each key.

TempodiBasic and I did most recent Dictionary stuff here at this forum, try search with our avatar names and Dictionary.

Too much noise in the searches:
here is some excellent code! Smile
Code: (Select All)
Option _Explicit ' Dictionary 3
' b+ remake of TempodiBasic post 2021-04-06
' ref: https://www.qb64.org/forum/index.php?topic=3786.msg131448#msg131448
' 2021-04-07 add some bells and whistles
' 2023-04-11 add Find for faster actions,  add load and save to file

Type Dictionary
    K As String ' keys all caps for faster searches
    V As String
End Type

ReDim MyDict(1 To 1) As Dictionary ' use ubound of array to tell how many values we have

'                                  This code checks all the stuff Dictionary 2 did
' make some new pairs
Print "Show empty MyDict at start of this demo:"
ShowDict MyDict()
Print "Add a KV pair:"
AddModDictionary MyDict(), "mammals", "Cats"
ShowDict MyDict()
Print "Add a KV pair:"
AddModDictionary MyDict(), "trees", "Oak"
ShowDict MyDict()
Print "Add a KV pair:"
AddModDictionary MyDict(), "fish", "Bass"
ShowDict MyDict()
Print "Swap Dogs for Cats in mammals:"
AddModDictionary MyDict(), "mammals", "Dogs"
ShowDict MyDict()
Print "Check current mammals:"
Print "What is current mammal ? answer: "; GetValue$(MyDict(), "mammals")
Print "Remove mammals:"
RemoveKV MyDict(), "mammals"
ShowDict MyDict()
Print "Bring mammals back with Horses AND Dogs,Cats:"
AddAppendDictionary MyDict(), "Mammals", "Horses"
AddAppendDictionary MyDict(), "mammals", "Cats,Dogs"
ShowDict MyDict()
Print "Remove Cats from mammals:"
RemoveValue MyDict(), "mammals", "Cats"
ShowDict MyDict()
Print "Remove Horses from mammals:"
RemoveValue MyDict(), "mammals", "Horses"
ShowDict MyDict()
Print "Remove Unicorns from mammals:"
RemoveValue MyDict(), "mammals", "Unicorns"
ShowDict MyDict()
Print "And finally wipe out mammals again by removing dogs:"
RemoveValue MyDict(), "mammals", "Dogs"
ShowDict MyDict()

' all above seems to work how bout new subs?
Print "Test Save and Load of the Dictionary:"
SaveDictionary MyDict(), "My Dictionary.txt"
_Delay .25
LoadDictionary MyDict(), "My Dictionary.txt"
ShowDict MyDict()
' good

Sub SaveDictionary (Dict() As Dictionary, pathedFileName$)
    Dim As Long i
    Open pathedFileName$ For Output As #1 ' 2 line format key then value list
    For i = 1 To UBound(Dict)
        Print #1, Dict(i).K
        If _Trim$(Dict(i).V) = "" Then Print #1, " " Else Print #1, _Trim$(Dict(i).V)
    Next
    Close #1
End Sub

Sub LoadDictionary (Dict() As Dictionary, pathedFileName$)
    Dim As Long ub ' will track actual amout of items
    ReDim Dict(1 To 1) As Dictionary
    Dict(1).K = "": Dict(1).V = "" ' sometimes var string UDT's have to be zero'd
    If _FileExists(pathedFileName$) Then
        Open pathedFileName$ For Input As #1
        While Not EOF(1)
            ub = ub + 1
            If ub > UBound(Dict) Then ReDim _Preserve Dict(1 To ub + 1000) As Dictionary
            Line Input #1, Dict(ub).K
            Line Input #1, Dict(ub).V
        Wend
        ReDim _Preserve Dict(1 To ub) As Dictionary
    End If
End Sub

' replace 2 TempodiBasic Functions with 1 Sub, to handle both new and modified values for keys and dynamic Dict() dbl string array.
' Now just take ubound of dict() and have number of pairs it contains
Sub AddModDictionary (Dict() As Dictionary, K$, V$) ' mod with mod Find
    ReDim ub As Long, i As Long, ky$, f As Long, ip As Long
    ub = UBound(Dict)
    ky$ = UCase$(_Trim$(K$)) 'don't change k$ but make case insensitive?
    If ky$ <> "" Then ' bullet proof sub routine K$ must not be empty!
        If ub = 1 And Dict(1).K = "" Then 'our very first pair!
            Dict(1).K = ky$: Dict(1).V = V$: Exit Sub
        Else
            'For i = 1 To ub ' see if we have that name yet
            '    If ky$ = Dict(i).K Then Dict(i).V = V$: Exit Sub ' yes name is registered so change value
            'Next
            f = Find&(Dict(), ky$, ip)
            If f Then
                Dict(f).V = V$
            Else
                'still here? add var name and value to dictionary
                ReDim _Preserve Dict(1 To ub + 1) As Dictionary ' create one slot at a time such that ubound = number or pairs
                For i = ub To ip Step -1
                    Dict(i + 1) = Dict(i)
                Next
                Dict(ip).K = ky$: Dict(ip).V = V$ ' fill it with key and value
            End If
        End If
    End If
End Sub

Function GetValue$ (Dict() As Dictionary, K$) 'mod
    Dim f As Long, ip As Long
    f = Find&(Dict(), K$, ip)
    If f Then GetValue$ = Dict(f).V
End Function

Sub ShowDict (Dict() As Dictionary)
    Dim i As Long
    Print "Dictionary has "; _Trim$(Str$(UBound(Dict))); " items."
    For i = 1 To UBound(Dict)
        Print i, Dict(i).K, Dict(i).V
    Next
    Print
    Print "zzz... press any to continue"
    Sleep
    Print
End Sub

Sub RemoveKV (Dict() As Dictionary, K$) ' mod
    Dim As Long j, f, ip
    f = Find&(Dict(), K$, ip)
    If f Then
        If f <> UBound(Dict) Then
            For j = f + 1 To UBound(Dict)
                Swap Dict(j - 1), Dict(j)
            Next
        End If
        ReDim _Preserve Dict(1 To UBound(Dict) - 1) As Dictionary
    End If
End Sub

' instead or replacing a value with another we will add the new value delimited by a comma
Sub AddAppendDictionary (Dict() As Dictionary, K$, V$) ' mod
    Dim As Long ub, i, f, ip
    Dim ky$
    ub = UBound(Dict)
    ky$ = UCase$(_Trim$(K$)) 'don't change k$ but make case insensitive?
    If ky$ <> "" Then ' bullet proof sub routine K$ must not be empty!
        If ub = 1 And Dict(1).K = "" Then 'our very first pair!
            Dict(1).K = ky$: Dict(1).V = V$: Exit Sub
        Else
            f = Find&(Dict(), ky$, ip)
            If f Then
                Dict(f).V = Dict(f).V + "," + V$
            Else

                ReDim _Preserve Dict(1 To ub + 1) As Dictionary ' create one slot at a time such that ubound = number or pairs
                For i = ub To ip Step -1
                    Dict(i + 1) = Dict(i)
                Next
                Dict(ip).K = ky$: Dict(ip).V = V$ ' fill it with key and value
            End If
        End If
    End If
End Sub

Sub RemoveValue (Dict() As Dictionary, K$, RemoveV$) ' mod
    ReDim As Long ub, j, f, ip
    ReDim ky$, b$
    ub = UBound(Dict)
    ky$ = UCase$(_Trim$(K$)) 'don't change k$ but make case insensitive?
    If ky$ <> "" Then ' bullet proof sub routine K$ must not be empty!
        If ub = 1 And Dict(1).K = "" Then 'our very first pair!
            Exit Sub
        Else
            f = Find&(Dict(), ky$, ip)
            If f Then
                If InStr(Dict(f).V, ",") > 0 Then
                    ReDim t$(1 To 1)
                    Split Dict(f).V, ",", t$()
                    For j = 1 To UBound(t$)
                        If t$(j) <> RemoveV$ Then
                            If b$ = "" Then
                                b$ = t$(j)
                            Else
                                b$ = b$ + "," + t$(j)
                            End If
                        End If
                    Next
                    Dict(f).V = b$
                ElseIf Dict(f).V = RemoveV$ Then
                    Dict(f).V = ""
                End If
            End If
        End If
    End If
End Sub

' 2023-04-11 mod for Dictionary Type and inserting new words
Function Find& (SortedArr() As Dictionary, x$, insertPlace&)
    Dim As Long low, hi, test
    Dim xcap$
    xcap$ = UCase$(x$)
    low = LBound(SortedArr): hi = UBound(SortedArr)
    While low <= hi
        test = Int((low + hi) / 2)
        If SortedArr(hi).K < xcap$ Then insertPlace& = hi + 1 Else insertPlace& = low
        If SortedArr(test).K = xcap$ Then
            Find& = test: Exit Function
        Else
            If SortedArr(test).K <= xcap$ Then low = test + 1 Else hi = test - 1
        End If
    Wend
End Function

' note: I buggered this twice now, FOR base 1 array REDIM MyArray (1 to 1) AS ... the (1 to 1) is not same as (1) which was the Blunder!!!
'notes: REDIM the array(0) to be loaded before calling Split '<<<< IMPORTANT dynamic array and empty, can use any lbound though
'This SUB will take a given N delimited string, and delimiter$ and create an array of N+1 strings using the LBOUND of the given dynamic array to load.
'notes: the loadMeArray() needs to be dynamic string array and will not change the LBOUND of the array it is given.  rev 2019-08-27
Sub Split (SplitMeString As String, delim As String, loadMeArray() As String) ' from Handy library
    Dim curpos As Long, arrpos As Long, LD As Long, dpos As Long 'fix use the Lbound the array already has
    curpos = 1: arrpos = LBound(loadMeArray): LD = Len(delim)
    dpos = InStr(curpos, SplitMeString, delim)
    Do Until dpos = 0
        loadMeArray(arrpos) = Mid$(SplitMeString, curpos, dpos - curpos)
        arrpos = arrpos + 1
        If arrpos > UBound(loadMeArray) Then ReDim _Preserve loadMeArray(LBound(loadMeArray) To UBound(loadMeArray) + 1000) As String
        curpos = dpos + LD
        dpos = InStr(curpos, SplitMeString, delim)
    Loop
    loadMeArray(arrpos) = Mid$(SplitMeString, curpos)
    ReDim _Preserve loadMeArray(LBound(loadMeArray) To arrpos) As String 'get the ubound correct
End Sub
b = b + ...
Reply
#3
(10-07-2024, 07:18 PM)Dimster Wrote: I've just recently come across a Dictionary as an alternative to an Array. Doesn't appear that QB64PE supports Dictionaries. Does anyone who codes in languages which do use Dictionaries find them the same as using an Array or better than an Array or offering a completely different manipulation of data than an Array?
You must have been exploring Python data sets. Smile
New to QB64pe? Visit the QB64 tutorial to get started.
QB64 Tutorial
Reply
#4
(10-07-2024, 07:18 PM)Dimster Wrote: I've just recently come across a Dictionary as an alternative to an Array. Doesn't appear that QB64PE supports Dictionaries. Does anyone who codes in languages which do use Dictionaries find them the same as using an Array or better than an Array or offering a completely different manipulation of data than an Array?
Arrays and dictionary are quite different really, whether you want one or the other depends on how you intend to use it. That said I'd say dictionaries are typically more useful.

The details depend on the particular dictionary implementation, but typically a dictionary (if implemented via a hash table) will offer constant-time lookup, insert, and delete. An array in contrast offers constant-time lookup but a more expensive insert and delete. The disadvantage is that enumerating over all the entries in an dictionary is typically expensive and the entries are not always in a particular order, where-as enumerating over an array is about as fast as it gets.

If speed is not a real concern then you can use a dictionary in place of an array with no real issue. Otherwise, an array is appropriate if the data rarely gets entries added or removed and/or if you often loop over all the entries. A dictionary is better if insertions and removals are very often and you don't typically need to loop over all the entries.

Also note that the implementation backing the dictionary can greatly impact it's actual performance. A hash table is the typical implementation but that's not guaranteed, it could also be a binary search tree or just a sorted list. The latter two have the advantage of being ordered and are typically faster to enumerate, but a hash table will normally offer better performance for lookup/insert/delete. For the binary search tree, it's not significantly different, but a sorted list is basically just the same performance as an array.

For QB64-PE support, it's not built-in but you could create a dictionary yourself. I typically prefer the array of linked-lists approach as it's pretty easy to make (performance is good assuming you size the underlying array appropriately). I'm not so sure how easy it would be to make in QB64-PE though. You could also skip the linked-lists and just use the array with an approach to handle hash collisions.
Reply
#5
Hi Terry, was actually on the internet searching multiple examples of arrays and Dictionary was commented as being in C++

You know b+, when I first read the word Dictionary and did a little read up on it, it seemed to be just a 2 dimensional array exactly like you have laid out in your code. It would appear, as DSMAN has described its' inner workings, has a superior "constant-time lookup, insert and delete. I'm imagining this would suggest a 2 dimensional array would have a serial lookup (ie if I want to find an entry it would go through the stored data one item at a time until it finds the search item) whereas the same Dictionary is more like a random access (ie it goes directly to the search item)

I like the order I get with a 2 dim array to build a data base but seems the Dictionary approach would be great to maintain a data base. I haven't worked with linked lists or hash tables (old dog new trickisim) but I have seen examples of them on this forum (or maybe the old forum).

Thanks for the info guys
Reply
#6
(10-08-2024, 10:26 AM)Dimster Wrote: I'm imagining this would suggest a 2 dimensional array would have a serial lookup (ie if I want to find an entry it would go through the stored data one item at a time until it finds the search item) whereas the same Dictionary is more like a random access (ie it goes directly to the search item)
I probably confused you slightly here, arrays do have constant-time lookup. When you do `array(5)`, the location of entry `5` is calculated directly, so it's quite fast (a bit faster than a dictionary).

Insertions and removals are the big deal, if you have a `ReDim array(10)` and you need to add an 11th entry, you can do a `ReDim array(11)` but behind the scenes that will involve copying the entire contents of the array into a new memory location. If you then wanted to insert your new entry at entry 4 instead of at the end, you'll need to copy the existing entries 4 to 10 into spots 5 to 11 so that entry 4 is now unused. If you go the other way and want to remove entry 4, you have to copy entries 5 to 11 into spots 4 to 10 so that there isn't a hole at entry 5. There are ways to work around some of these issues, but overall there's a limit to how much you can do because of how arrays are implemented, they don't lend themselves to being cheaply resized.

A dictionary doesn't have those problems. You can do a theoretical `DictAdd 5, "bar"` and if entry 5 didn't already exist it can allocate space for it without needing to move/copy most of the data already in the dictionary. Same with a `DictRemove 5`, the removal doesn't involve copying the entire contents of the dictionary.

I might try creating a simple dictionary implementation later, looking at the internals might make the advantages/disadvantages a bit clearer. I do see @bplus's implementation but it appears to be based on a sorted list which means its performance is more similar to a regular array.
Reply
#7
Thanks DS, that does make it a lot more clearer to me.
Reply
#8
Oh Ds...another thought just crossed my mind (dangerous I know)

To ReDim a 2 dimensional array ionly works on the 1st index, so ReDim MyArray(1 to x, 1 to 350) is doable whereas ReDim MyArray (1 to 350, 1 to x) doesn't work. Does the use of Dictionary solve this reDimming of multiple dimensional arrays?
Reply
#9
(10-08-2024, 02:46 PM)Dimster Wrote: Oh Ds...another thought just crossed my mind (dangerous I know)

To ReDim a 2 dimensional array ionly works on the 1st index, so ReDim MyArray(1 to x, 1 to 350) is doable whereas ReDim MyArray (1 to 350, 1 to x) doesn't work. Does the use of Dictionary solve this reDimming of multiple dimensional arrays?
Maybe this will help you understand how Redim works. - Neither the type nor the dimension of an array can/may be changed.
There was already a long discussion about this here somewhere.  Rolleyes

PS: Redim only works with dynamic arrays!

Code: (Select All)

'Zweidimensionales Feld mit Redim neu dimensionieren - 29. Dez. 2022

$Console:Only
Option _Explicit

Option Base 1

Dim As Integer neuDimensionZeile, neuDimensionSpalte
Dim As Integer zeilenDim, spaltenDim
Dim As Integer a, b, i, j, y, z

Locate 2, 2
Input "Feldimension Zeilen  : ", zeilenDim
Locate 3, 2
Input "Felddimension Spalten: ", spaltenDim

'Feld mit Vorgaben initialisieren
Dim As Integer zweiDimfeld(zeilenDim, spaltenDim)

Locate CsrLin + 2, 2
z = 1
For i = 1 To zeilenDim
  For j = 1 To spaltenDim
    zweiDimfeld(i, j) = z
    Print Using "## "; zweiDimfeld(i, j),
    z = z + 1
  Next
  Print: Locate , 2
Next

'Vor Neudimensionierung Speicher freigeben. Ist bei Anwendung
'von REDIM nicht noetig, da dieser ERASE + DIM zusammenfasst - S.188
'Erase zweiDimfeld

'Feld neu dimensionieren
Locate CsrLin + 2, 2
Input "Neue Feldimension Zeile : ", neuDimensionZeile
Locate CsrLin + 0, 2
Input "Neue Feldimension Spalte: ", neuDimensionSpalte

ReDim zweiDimfeld(neuDimensionZeile, neuDimensionSpalte)

Locate CsrLin + 2, 2
y = 1
For a = 1 To neuDimensionZeile
  For b = 1 To neuDimensionSpalte
    zweiDimfeld(a, b) = y
    Print Using "## "; zweiDimfeld(a, b),
    y = y + 1
  Next
  Print: Locate , 2
Next

Locate CsrLin + 3, 2

End

[Image: Array-neu-dimensionieren08-10-2024.jpg]
Reply
#10
(10-08-2024, 02:46 PM)Dimster Wrote: Oh Ds...another thought just crossed my mind (dangerous I know)

To ReDim a 2 dimensional array ionly works on the 1st index, so ReDim MyArray(1 to x, 1 to 350) is doable whereas ReDim MyArray (1 to 350, 1 to x) doesn't work. Does the use of Dictionary solve this reDimming of multiple dimensional arrays?

A 2D array is not needed. You could use 2 - 1D arrays, one for Keys and one for Values and associate them by using the same index number. But this seems perfect place to use
Type Dictionary
as String Key, Value
End Type

if like what's going on then use advanced linked lists or hash table for speed.

Update: BTW KP correct about needing to use Dynamic arrays. Starting them with ReDim instead of Dim is best.
b = b + ...
Reply




Users browsing this thread: 5 Guest(s)