RegressionTests__DictionaryTest.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 18:53:03 +0200
changeset 2327 bf482d49aeaf
parent 2166 a93ab3a63417
child 2343 f639bb06d701
permissions -rw-r--r--
#QUALITY by exept class: RegressionTests::StringTests added: #test82c_expanding

"{ Package: 'stx:goodies/regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#DictionaryTest
	instanceVariableNames:'dictionaryClass'
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression-Collections'
!


!DictionaryTest methodsFor:'initialize / release'!

setUp
    dictionaryClass := Dictionary.
"/    dictionaryClass := SmallDictionary.

    "Created: / 14-09-2018 / 16:38:30 / Stefan Vogel"
! !

!DictionaryTest methodsFor:'testing'!

testAddAll
        "(self run: #testAddAll)"

        | dict1 dict2 |
        dict1 := dictionaryClass new.
        dict1 at: #a put:1 ; at: #b put: 2.
        dict2 := dictionaryClass new.
        dict2 at: #a put: 3 ; at: #c put: 4.
        dict1 addAll: dict2.
        self assert: (dict1 at: #a) = 3.
        self assert: (dict1 at: #b) = 2.
        self assert: (dict1 at: #c) = 4.

    "Modified: / 14-09-2018 / 16:38:54 / Stefan Vogel"
!

testAssociationsSelect

        "(self selector: #testAssociationsSelect) run"

        | answer d|

        d := dictionaryClass new.
        d at: (Array with: #hello with: #world) put: #fooBar.
        d at: Smalltalk put: #'Smalltalk is the key'.
        d at: #Smalltalk put: Smalltalk.

        answer := d associationsSelect:
                [:assoc | (assoc key == #Smalltalk) and: [assoc value == Smalltalk]].
        self should: [answer isKindOf: dictionaryClass].
        self should: [answer size == 1].
        self should: [(answer at: #Smalltalk) == Smalltalk].

        answer := d associationsSelect:
                [:assoc | (assoc key == #NoSuchKey) and: [assoc value == #NoSuchValue]].
        self should: [answer isKindOf: dictionaryClass].
        self should: [answer size == 0]

    "Modified: / 14-09-2018 / 16:39:05 / Stefan Vogel"
!

testComma
        "(self run: #testComma)"

        | dict1 dict2 dict3 |
        dict1 := dictionaryClass new.
        dict1 at: #a put:1 ; at: #b put: 2.
        dict2 := dictionaryClass new.
        dict2 at: #a put: 3 ; at: #c put: 4.
        dict3 := dict1, dict2.
        self assert: (dict3 at: #a) = 3.
        self assert: (dict3 at: #b) = 2.
        self assert: (dict3 at: #c) = 4.

    "Modified: / 14-09-2018 / 16:39:14 / Stefan Vogel"
!

testIncludesAssociation
        "self debug: #testIncludesAssociation"

        | d |
        d := dictionaryClass new
                at: #five put: 5;
                at: #givemefive put: 5;
                at: #six put: 6;
                yourself.

        self assert: (d includesAssociation: (d associationAt: #five)).
        self assert: (d associationAt: #five) key == #five.
        self assert: (d associationAt: #five) value == 5.
        self assert: (d includesAssociation: (#five -> 5)).
        self assert: (d includesAssociation: (#five -> 6)) not.

    "Modified: / 06-12-2016 / 14:19:15 / cg"
    "Modified: / 14-09-2018 / 16:39:21 / Stefan Vogel"
!

testRemoveAllDeclareAll
    "self debug: #testRemoveAllDeclareAll"

    "/ verifies that we can restore a dictionaries original contents
    "/ by making a copy of it, then redeclaring from the copy.
    "/ (needed by the refactorybrowser)
    
    | d copyOfIt |
    
    d := dictionaryClass new
            at: #five put: (5@5);
            at: #givemefive put: (55@55);
            at: #six put: (6@6);
            yourself.

    copyOfIt := d copy.
    d keysAndValuesDo:[:k :v |
        self assert: (copyOfIt at:k) == v.
    ].

    "/ add something
    d at:#seven put:(7@7).

    "/ removeall - redeclare
    d removeAll; declareAllFrom:copyOfIt.

    self assert: (d size = copyOfIt size).
    self assert: (d keys = copyOfIt keys).
    d keysAndValuesDo:[:k :v |
        self assert: (copyOfIt at:k) == v.
    ].

    "Created: / 06-02-2017 / 12:26:22 / cg"
    "Modified: / 14-09-2018 / 16:39:28 / Stefan Vogel"
! !

!DictionaryTest class methodsFor:'documentation'!

version
    ^ '$Header$'
! !