diff --git a/src/Collections-Tests/SortedCollectionTest.class.st b/src/Collections-Tests/SortedCollectionTest.class.st index 7e7b68dec0c..f6799e5ad28 100644 --- a/src/Collections-Tests/SortedCollectionTest.class.st +++ b/src/Collections-Tests/SortedCollectionTest.class.st @@ -31,25 +31,29 @@ Class { { #category : #requirements } SortedCollectionTest >> accessCollection [ -"Return a collection of size 5" + "Return a collection of size 5" + ^accessCollection ] { #category : #requirements } SortedCollectionTest >> anotherElementNotIn [ -" return an element different of 'elementNotIn' not included in 'nonEmpty' " + "Return an element different of 'elementNotIn' not included in 'nonEmpty' " + ^666 ] { #category : #requirements } SortedCollectionTest >> anotherElementOrAssociationIn [ - " return an element (or an association for Dictionary ) present in 'collection' " + "Return an element (or an association for Dictionary ) present in 'collection' " + ^ self collection anyOne ] { #category : #requirements } SortedCollectionTest >> anotherElementOrAssociationNotIn [ - " return an element (or an association for Dictionary )not present in 'collection' " + "Return an element (or an association for Dictionary )not present in 'collection' " + ^ elementNoteIn ] @@ -61,186 +65,211 @@ SortedCollectionTest >> collection [ { #category : #requirements } SortedCollectionTest >> collectionClass [ -" return the class to be used to create instances of the class tested" + "Return the class to be used to create instances of the class tested" + ^ SortedCollection ] { #category : #requirements } SortedCollectionTest >> collectionMoreThan1NoDuplicates [ - " return a collection of size 5 without equal elements" + "Return a collection of size 5 without equal elements" + ^ withoutEqualElements ] { #category : #requirements } SortedCollectionTest >> collectionMoreThan5Elements [ -" return a collection including at least 5 elements" + "Return a collection including at least 5 elements" ^ nonEmpty5Elements ] { #category : #requirements } SortedCollectionTest >> collectionNotIncluded [ -" return a collection for wich each element is not included in 'nonEmpty' " + "Return a collection for wich each element is not included in 'nonEmpty' " + ^ collectionNotIncluded ] { #category : #requirements } SortedCollectionTest >> collectionOfFloat [ -" return a collection only includiing Float elements " + "Return a collection only includiing Float elements " + ^ collectionOfFloat ] { #category : #requirements } SortedCollectionTest >> collectionOfSize5 [ -" return a collection of size 5" -^ accessCollection + "Return a collection of size 5" + + ^ accessCollection ] { #category : #requirements } SortedCollectionTest >> collectionWith1TimeSubcollection [ -" return a collection including 'oldSubCollection' only one time " + "Return a collection including 'oldSubCollection' only one time." + ^ (SortedCollection new add: elementNoteIn ; yourself) , self oldSubCollection ] { #category : #requirements } SortedCollectionTest >> collectionWith2TimeSubcollection [ -" return a collection including 'oldSubCollection' two or many time " + "Return a collection including 'oldSubCollection' two or many time." + ^ (SortedCollection new add: elementNoteIn ; yourself) , self oldSubCollection , self oldSubCollection ] { #category : #requirements } SortedCollectionTest >> collectionWith5Elements [ -" return a collection of size 5 including 5 elements" -^ accessCollection + "Return a collection of size 5 including 5 elements" + + ^ accessCollection ] { #category : #requirements } SortedCollectionTest >> collectionWithCopyNonIdentical [ - " return a collection that include elements for which 'copy' return a different object (this is not the case of SmallInteger)" + "Return a collection that include elements for which 'copy' return a different object (this is not the case of SmallInteger)" + ^ collectionOfFloat ] { #category : #requirements } SortedCollectionTest >> collectionWithElement [ "Returns a collection that already includes what is returned by #element." + ^ SortedCollection new add: self element ; add: 5 ; add: 2; yourself. ] { #category : #requirements } SortedCollectionTest >> collectionWithElementsToRemove [ -" return a collection of elements included in 'nonEmpty' " + "Return a collection of elements included in 'nonEmpty'." + ^ collectionIncluded ] { #category : #requirements } SortedCollectionTest >> collectionWithEqualElements [ -" return a collecition including atLeast two elements equal" + "Return a collection including atLeast two elements equal." -^ collectionOfFloatWithDuplicate + ^ collectionOfFloatWithDuplicate ] { #category : #requirements } SortedCollectionTest >> collectionWithNonIdentitySameAtEndAndBegining [ - " return a collection with elements at end and begining equals only with classic equality (they are not the same object). + "Return a collection with elements at end and begining equals only with classic equality (they are not the same object). (others elements of the collection are not equal to those elements)" + ^ floatCollectionSameEndAndBegining ] { #category : #requirements } SortedCollectionTest >> collectionWithSameAtEndAndBegining [ -" return a collection with elements at end and begining equals . -(others elements of the collection are not equal to those elements)" + "Return a collection with elements at end and begining equals (others elements of the collection are not equal to those elements)" + ^ floatCollectionSameEndAndBegining ] { #category : #requirements } SortedCollectionTest >> collectionWithSortableElements [ -" return a collection elements that can be sorte ( understanding message ' < ' or ' > ')" + "Return a collection elements that can be sorted ( understanding message ' < ' or ' > ')" + ^ collectionOfFloat ] { #category : #requirements } SortedCollectionTest >> collectionWithoutEqualElements [ - -" return a collection not including equal elements " + "Return a collection not including equal elements." + ^withoutEqualElements ] { #category : #requirements } SortedCollectionTest >> collectionWithoutNilElements [ -" return a collection that doesn't includes a nil element and that doesn't includes equal elements'" + "Return a collection that doesn't includes a nil element and that doesn't includes equal elements'" + ^ collectionWithoutNil ] { #category : #requirements } SortedCollectionTest >> element [ "Returns an object that can be added to the collection returned by #collection." + ^ 88 ] { #category : #requirements } SortedCollectionTest >> elementInCollectionOfFloat [ -" return an element included in 'collectionOfFloat' " + "Return an element included in 'collectionOfFloat'" + ^ collectionOfFloat anyOne ] { #category : #requirements } SortedCollectionTest >> elementInForElementAccessing [ -" return an element inculded in 'accessCollection '" + "Return an element inculded in 'accessCollection '" + ^ self accessCollection anyOne ] { #category : #requirements } SortedCollectionTest >> elementInForIncludesTest [ -" return an element included in nonEmpty " + "Return an element included in nonEmpty." + ^ nonEmpty anyOne ] { #category : #requirements } SortedCollectionTest >> elementInForIndexAccessing [ -" return an element included in 'accessCollection' " + "Return an element included in 'accessCollection' " + ^ self collectionMoreThan1NoDuplicates anyOne ] { #category : #requirements } SortedCollectionTest >> elementNotIn [ -"return an element not included in 'nonEmpty' " + "Return an element not included in 'nonEmpty' " ^ elementNoteIn ] { #category : #requirements } SortedCollectionTest >> elementNotInForElementAccessing [ -" return an element not included in 'accessCollection' " + "Return an element not included in 'accessCollection' " + ^ elementNoteIn ] { #category : #requirements } SortedCollectionTest >> elementNotInForIndexAccessing [ -" return an element not included in 'accessCollection' " + "Return an element not included in 'accessCollection' " + ^ elementNoteIn ] { #category : #requirements } SortedCollectionTest >> elementNotInForOccurrences [ + ^ 666 ] { #category : #requirements } SortedCollectionTest >> elementToAdd [ -" return an element of type 'nonEmpy' elements'type'" + "Return an element of type 'nonEmpy' elements'type'" + ^ 5 ] { #category : #requirements } SortedCollectionTest >> elementTwiceInForOccurrences [ -" return an element included exactly two time in # collectionWithEqualElements" -^ duplicateFloat + "Return an element included exactly two time in # collectionWithEqualElements." + + ^ duplicateFloat ] { #category : #requirements } SortedCollectionTest >> elementsCopyNonIdenticalWithoutEqualElements [ - " return a collection that does niot incllude equal elements ( classic equality )" + "Return a collection that does niot incllude equal elements ( classic equality )" + ^ collectionOfFloat ] @@ -252,51 +281,57 @@ SortedCollectionTest >> empty [ { #category : #requirements } SortedCollectionTest >> expectedSizeAfterReject [ - ^1 + + ^ 1 ] { #category : #requirements } SortedCollectionTest >> floatCollectionWithSameAtEndAndBegining [ -" return a collection with elements at end and begining equals only with classic equality (they are not the same object). + "Return a collection with elements at end and begining equals only with classic equality (they are not the same object). (others elements of the collection are not equal to those elements)" + ^ floatCollectionSameEndAndBegining ] { #category : #requirements } SortedCollectionTest >> indexInForCollectionWithoutDuplicates [ -" return an index between 'collectionWithoutEqualsElements' bounds" + "Return an index between 'collectionWithoutEqualsElements' bounds." + ^ 2 ] { #category : #requirements } SortedCollectionTest >> indexInNonEmpty [ -" return an index between bounds of 'nonEmpty' " + "Return an index between bounds of 'nonEmpty'." ^ 2 ] { #category : #requirements } SortedCollectionTest >> integerCollection [ -" return a collection only including SmallInteger elements" + "Return a collection only including SmallInteger elements." + ^ accessCollection ] { #category : #requirements } SortedCollectionTest >> integerCollectionWithoutEqualElements [ -" return a collection of integer without equal elements" + "Return a collection of integer without equal elements." + ^ withoutEqualElements ] { #category : #requirements } SortedCollectionTest >> moreThan3Elements [ - " return a collection including atLeast 3 elements" + "Return a collection including atLeast 3 elements." + ^ accessCollection ] { #category : #requirements } SortedCollectionTest >> moreThan4Elements [ - -" return a collection including at leat 4 elements" + "Return a collection including at leat 4 elements" + ^ accessCollection ] @@ -308,39 +343,48 @@ SortedCollectionTest >> nonEmpty [ { #category : #requirements } SortedCollectionTest >> nonEmpty1Element [ -" return a collection of size 1 including one element" + "Return a collection of size 1 including one element." + ^ nonEmpty1Element ] { #category : #requirements } SortedCollectionTest >> nonEmptyMoreThan1Element [ -" return a collection of integer with more than one element" - ^withoutEqualElements - . + "Return a collection of integer with more than one element" + + ^withoutEqualElements ] { #category : #requirements } SortedCollectionTest >> nonEmptyWithoutEqualElements [ -" return a collection without equal elements " + "Return a collection without equal elements." + ^ withoutEqualElements ] { #category : #requirements } SortedCollectionTest >> oldSubCollection [ -" return a subCollection included in collectionWith1TimeSubcollection . -ex : subCollection := #( 2 3 4) and collectionWith1TimeSubcollection := #(1 2 3 4 5)" + "Return a subCollection included in collectionWith1TimeSubcollection. + Example: subCollection := #( 2 3 4) and collectionWith1TimeSubcollection := #(1 2 3 4 5)" + ^ oldSubcollection ] { #category : #requirements } SortedCollectionTest >> otherCollection [ "Returns a collection that does not include what is returned by #element." - ^ SortedCollection new add: 7 ; add: 5 ; add: 2; yourself. + + ^ SortedCollection new + add: 7; + add: 5; + add: 2; + yourself ] { #category : #requirements } SortedCollectionTest >> replacementCollection [ -" return a collection that will be used to replace 'oldSubcollection' in ' collectionWith1TimeSubcollection' " + "Return a collection that will be used to replace 'oldSubcollection' in ' collectionWith1TimeSubcollection' " + ^ collectionWith4Elements ] @@ -352,6 +396,7 @@ SortedCollectionTest >> result [ { #category : #running } SortedCollectionTest >> setUp [ + super setUp. nonEmpty := SortedCollection new. elementExistsTwice := 12332312321. @@ -386,6 +431,7 @@ SortedCollectionTest >> setUp [ { #category : #requirements } SortedCollectionTest >> sizeCollection [ + ^ collectionWith4Elements ] @@ -397,13 +443,14 @@ SortedCollectionTest >> speciesClass [ { #category : #requirements } SortedCollectionTest >> subCollectionNotIn [ -" return a collection for which at least one element is not included in 'accessCollection' " + "Return a collection for which at least one element is not included in 'accessCollection'." + ^ SortedCollection new add: elementNoteIn ; add: elementNoteIn ; yourself. ] { #category : #'tests - fixture' } SortedCollectionTest >> test0FixtureTConvertAsSetForMultiplinessTest [ - "a collection ofFloat with equal elements:" + "A collection ofFloat with equal elements:" | res | self withEqualElements. @@ -433,7 +480,7 @@ SortedCollectionTest >> testAdd [ collection add: 6. self assert: (collection at: 5) equals: 5. self assert: collection size equals: 10. - collection add: 3. + collection add: 3 ] @@ -444,10 +491,10 @@ SortedCollectionTest >> testAddAll [ sorted2 := SortedCollection new. sorted2 add: 'brochet'; - add:'truitelle'. + add: 'truitelle'. sorted := SortedCollection new. sorted addAll: sorted2. - self assert: (sorted hasEqualElements: sorted2). + self assert: (sorted hasEqualElements: sorted2) ] @@ -499,7 +546,7 @@ SortedCollectionTest >> testCopy [ self assert: (copySorted hasEqualElements: aSortedCollection). self assert: copySorted species equals: aSortedCollection species. self assert: copySorted sortBlock equals: aSortedCollection sortBlock. - self assert: copySorted first = 'brochet' + self assert: copySorted first equals: 'brochet' ] { #category : #'tests - basic' } @@ -507,7 +554,7 @@ SortedCollectionTest >> testCreation [ | collection | collection := #(10 9 3 6 1 8 7 5 4 2) asSortedCollection. - self assert: collection equals: (1 to: 10) asSortedCollection. + self assert: collection equals: (1 to: 10) asSortedCollection ] @@ -517,7 +564,7 @@ SortedCollectionTest >> testDo2 [ | res | res := self speciesClass sortBlock: [:a :b | a name < b name].. self collection do: [:each | res add: each class]. - self assert: res asArray = self result asArray. + self assert: res asArray equals: self result asArray ] @@ -526,20 +573,23 @@ SortedCollectionTest >> testEquals [ |aSortedCollection| aSortedCollection := SortedCollection new. - aSortedCollection add: 'truite'; add: 'brochet'. - self assert: aSortedCollection copy equals: aSortedCollection. + aSortedCollection + add: 'truite'; + add: 'brochet'. + self assert: aSortedCollection copy equals: aSortedCollection ] { #category : #'tests - enumerating' } SortedCollectionTest >> testFlatCollect [ - self assert: (#(1 2) asSortedCollection flatCollect: [ :x | { x } ]) = #(1 2) asOrderedCollection + + self assert: (#(1 2) asSortedCollection flatCollect: [ :x | { x } ]) equals: #(1 2) asOrderedCollection ] { #category : #'tests - includes' } SortedCollectionTest >> testIdentityIncludes [ - " test the comportement in presence of elements 'includes' but not 'identityIncludes' " + "Test the comportement in presence of elements 'includes' but not 'identityIncludes'." - " can not be used by collections that can't include elements for wich copy doesn't return another instance " + "Can not be used by collections that can't include elements for wich copy doesn't return another instance " | collection element | self collectionWithCopyNonIdentical. @@ -554,20 +604,21 @@ SortedCollectionTest >> testIdentityIndexOf [ | collection element | collection := self collectionMoreThan1NoDuplicates. element := collection first. - self assert: (collection identityIndexOf: element) = (collection indexOf: element) + self assert: (collection identityIndexOf: element) equals: (collection indexOf: element) ] { #category : #'tests - index access' } SortedCollectionTest >> testIdentityIndexOfIAbsent [ + | collection element | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection identityIndexOf: element - ifAbsent: [ 0 ]) = 1. + ifAbsent: [ 0 ]) equals: 1. self assert: (collection identityIndexOf: self elementNotInForIndexAccessing - ifAbsent: [ 55 ]) = 55 + ifAbsent: [ 55 ]) equals: 55 ] { #category : #'tests - index access' } @@ -580,7 +631,7 @@ SortedCollectionTest >> testIndexOf [ [ :each | each = self elementInForIndexAccessing ifTrue: [ index := tmp ]. tmp := tmp - 1 ]. - self assert: (collection indexOf: self elementInForIndexAccessing) = index + self assert: (collection indexOf: self elementInForIndexAccessing) equals: index ] { #category : #'tests - index access' } @@ -590,10 +641,10 @@ SortedCollectionTest >> testIndexOfIfAbsent [ collection := self collectionMoreThan1NoDuplicates. self assert: (collection indexOf: collection first - ifAbsent: [ 33 ]) = 1. + ifAbsent: [ 33 ]) equals: 1. self assert: (collection indexOf: self elementNotInForIndexAccessing - ifAbsent: [ 33 ]) = 33 + ifAbsent: [ 33 ]) equals: 33 ] { #category : #'tests - index access' } @@ -605,15 +656,15 @@ SortedCollectionTest >> testIndexOfStartingAt [ self assert: (collection indexOf: element startingAt: 2 - ifAbsent: [ 99 ]) = 99. + ifAbsent: [ 99 ]) equals: 99. self assert: (collection indexOf: element startingAt: 1 - ifAbsent: [ 99 ]) = 1. + ifAbsent: [ 99 ]) equals: 1. self assert: (collection indexOf: self elementNotInForIndexAccessing startingAt: 1 - ifAbsent: [ 99 ]) = 99 + ifAbsent: [ 99 ]) equals: 99 ] { #category : #'tests - index access' } @@ -658,8 +709,8 @@ SortedCollectionTest >> testLastIndexOf [ | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. - self assert: (collection lastIndexOf: element) = 1. - self assert: (collection lastIndexOf: self elementNotInForIndexAccessing) = 0 + self assert: (collection lastIndexOf: element) equals: 1. + self assert: (collection lastIndexOf: self elementNotInForIndexAccessing) equals: 0 ] { #category : #'tests - index access' } @@ -671,15 +722,15 @@ SortedCollectionTest >> testLastIndexOfStartingAt [ self assert: (collection lastIndexOf: element startingAt: collection size - ifAbsent: [ 99 ]) = collection size. + ifAbsent: [ 99 ]) equals: collection size. self assert: (collection lastIndexOf: element startingAt: collection size - 1 - ifAbsent: [ 99 ]) = 99. + ifAbsent: [ 99 ]) equals: 99. self assert: (collection lastIndexOf: self elementNotInForIndexAccessing startingAt: collection size - ifAbsent: [ 99 ]) = 99 + ifAbsent: [ 99 ]) equals: 99 ] { #category : #'tests - basic' } @@ -695,7 +746,7 @@ SortedCollectionTest >> testMedian [ add: 'porcinet'; add: 'carpe'. - self assert: aSortedCollection median equals: 'porcinet'. + self assert: aSortedCollection median equals: 'porcinet' ] @@ -710,11 +761,11 @@ SortedCollectionTest >> testRemoveAll [ c1 removeAll. - self assert: c1 size = 0. + self assert: c1 size equals: 0. self assert: c2 size = s2 description: 'the copy has not been modified'. c1 add: 13; add: 14. - self assert: (c1 first = 14 and: [c1 second = 13]) description: 'the sortBlock has been preserved'. + self assert: (c1 first = 14 and: [c1 second = 13]) description: 'the sortBlock has been preserved' ] { #category : #'tests - basic' } @@ -771,23 +822,24 @@ SortedCollectionTest >> testSpeciesLooseSortBlock [ reverseOrder addAll: numbers. "The elements are inverted" - self assert: (reverseOrder asArray = #(5 4 3 2 1)). + self assert: reverseOrder asArray equals: #(5 4 3 2 1). "Copy the first 3 elements" firstThree := reverseOrder copyFrom: 1 to: 3. "It appears to work" - self assert: (firstThree asArray = #(5 4 3)). + self assert: firstThree asArray equals: #(5 4 3). "but we have lost the sort block" firstThree add: 1. " firstThree is now #(1 5 4 3)! " - self assert: firstThree asArray = #(5 4 3 1) "fails" + self assert: firstThree asArray equals: #(5 4 3 1) "fails" ] { #category : #requirements } SortedCollectionTest >> withEqualElements [ - " return a collection of float including equal elements (classic equality)" + "Return a collection of float including equal elements (classic equality)." + ^ collectionOfFloatWithDuplicate ] diff --git a/src/Collections-Tests/TAddTest.trait.st b/src/Collections-Tests/TAddTest.trait.st index 4cae3efb82f..45be0fba662 100644 --- a/src/Collections-Tests/TAddTest.trait.st +++ b/src/Collections-Tests/TAddTest.trait.st @@ -26,6 +26,7 @@ TAddTest >> otherCollection [ { #category : #'tests - fixture' } TAddTest >> test0FixtureRequirementsOfTAddTest [ + self collectionWithElement. self otherCollection. self element. @@ -36,7 +37,7 @@ TAddTest >> test0FixtureRequirementsOfTAddTest [ { #category : #'tests - adding' } TAddTest >> testTAdd [ | added collection | - collection :=self otherCollection . + collection := self otherCollection. added := collection add: self element. self assert: added == self element. "test for identiy because #add: has not reason to copy its parameter." @@ -48,10 +49,11 @@ TAddTest >> testTAdd [ { #category : #'tests - adding' } TAddTest >> testTAddAll [ + | added collection toBeAdded | - collection := self collectionWithElement . - toBeAdded := self otherCollection . - added := collection addAll: toBeAdded . + collection := self collectionWithElement. + toBeAdded := self otherCollection. + added := collection addAll: toBeAdded. self assert: added == toBeAdded . "test for identiy because #addAll: has not reason to copy its parameter." self assert: (collection includesAll: toBeAdded ) ] @@ -60,70 +62,72 @@ TAddTest >> testTAddAll [ TAddTest >> testTAddIfNotPresentWithElementAlreadyIn [ | added oldSize collection anElement | - collection := self collectionWithElement . + collection := self collectionWithElement. oldSize := collection size. - anElement := self element . - self assert: (collection includes: anElement ). + anElement := self element. + self assert: (collection includes: anElement). - added := collection addIfNotPresent: anElement . + added := collection addIfNotPresent: anElement. self assert: added == anElement . "test for identiy because #add: has not reason to copy its parameter." - self assert: collection size = oldSize + self assert: collection size equals: oldSize ] { #category : #'tests - adding' } TAddTest >> testTAddIfNotPresentWithNewElement [ | added oldSize collection elem | - collection := self otherCollection . - oldSize := collection size. - elem := self element . - self deny: (collection includes: elem ). + collection := self otherCollection. + oldSize := collection size. + elem := self element. + self deny: (collection includes: elem ). added := collection addIfNotPresent: elem . self assert: added == elem . "test for identiy because #add: has not reason to copy its parameter." - self assert: (collection size = (oldSize + 1)). + self assert: collection size equals: (oldSize + 1). ] { #category : #'tests - adding' } TAddTest >> testTAddTwice [ + | added oldSize collection anElement | - collection := self collectionWithElement . - anElement := self element . - oldSize := collection size. + collection := self collectionWithElement. + anElement := self element. + oldSize := collection size. added := collection - add: anElement ; - add: anElement . - self assert: added == anElement . "test for identiy because #add: has not reason to copy its parameter." - self assert: (collection includes: anElement ). - self assert: collection size = (oldSize + 2) + add: anElement; + add: anElement. + self assert: added == anElement. "test for identiy because #add: has not reason to copy its parameter." + self assert: (collection includes: anElement). + self assert: collection size equals: (oldSize + 2) ] { #category : #'tests - adding' } TAddTest >> testTAddWithOccurences [ | added oldSize collection anElement | - collection := self collectionWithElement . - anElement := self element . - oldSize := collection size. - added := collection add: anElement withOccurrences: 5. + collection := self collectionWithElement. + anElement := self element. + oldSize := collection size. + added := collection add: anElement withOccurrences: 5. self assert: added == anElement. "test for identiy because #add: has not reason to copy its parameter." - self assert: (collection includes: anElement). - self assert: collection size = (oldSize + 5) + self assert: (collection includes: anElement). + self assert: collection size equals: (oldSize + 5) ] { #category : #'tests - adding' } TAddTest >> testTWrite [ + | added collection elem | - collection := self otherCollection . - elem := self element . - added := collection write: elem . + collection := self otherCollection. + elem := self element. + added := collection write: elem. - self assert: added == elem . "test for identiy because #add: has not reason to copy its parameter." - self assert: (collection includes: elem ) . - self assert: (collection includes: elem ). + self assert: added == elem. "test for identiy because #add: has not reason to copy its parameter." + self assert: (collection includes: elem). + self assert: (collection includes: elem) ] @@ -131,13 +135,13 @@ TAddTest >> testTWrite [ { #category : #'tests - adding' } TAddTest >> testTWriteTwice [ | added oldSize collection elem | - collection := self collectionWithElement . - elem := self element . - oldSize := collection size. + collection := self collectionWithElement. + elem := self element. + oldSize := collection size. added := collection - write: elem ; - write: elem . + write: elem; + write: elem. self assert: added == elem . "test for identiy because #add: has not reason to copy its parameter." self assert: (collection includes: elem ). - self assert: collection size = (oldSize + 2) + self assert: collection size equals: (oldSize + 2) ] diff --git a/src/Collections-Tests/TAsStringCommaAndDelimiterSequenceableTest.trait.st b/src/Collections-Tests/TAsStringCommaAndDelimiterSequenceableTest.trait.st index 938bf671b43..6f4d6493367 100644 --- a/src/Collections-Tests/TAsStringCommaAndDelimiterSequenceableTest.trait.st +++ b/src/Collections-Tests/TAsStringCommaAndDelimiterSequenceableTest.trait.st @@ -28,6 +28,7 @@ TAsStringCommaAndDelimiterSequenceableTest >> nonEmpty1Element [ { #category : #'tests - fixture' } TAsStringCommaAndDelimiterSequenceableTest >> test0FixtureAsStringCommaAndDelimiterTest [ + self nonEmpty. self deny: self nonEmpty isEmpty. self empty. @@ -40,7 +41,7 @@ TAsStringCommaAndDelimiterSequenceableTest >> test0FixtureAsStringCommaAndDelimi TAsStringCommaAndDelimiterSequenceableTest >> testAsCommaStringEmpty [ self assert: self empty asCommaString = ''. - self assert: self empty asCommaStringAnd = ''. + self assert: self empty asCommaStringAnd = '' ] @@ -49,8 +50,7 @@ TAsStringCommaAndDelimiterSequenceableTest >> testAsCommaStringEmpty [ TAsStringCommaAndDelimiterSequenceableTest >> testAsCommaStringMore [ "self assert: self oneTwoThreeItemCol asCommaString = '1, 2, 3'. - self assert: self oneTwoThreeItemCol asCommaStringAnd = '1, 2 and 3' -" + self assert: self oneTwoThreeItemCol asCommaStringAnd = '1, 2 and 3'" | result resultAnd index allElementsAsString | result:= self nonEmpty asCommaString . @@ -92,18 +92,20 @@ TAsStringCommaAndDelimiterSequenceableTest >> testAsCommaStringOne [ "self assert: self oneItemCol asCommaString = '1'. self assert: self oneItemCol asCommaStringAnd = '1'." - self assert: self nonEmpty1Element asCommaString = (self nonEmpty1Element first asString). - self assert: self nonEmpty1Element asCommaStringAnd = (self nonEmpty1Element first asString). + self assert: self nonEmpty1Element asCommaString = (self nonEmpty1Element first asString). + self assert: self nonEmpty1Element asCommaStringAnd = (self nonEmpty1Element first asString) ] { #category : #'tests - as string comma delimiter sequenceable' } TAsStringCommaAndDelimiterSequenceableTest >> testAsStringOnDelimiterEmpty [ + self assert: (String streamContents: [ :emptyStream | self empty asStringOn: emptyStream delimiter: ', ' ]) equals: '' ] { #category : #'tests - as string comma delimiter sequenceable' } TAsStringCommaAndDelimiterSequenceableTest >> testAsStringOnDelimiterLastEmpty [ + self assert: (String streamContents: [ :emptyStream | self empty asStringOn: emptyStream delimiter: ', ' last: 'and' ]) equals: '' ] @@ -126,22 +128,19 @@ TAsStringCommaAndDelimiterSequenceableTest >> testAsStringOnDelimiterLastMore [ i=(allElementsAsString size-1) ifTrue:[ self deny: (allElementsAsString at:i)=(last)asString]. i=(allElementsAsString size) - ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)]. - ]. - + ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)]] ] { #category : #'tests - comma and delimiter' } TAsStringCommaAndDelimiterSequenceableTest >> testAsStringOnDelimiterLastOne [ - | delim oneItemStream result | - + | delim oneItemStream result | delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim last: 'and'. - oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)]. + oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)] @@ -151,38 +150,27 @@ TAsStringCommaAndDelimiterSequenceableTest >> testAsStringOnDelimiterLastOne [ TAsStringCommaAndDelimiterSequenceableTest >> testAsStringOnDelimiterMore [ | delim multiItemStream result index | - "delim := ', '. - multiItemStream := '' readWrite. - self oneTwoThreeItemCol asStringOn: multiItemStream delimiter: ', '. - self assert: multiItemStream contents = '1, 2, 3'." - delim := ', '. - result:=''. - multiItemStream := ReadWriteStream on:result. + result := ''. + multiItemStream := ReadWriteStream on: result. self nonEmpty asStringOn: multiItemStream delimiter: delim. result := multiItemStream contents. index:=1. - (result findBetweenSubstrings: delim )do: + (result findBetweenSubstrings: delim)do: [:each | - self assert: each= ((self nonEmpty at:index)asString). - index:=index+1 - ]. + self assert: each= ((self nonEmpty at:index) asString). + index:=index+1 ] ] { #category : #'tests - comma and delimiter' } TAsStringCommaAndDelimiterSequenceableTest >> testAsStringOnDelimiterOne [ | delim oneItemStream result | - "delim := ', '. - oneItemStream := '' readWrite. - self oneItemCol asStringOn: oneItemStream delimiter: delim. - self assert: oneItemStream contents = '1'." - delim := ', '. - result:=''. + result := ''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim. - oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)]. + oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)] diff --git a/src/Collections-Tests/TBeginsEndsWith.trait.st b/src/Collections-Tests/TBeginsEndsWith.trait.st index 5c61f89a96d..438b204a3c1 100644 --- a/src/Collections-Tests/TBeginsEndsWith.trait.st +++ b/src/Collections-Tests/TBeginsEndsWith.trait.st @@ -18,6 +18,7 @@ TBeginsEndsWith >> nonEmpty [ { #category : #'tests - fixture' } TBeginsEndsWith >> test0FixtureBeginsEndsWithTest [ + self nonEmpty. self deny: self nonEmpty isEmpty. self assert: self nonEmpty size > 1. @@ -28,16 +29,16 @@ TBeginsEndsWith >> test0FixtureBeginsEndsWithTest [ { #category : #'tests - begins ends with' } TBeginsEndsWith >> testsBeginsWith [ - self assert: (self nonEmpty beginsWith:(self nonEmpty copyUpTo: self nonEmpty last)). - self assert: (self nonEmpty beginsWith:(self nonEmpty )). - self deny: (self nonEmpty beginsWith:(self nonEmpty copyWith:self nonEmpty first)). + self assert: (self nonEmpty beginsWith: (self nonEmpty copyUpTo: self nonEmpty last)). + self assert: (self nonEmpty beginsWith: self nonEmpty). + self deny: (self nonEmpty beginsWith: (self nonEmpty copyWith: self nonEmpty first)) ] { #category : #'tests - begins ends with' } TBeginsEndsWith >> testsBeginsWithEmpty [ self deny: (self nonEmpty beginsWith:(self empty)). - self deny: (self empty beginsWith:(self nonEmpty )). + self deny: (self empty beginsWith:(self nonEmpty)) ] @@ -46,13 +47,13 @@ TBeginsEndsWith >> testsEndsWith [ self assert: (self nonEmpty endsWith: self nonEmpty copyWithoutFirst). self assert: (self nonEmpty endsWith: self nonEmpty). - self deny: (self nonEmpty endsWith: (self nonEmpty copyWith: self nonEmpty first)). + self deny: (self nonEmpty endsWith: (self nonEmpty copyWith: self nonEmpty first)) ] { #category : #'tests - begins ends with' } TBeginsEndsWith >> testsEndsWithEmpty [ self deny: (self nonEmpty endsWith: self empty). - self deny: (self empty endsWith: self nonEmpty). + self deny: (self empty endsWith: self nonEmpty) ] diff --git a/src/Collections-Tests/TConvertAsSetForMultiplinessIdentityTest.trait.st b/src/Collections-Tests/TConvertAsSetForMultiplinessIdentityTest.trait.st index 9fc919c7bb6..c91c8a9ff86 100644 --- a/src/Collections-Tests/TConvertAsSetForMultiplinessIdentityTest.trait.st +++ b/src/Collections-Tests/TConvertAsSetForMultiplinessIdentityTest.trait.st @@ -10,8 +10,9 @@ Trait { { #category : #requirements } TConvertAsSetForMultiplinessIdentityTest >> collectionWithCopy [ - "return a collection of type 'self collectionWIithoutEqualsElements class' containing no elements equals ( with identity equality) - but 2 elements only equals with classic equality" + "Return a collection of type 'self collectionWIithoutEqualsElements class' containing no elements equals (with identity equality) + but 2 elements only equals with classic equality" + | result collection | collection := OrderedCollection withAll: self elementsCopyNonIdenticalWithoutEqualElements. collection add: collection first copy. @@ -21,7 +22,8 @@ TConvertAsSetForMultiplinessIdentityTest >> collectionWithCopy [ { #category : #requirements } TConvertAsSetForMultiplinessIdentityTest >> collectionWithIdentical [ - "return a collection of type : 'self collectionWIithoutEqualsElements class containing two elements equals ( with identity equality)" + "Return a collection of type: 'self collectionWIithoutEqualsElements class containing two elements equals (with identity equality)." + | result collection anElement | collection := OrderedCollection withAll: self elementsCopyNonIdenticalWithoutEqualElements. anElement := collection first. @@ -39,7 +41,7 @@ TConvertAsSetForMultiplinessIdentityTest >> elementsCopyNonIdenticalWithoutEqual { #category : #'tests - fixture' } TConvertAsSetForMultiplinessIdentityTest >> test0FixtureAsSetForIdentityMultiplinessTest [ - "a collection (of elements for which copy is not identical ) without equal elements:" + "A collection (of elements for which copy is not identical ) without equal elements:" | anElement res | self elementsCopyNonIdenticalWithoutEqualElements. @@ -65,15 +67,17 @@ TConvertAsSetForMultiplinessIdentityTest >> test0FixtureTConvertAsSetForMultipli { #category : #'tests - as set tests' } TConvertAsSetForMultiplinessIdentityTest >> testAsIdentitySetWithEqualsElements [ + | result collection | collection := self withEqualElements . result := collection asIdentitySet. collection do: [ :each | self assert: (result occurrencesOf: each) = 1 ]. - self assert: result class = IdentitySet. + self assert: result class = IdentitySet ] { #category : #'tests - as identity set' } TConvertAsSetForMultiplinessIdentityTest >> testAsIdentitySetWithIdentityEqualsElements [ + | result | result := self collectionWithIdentical asIdentitySet. " Only one element should have been removed as two elements are equals with Identity equality" @@ -91,6 +95,7 @@ TConvertAsSetForMultiplinessIdentityTest >> testAsIdentitySetWithIdentityEqualsE { #category : #'tests - as identity set' } TConvertAsSetForMultiplinessIdentityTest >> testAsIdentitySetWithoutIdentityEqualsElements [ + | result collection | collection := self collectionWithCopy. result := collection asIdentitySet. @@ -104,6 +109,7 @@ TConvertAsSetForMultiplinessIdentityTest >> testAsIdentitySetWithoutIdentityEqua { #category : #'tests - as set tests' } TConvertAsSetForMultiplinessIdentityTest >> testAsSetWithEqualsElements [ + | result | result := self withEqualElements asSet. self withEqualElements do: [ :each | self assert: (result occurrencesOf: each) = 1 ]. diff --git a/src/Collections-Tests/TConvertAsSortedTest.trait.st b/src/Collections-Tests/TConvertAsSortedTest.trait.st index 13fe5fddb04..7d1cb1e5227 100644 --- a/src/Collections-Tests/TConvertAsSortedTest.trait.st +++ b/src/Collections-Tests/TConvertAsSortedTest.trait.st @@ -14,12 +14,14 @@ TConvertAsSortedTest >> collectionWithSortableElements [ { #category : #'tests - fixture' } TConvertAsSortedTest >> test0FixtureConverAsSortedTest [ + self collectionWithSortableElements. self deny: self collectionWithSortableElements isEmpty ] { #category : #'tests - as sorted collection' } TConvertAsSortedTest >> testAsSortedArray [ + | result collection | collection := self collectionWithSortableElements . result := collection asArray sort. @@ -40,19 +42,20 @@ TConvertAsSortedTest >> testAsSortedCollection [ [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. - self assert: result size = aCollection size. + self assert: result size = aCollection size ] { #category : #'tests - as sorted collection' } TConvertAsSortedTest >> testAsSortedCollectionWithSortBlock [ + | result tmp | - result := self collectionWithSortableElements asSortedCollection: [:a :b | a > b]. + result := self collectionWithSortableElements asSortedCollection: [:a :b | a > b ]. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | - self assert: (self collectionWithSortableElements occurrencesOf: each) = (result occurrencesOf: each) ]. - self assert: result size = self collectionWithSortableElements size. + self assert: (self collectionWithSortableElements occurrencesOf: each) equals: (result occurrencesOf: each) ]. + self assert: result size equals: self collectionWithSortableElements size. tmp:=result at: 1. - result do: [:each| self assert: tmp>=each. tmp:=each]. + result do: [:each| self assert: tmp >= each. tmp := each ] ] diff --git a/src/Collections-Tests/TConvertTest.trait.st b/src/Collections-Tests/TConvertTest.trait.st index e739c3a3cff..716b7e3c19a 100644 --- a/src/Collections-Tests/TConvertTest.trait.st +++ b/src/Collections-Tests/TConvertTest.trait.st @@ -6,30 +6,33 @@ Trait { #category : #'Collections-Tests-Abstract' } -{ #category : #'tests - converting' } -TConvertTest >> assertNoDuplicates: aCollection whenConvertedTo: aClass [ +{ #category : #'as yet unclassified' } +TConvertTest >> assertNoDuplicates: aCollection whenConvertedTo: aClass [ + | result | result := self collectionWithEqualElements asIdentitySet. self assert: (result class includesBehavior: IdentitySet). - self collectionWithEqualElements do: [ :initial | self assert: (result occurrencesOf: initial) = 1 ] + self collectionWithEqualElements do: [ :initial | self assert: (result occurrencesOf: initial) equals: 1 ] ] { #category : #'tests - converting' } -TConvertTest >> assertNonDuplicatedContents: aCollection whenConvertedTo: aClass [ +TConvertTest >> assertNonDuplicatedContents: aCollection whenConvertedTo: aClass [ + | result | result := aCollection perform: ('as' , aClass name) asSymbol. self assert: (result class includesBehavior: aClass). result do: [ :each | - self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. + self assert: (aCollection occurrencesOf: each) equals: (result occurrencesOf: each) ]. ^ result ] { #category : #'tests - converting' } -TConvertTest >> assertSameContents: aCollection whenConvertedTo: aClass [ +TConvertTest >> assertSameContents: aCollection whenConvertedTo: aClass [ + | result | result := self assertNonDuplicatedContents: aCollection whenConvertedTo: aClass. - self assert: result size = aCollection size + self assert: result size equals: aCollection size ] { #category : #requirements } @@ -46,7 +49,7 @@ TConvertTest >> integerCollectionWithoutEqualElements [ { #category : #'tests - fixture' } TConvertTest >> test0FixtureTConvertTest [ - "a collection of number without equal elements:" + "A collection of number without equal elements:" | res | self collectionWithoutEqualElements. @@ -73,6 +76,7 @@ TConvertTest >> testAsBag [ { #category : #'tests - converting' } TConvertTest >> testAsByteArray [ + | res | self integerCollectionWithoutEqualElements. self integerCollectionWithoutEqualElements do: [ :each | self assert: each class = SmallInteger ]. @@ -86,10 +90,11 @@ TConvertTest >> testAsByteArray [ { #category : #'tests - converting' } TConvertTest >> testAsIdentitySet [ - "test with a collection without equal elements :" + "Test with a collection without equal elements :" + self assertSameContents: self collectionWithoutEqualElements - whenConvertedTo: IdentitySet. + whenConvertedTo: IdentitySet ] @@ -101,8 +106,8 @@ TConvertTest >> testAsOrderedCollection [ { #category : #'tests - converting' } TConvertTest >> testAsSet [ - | | - "test with a collection without equal elements :" - self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Set. + "Test with a collection without equal elements" + + self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Set ] diff --git a/src/Collections-Tests/TCopyPartOfSequenceable.trait.st b/src/Collections-Tests/TCopyPartOfSequenceable.trait.st index 6b53f103d22..ea3e7536a4d 100644 --- a/src/Collections-Tests/TCopyPartOfSequenceable.trait.st +++ b/src/Collections-Tests/TCopyPartOfSequenceable.trait.st @@ -26,6 +26,7 @@ TCopyPartOfSequenceable >> indexInForCollectionWithoutDuplicates [ { #category : #'tests - fixture' } TCopyPartOfSequenceable >> test0FixtureCopyPartOfSequenceableTest [ + self collectionWithoutEqualElements. self collectionWithoutEqualElements do: [ :each | self assert: (self collectionWithoutEqualElements occurrencesOf: each) = 1 ]. @@ -45,52 +46,54 @@ TCopyPartOfSequenceable >> testCopyAfter [ index:= self indexInForCollectionWithoutDuplicates . result := collection copyAfter: (collection at:index ). - "verifying content: " - (1) to: result size do: - [:i | - self assert: (collection at:(i + index ))=(result at: (i))]. + "Verify content" + result withIndexDo: + [:e :i | self assert: (collection at: (i + index )) equals: (result at: i)]. - "verify size: " - self assert: result size = (collection size - index). + "Verify size" + self assert: result size equals: (collection size - index) ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyAfterEmpty [ + | result | result := self empty copyAfter: self collectionWithoutEqualElements first. - self assert: result isEmpty. + self assert: result isEmpty ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyAfterLast [ + | result index collection | collection := self collectionWithoutEqualElements . index:= self indexInForCollectionWithoutDuplicates . - result := collection copyAfterLast: (collection at:index ). + result := collection copyAfterLast: (collection at:index ). - "verifying content: " - (1) to: result size do: - [:i | - self assert: (collection at:(i + index ))=(result at: (i))]. + "Verify content" + result withIndexDo: + [:el :i | self assert: (collection at: (i + index )) equals: (result at: i)]. - "verify size: " - self assert: result size = (collection size - index). + "Verify size" + self assert: result size equals: (collection size - index) ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyAfterLastEmpty [ + | result | result := self empty copyAfterLast: self collectionWithoutEqualElements first. - self assert: result isEmpty. + self assert: result isEmpty ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyEmptyMethod [ + | result | result := self collectionWithoutEqualElements copyEmpty . self assert: result isEmpty . - self assert: result class= self nonEmpty class. + self assert: result class equals: self nonEmpty class. ] { #category : #'tests - copying part of sequenceable' } @@ -100,55 +103,58 @@ TCopyPartOfSequenceable >> testCopyFromTo [ index :=self indexInForCollectionWithoutDuplicates . result := collection copyFrom: index to: collection size . - "verify content of 'result' : " - 1 to: result size do: - [:i | - self assert: (result at:i)=(collection at: (i + index - 1))]. + "Verify content" + result withIndexDo: + [:el :i | self assert: (result at:i) equals: (collection at: (i + index - 1))]. - "verify size of 'result' : " - self assert: result size = (collection size - index + 1). + "Verify size" + self assert: result size equals: (collection size - index + 1) ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyUpTo [ + | result index collection | - collection := self collectionWithoutEqualElements . - index:= self indexInForCollectionWithoutDuplicates . + collection := self collectionWithoutEqualElements. + index:= self indexInForCollectionWithoutDuplicates. result := collection copyUpTo: (collection at:index). - "verify content of 'result' :" - 1 to: result size do: [:i| self assert: (collection at:i)=(result at:i)]. + "Verify content" + result withIndexDo: [:el :i| self assert: (collection at:i) equals: (result at:i)]. - "verify size of 'result' :" - self assert: result size = (index-1). + "Verify size" + self assert: result size equals: (index-1) ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyUpToEmpty [ + | result | result := self empty copyUpTo: self collectionWithoutEqualElements first. - self assert: result isEmpty. + self assert: result isEmpty ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyUpToLast [ + | result index collection | - collection := self collectionWithoutEqualElements . - index:= self indexInForCollectionWithoutDuplicates . - result := collection copyUpToLast: (collection at:index). + collection := self collectionWithoutEqualElements. + index:= self indexInForCollectionWithoutDuplicates. + result := collection copyUpToLast: (collection at:index). - "verify content of 'result' :" - 1 to: result size do: [:i| self assert: (collection at:i)=(result at:i)]. + "Verify content" + result withIndexDo: [:el :i| self assert: (collection at:i) equals: (result at: i)]. - "verify size of 'result' :" - self assert: result size = (index-1). + "Verify size" + self assert: result size equals: (index-1) ] { #category : #'tests - copying part of sequenceable' } TCopyPartOfSequenceable >> testCopyUpToLastEmpty [ + | result | result := self empty copyUpToLast: self collectionWithoutEqualElements first. - self assert: result isEmpty. + self assert: result isEmpty ] diff --git a/src/Collections-Tests/TCopyPartOfSequenceableForMultipliness.trait.st b/src/Collections-Tests/TCopyPartOfSequenceableForMultipliness.trait.st index c0d873f7b5d..3d73f309495 100644 --- a/src/Collections-Tests/TCopyPartOfSequenceableForMultipliness.trait.st +++ b/src/Collections-Tests/TCopyPartOfSequenceableForMultipliness.trait.st @@ -15,6 +15,7 @@ TCopyPartOfSequenceableForMultipliness >> collectionWithSameAtEndAndBegining [ { #category : #'tests - fixture' } TCopyPartOfSequenceableForMultipliness >> test0FixtureCopyPartOfForMultipliness [ + self collectionWithSameAtEndAndBegining. self assert: self collectionWithSameAtEndAndBegining first = self collectionWithSameAtEndAndBegining last. self assert: self collectionWithSameAtEndAndBegining size > 1. @@ -25,73 +26,73 @@ TCopyPartOfSequenceableForMultipliness >> test0FixtureCopyPartOfForMultipliness { #category : #'tests - copying part of sequenceable for multipliness' } TCopyPartOfSequenceableForMultipliness >> testCopyAfterLastWithDuplicate [ + | result element collection | - collection := self collectionWithSameAtEndAndBegining . - element := collection first. + collection := self collectionWithSameAtEndAndBegining. + element := collection first. - " collectionWithSameAtEndAndBegining first and last elements are equals. + "collectionWithSameAtEndAndBegining first and last elements are equals. 'copyAfter:' should copy after the last occurence of element :" - result := collection copyAfterLast: (element ). + result := collection copyAfterLast: (element ). - "verifying content: " - self assert: result isEmpty. + "Verify content" + self assert: result isEmpty ] { #category : #'tests - copying part of sequenceable for multipliness' } TCopyPartOfSequenceableForMultipliness >> testCopyAfterWithDuplicate [ + | result element collection | - collection := self collectionWithSameAtEndAndBegining . - element := collection last. + collection := self collectionWithSameAtEndAndBegining. + element := collection last. - " collectionWithSameAtEndAndBegining first and last elements are equals. - 'copyAfter:' should copy after the first occurence :" + "collectionWithSameAtEndAndBegining first and last elements are equals. + 'copyAfter:' should copy after the first occurence:" result := collection copyAfter: (element ). - "verifying content: " - 1 to: result size do: - [:i | - self assert: (collection at:(i + 1 )) = (result at: (i)) - ]. - - "verify size: " - self assert: result size = (collection size - 1). + "Verifying content" + result withIndexDo: + [:e :i | self assert: (collection at: (i + 1 )) equals: (result at: (i)) ]. + + "Verify size" + self assert: result size equals: (collection size - 1). ] { #category : #'tests - copying part of sequenceable for multipliness' } TCopyPartOfSequenceableForMultipliness >> testCopyUpToLastWithDuplicate [ + | result element collection | - collection := self collectionWithSameAtEndAndBegining . - element := collection first. + collection := self collectionWithSameAtEndAndBegining. + element := collection first. - " collectionWithSameAtEndAndBegining first and last elements are equals. + "collectionWithSameAtEndAndBegining first and last elements are equals. 'copyUpToLast:' should copy until the last occurence :" - result := collection copyUpToLast: (element ). + result := collection copyUpToLast: (element ). - "verifying content: " - 1 to: result size do: - [:i | - self assert: (result at: i ) = ( collection at: i ) - ]. + "Verify content" + result withIndexDo: + [:el :i | self assert: (result at: i) equals: (collection at: i) ]. - self assert: result size = (collection size - 1). + self assert: result size equals: (collection size - 1) ] { #category : #'tests - copying part of sequenceable for multipliness' } TCopyPartOfSequenceableForMultipliness >> testCopyUpToWithDuplicate [ + | result element collection | - collection := self collectionWithSameAtEndAndBegining . - element := collection last. + collection := self collectionWithSameAtEndAndBegining. + element := collection last. - " collectionWithSameAtEndAndBegining first and last elements are equals. - 'copyUpTo:' should copy until the first occurence :" - result := collection copyUpTo: (element ). + "collectionWithSameAtEndAndBegining first and last elements are equals. + 'copyUpTo:' should copy until the first occurence" + result := collection copyUpTo: (element ). - "verifying content: " - self assert: result isEmpty. + "Verify content" + self assert: result isEmpty ] diff --git a/src/Collections-Tests/TCopySequenceableSameContents.trait.st b/src/Collections-Tests/TCopySequenceableSameContents.trait.st index 39024a4b7ff..a0928d069d3 100644 --- a/src/Collections-Tests/TCopySequenceableSameContents.trait.st +++ b/src/Collections-Tests/TCopySequenceableSameContents.trait.st @@ -24,6 +24,7 @@ TCopySequenceableSameContents >> nonEmpty [ { #category : #'tests - fixture' } TCopySequenceableSameContents >> test0FixtureCopySameContentsTest [ + self nonEmpty. self deny: self nonEmpty isEmpty. self empty. @@ -40,38 +41,43 @@ TCopySequenceableSameContents >> testReverse [ [:i | self assert: ((result at: i) = (self nonEmpty at: (self nonEmpty size - i + 1)))]. "verify size of 'result' :" - self assert: result size=self nonEmpty size. + self assert: result size=self nonEmpty size ] { #category : #'tests - copying same contents' } TCopySequenceableSameContents >> testReversed [ + | result | - result := self nonEmpty reversed . + result := self nonEmpty reversed. - "verify content of 'result: '" - 1 to: result size do: - [:i | self assert: ((result at:i)=(self nonEmpty at:(self nonEmpty size-i+1)))]. - "verify size of 'result' :" + "Verify content" + result withIndexDo: + [:el :i | self assert: el equals: (self nonEmpty at: (self nonEmpty size - i + 1))]. + + "Verify size" self assert: result size=self nonEmpty size. ] { #category : #'tests - copying same contents' } TCopySequenceableSameContents >> testShallowCopy [ + | result | - result := self nonEmpty shallowCopy . + result := self nonEmpty shallowCopy. - "verify content of 'result: '" - 1 to: self nonEmpty size do: - [:i | self assert: ((result at:i)=(self nonEmpty at:i))]. - "verify size of 'result' :" - self assert: result size=self nonEmpty size. + "Verfy content" + self nonEmpty withIndexDo: + [:el :i | self assert: (result at:i) equals: (self nonEmpty at:i)]. + + "Verify size" + self assert: result size equals: self nonEmpty size. ] { #category : #'tests - copying same contents' } TCopySequenceableSameContents >> testShallowCopyEmpty [ + | result | - result := self empty shallowCopy . - self assert: result isEmpty . + result := self empty shallowCopy. + self assert: result isEmpty ] { #category : #'tests - copying same contents' } diff --git a/src/Collections-Tests/TCopySequenceableWithOrWithoutSpecificElements.trait.st b/src/Collections-Tests/TCopySequenceableWithOrWithoutSpecificElements.trait.st index 3c7c8f3dd99..f01742fddb2 100644 --- a/src/Collections-Tests/TCopySequenceableWithOrWithoutSpecificElements.trait.st +++ b/src/Collections-Tests/TCopySequenceableWithOrWithoutSpecificElements.trait.st @@ -20,6 +20,7 @@ TCopySequenceableWithOrWithoutSpecificElements >> nonEmpty [ { #category : #'tests - fixture' } TCopySequenceableWithOrWithoutSpecificElements >> test0FixtureCopyWithOrWithoutSpecificElementsTest [ + self nonEmpty. self deny: self nonEmpty isEmpty. self indexInNonEmpty. @@ -48,16 +49,15 @@ TCopySequenceableWithOrWithoutSpecificElements >> testCopyWithFirst [ TCopySequenceableWithOrWithoutSpecificElements >> testCopyWithSequenceable [ | result index element | - index := self indexInNonEmpty . + index := self indexInNonEmpty. element := self nonEmpty at: index. result := self nonEmpty copyWith: (element ). - self assert: result size = (self nonEmpty size + 1). - self assert: result last = element . + self assert: result size equals: (self nonEmpty size + 1). + self assert: result last equals: element. 1 to: (result size - 1) do: - [ :i | - self assert: (result at: i) = ( self nonEmpty at: ( i ))]. + [ :i | self assert: (result at: i) equals: ( self nonEmpty at: i)] ] { #category : #'tests - copying with or without' } @@ -66,11 +66,10 @@ TCopySequenceableWithOrWithoutSpecificElements >> testCopyWithoutFirst [ | result | result := self nonEmpty copyWithoutFirst. - self assert: result size = (self nonEmpty size - 1). + self assert: result size equals: (self nonEmpty size - 1). - 1 to: result size do: - [:i | - self assert: (result at: i)= (self nonEmpty at: (i + 1))]. + result withIndexDo: + [:el :i | self assert: (result at: i) equals: (self nonEmpty at: (i + 1))] ] { #category : #'tests - copying with or without' } diff --git a/src/Collections-Tests/TCopySequenceableWithReplacementForSorted.trait.st b/src/Collections-Tests/TCopySequenceableWithReplacementForSorted.trait.st index 95aecd85a08..38d47c26bce 100644 --- a/src/Collections-Tests/TCopySequenceableWithReplacementForSorted.trait.st +++ b/src/Collections-Tests/TCopySequenceableWithReplacementForSorted.trait.st @@ -25,6 +25,7 @@ self explicitRequirement { #category : #'tests - fixture' } TCopySequenceableWithReplacementForSorted >> test0FixtureCopyWithReplacementForSorted [ + self collectionOfSize5. self assert: self collectionOfSize5 size = 5. self replacementCollection. @@ -35,20 +36,20 @@ TCopySequenceableWithReplacementForSorted >> test0FixtureCopyWithReplacementForS { #category : #'tests - copying with replacement for sorted' } TCopySequenceableWithReplacementForSorted >> testCopyFromToWithForSorted [ -| collection result | -collection := self collectionOfSize5 . -" testing that elements to be replaced are removed from the copy :" -result := collection copyReplaceFrom: 1 to: collection size with: self empty . -self assert: result isEmpty. + | collection result | + collection := self collectionOfSize5 . + + "Testing that elements to be replaced are removed from the copy :" + result := collection copyReplaceFrom: 1 to: collection size with: self empty . + self assert: result isEmpty. -" testing that replacement elements are all put into the copy :" -result := collection copyReplaceFrom: 1 to: collection size with: self replacementCollection . - self replacementCollection do: - [:each | - self assert: (result occurrencesOf: each) = ( self replacementCollection occurrencesOf: each )]. + "Testing that replacement elements are all put into the copy :" + result := collection copyReplaceFrom: 1 to: collection size with: self replacementCollection . + self replacementCollection do: + [:each | self assert: (result occurrencesOf: each) equals: ( self replacementCollection occurrencesOf: each )]. -self assert: result size = self replacementCollection size. + self assert: result size equals: self replacementCollection size ] @@ -56,20 +57,19 @@ self assert: result size = self replacementCollection size. { #category : #'tests - copying with replacement for sorted' } TCopySequenceableWithReplacementForSorted >> testCopyReplaceAllWithForSorted [ -| collection result | -collection := self collectionOfSize5 . + | collection result | + collection := self collectionOfSize5 . -" testing that elements to be replaced are removed from the copy :" -result := collection copyReplaceAll: collection with: self empty . -self assert: result isEmpty. + "Testing that elements to be replaced are removed from the copy :" + result := collection copyReplaceAll: collection with: self empty. + self assert: result isEmpty. -" testing that replacement elements are all put into the copy :" -result := collection copyReplaceAll: collection with: self replacementCollection . - self replacementCollection do: - [:each | - self assert: (result occurrencesOf: each) = ( self replacementCollection occurrencesOf: each )]. + "Testing that replacement elements are all put into the copy :" + result := collection copyReplaceAll: collection with: self replacementCollection. + self replacementCollection do: + [:each | self assert: (result occurrencesOf: each) equals: (self replacementCollection occurrencesOf: each)]. -self assert: result size = self replacementCollection size. + self assert: result size equals: self replacementCollection size ] diff --git a/src/Collections-Tests/TCopyTest.trait.st b/src/Collections-Tests/TCopyTest.trait.st index 156e54dfcaa..06f73a39592 100644 --- a/src/Collections-Tests/TCopyTest.trait.st +++ b/src/Collections-Tests/TCopyTest.trait.st @@ -39,6 +39,7 @@ TCopyTest >> nonEmpty [ { #category : #'tests - fixture' } TCopyTest >> test0CopyTest [ + self empty. self assert: self empty size = 0. self nonEmpty. @@ -54,36 +55,39 @@ TCopyTest >> test0CopyTest [ { #category : #'tests - copy' } TCopyTest >> testCopyEmptyWith [ + | res anElement | anElement := self elementToAdd. res := self empty copyWith: anElement. - self assert: res size = (self empty size + 1). + self assert: res size equals: (self empty size + 1). self assert: (res includes: (anElement value)) ] { #category : #'tests - copy' } TCopyTest >> testCopyEmptyWithout [ + | res | res := self empty copyWithout: self elementToAdd. - self assert: res size = self empty size. + self assert: res size equals: self empty size. self deny: (res includes: self elementToAdd) ] { #category : #'tests - copy' } TCopyTest >> testCopyEmptyWithoutAll [ + | res | res := self empty copyWithoutAll: self collectionWithElementsToRemove. - self assert: res size = self empty size. + self assert: res size equals: self empty size. self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ] ] { #category : #'tests - copy' } TCopyTest >> testCopyEquals [ - "A copy should be equivalent to the things it's a copy of" + "A copy should be equivalent to the things it's a copy of." | copy | copy := self nonEmpty copy. - self assert: copy = self nonEmpty. + self assert: copy equals: self nonEmpty ] { #category : #'tests - copy' } @@ -92,7 +96,7 @@ TCopyTest >> testCopyNonEmptyWith [ | res anElement | anElement := self elementToAdd . res := self nonEmpty copyWith: anElement. - "here we do not test the size since for a non empty set we would get a problem. + "Here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self assert: (res includes: (anElement value)). @@ -111,13 +115,14 @@ TCopyTest >> testCopyNonEmptyWithout [ self deny: (res includes: anElementOfTheCollection). self nonEmpty do: [:each | (each = anElementOfTheCollection) - ifFalse: [self assert: (res includes: each)]]. + ifFalse: [self assert: (res includes: each)]] ] { #category : #'tests - copy' } TCopyTest >> testCopyNonEmptyWithoutAll [ + | res | res := self nonEmpty copyWithoutAll: self collectionWithElementsToRemove. "here we do not test the size since for a non empty set we would get a problem. @@ -157,7 +162,7 @@ TCopyTest >> testCopyNotSame [ | copy | copy := self nonEmpty copy. - self deny: copy == self nonEmpty. + self deny: copy == self nonEmpty ] { #category : #'tests - copy' } @@ -166,5 +171,5 @@ TCopyTest >> testCopySameClass [ | copy | copy := self empty copy. - self assert: copy class == self empty class. + self assert: copy class == self empty class ] diff --git a/src/Collections-Tests/TCreationWithTest.trait.st b/src/Collections-Tests/TCreationWithTest.trait.st index 9c12ae86300..585f0bba2f7 100644 --- a/src/Collections-Tests/TCreationWithTest.trait.st +++ b/src/Collections-Tests/TCreationWithTest.trait.st @@ -21,6 +21,7 @@ TCreationWithTest >> collectionMoreThan5Elements [ { #category : #'tests - fixture' } TCreationWithTest >> test0FixtureCreationWithTest [ + self collectionMoreThan5Elements. self assert: self collectionMoreThan5Elements size >= 5 ] @@ -30,7 +31,7 @@ TCreationWithTest >> testOfSize [ | aCol | aCol := self collectionClass ofSize: 3. - self assert: (aCol size = 3). + self assert: aCol size equals: 3. ] @@ -47,25 +48,25 @@ TCreationWithTest >> testWith [ TCreationWithTest >> testWithAll [ | aCol collection | - collection := self collectionMoreThan5Elements asOrderedCollection . - aCol := self collectionClass withAll: collection . + collection := self collectionMoreThan5Elements asOrderedCollection. + aCol := self collectionClass withAll: collection. - collection do: [ :each | self assert: (aCol occurrencesOf: each ) = ( collection occurrencesOf: each ) ]. + collection do: [ :each | self assert: (aCol occurrencesOf: each ) equals: ( collection occurrencesOf: each ) ]. - self assert: (aCol size = collection size ). + self assert: aCol size equals: collection size ] { #category : #'tests - creation' } TCreationWithTest >> testWithWith [ | aCol collection element1 element2 | - collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 2 . + collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 2. element1 := collection at: 1. - element2 := collection at:2. + element2 := collection at: 2. aCol := self collectionClass with: element1 with: element2 . - self assert: (aCol occurrencesOf: element1 ) = ( collection occurrencesOf: element1). - self assert: (aCol occurrencesOf: element2 ) = ( collection occurrencesOf: element2). + self assert: (aCol occurrencesOf: element1 ) equals: (collection occurrencesOf: element1). + self assert: (aCol occurrencesOf: element2 ) equals: (collection occurrencesOf: element2) ] @@ -75,9 +76,13 @@ TCreationWithTest >> testWithWithWith [ | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom:1 to: 3 . - aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3). + aCol := self collectionClass + with: (collection at: 1) + with: (collection at: 2) + with: (collection at: 3). - 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ]. + 1 to: 3 do: [ :i | + self assert: (aCol occurrencesOf: (collection at: i)) equals: (collection occurrencesOf: (collection at: i)) ] ] { #category : #'tests - creation' } @@ -85,17 +90,22 @@ TCreationWithTest >> testWithWithWithWith [ | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 4. - aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: ( collection at: 4). + aCol := self collectionClass with: (collection at:1) with: (collection at:2) with: (collection at: 3) with: (collection at: 4). - 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ]. + 1 to: 3 do: [ :i | self assert: (aCol occurrencesOf: (collection at: i)) equals: (collection occurrencesOf: (collection at: i)) ] ] { #category : #'tests - creation' } TCreationWithTest >> testWithWithWithWithWith [ | aCol collection | - collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 5 . - aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: (collection at: 4 ) with: ( collection at: 5 ). + collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 5. + aCol := self collectionClass + with: (collection at: 1) + with: (collection at: 2) + with: (collection at: 3) + with: (collection at: 4) + with: (collection at: 5). - 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ]. + 1 to: 3 do: [ :i | self assert: (aCol occurrencesOf: (collection at: i)) equals: (collection occurrencesOf: (collection at: i)) ] ] diff --git a/src/Collections-Tests/TIncludesWithIdentityCheckTest.trait.st b/src/Collections-Tests/TIncludesWithIdentityCheckTest.trait.st index fdb417d92b2..f8f142c0ccd 100644 --- a/src/Collections-Tests/TIncludesWithIdentityCheckTest.trait.st +++ b/src/Collections-Tests/TIncludesWithIdentityCheckTest.trait.st @@ -39,6 +39,7 @@ TIncludesWithIdentityCheckTest >> nonEmpty [ { #category : #'tests - fixture' } TIncludesWithIdentityCheckTest >> test0FixtureIncludeTest [ + | anElementIn | self nonEmpty. self deny: self nonEmpty isEmpty. @@ -56,6 +57,7 @@ TIncludesWithIdentityCheckTest >> test0FixtureIncludeTest [ { #category : #'tests - fixture' } TIncludesWithIdentityCheckTest >> test0FixtureIncludeWithIdentityTest [ + | anElement | self collectionWithCopyNonIdentical. anElement := self collectionWithCopyNonIdentical anyOne. @@ -76,19 +78,20 @@ TIncludesWithIdentityCheckTest >> testIdentityIncludes [ { #category : #'tests - includes' } TIncludesWithIdentityCheckTest >> testIdentityIncludesNonSpecificComportement [ - " test the same comportement than 'includes: ' " + "Test the same comportement than 'includes: '." + | collection | - collection := self nonEmpty . + collection := self nonEmpty. - self deny: (collection identityIncludes: self elementNotIn ). - self assert:(collection identityIncludes: collection anyOne) + self deny: (collection identityIncludes: self elementNotIn). + self assert: (collection identityIncludes: collection anyOne) ] { #category : #'tests - includes' } TIncludesWithIdentityCheckTest >> testIncludesAllNoneThere [ - self deny: (self empty includesAll: self nonEmpty ). + self deny: (self empty includesAll: self nonEmpty). self deny: (self nonEmpty includesAll: { self elementNotIn. self anotherElementNotIn }) ] @@ -97,7 +100,7 @@ TIncludesWithIdentityCheckTest >> testIncludesAnyAllThere [ self deny: (self nonEmpty includesAny: self empty). self assert: (self nonEmpty includesAny: { self nonEmpty anyOne }). - self assert: (self nonEmpty includesAny: self nonEmpty). + self assert: (self nonEmpty includesAny: self nonEmpty) ] { #category : #'tests - includes' } @@ -118,5 +121,5 @@ TIncludesWithIdentityCheckTest >> testIncludesElementIsNotThere [ { #category : #'tests - includes' } TIncludesWithIdentityCheckTest >> testIncludesElementIsThere [ - self assert: (self nonEmpty includes: self nonEmpty anyOne). + self assert: (self nonEmpty includes: self nonEmpty anyOne) ] diff --git a/src/Collections-Tests/TIndexAccessForMultipliness.trait.st b/src/Collections-Tests/TIndexAccessForMultipliness.trait.st index c501a8becbc..656447c8f0f 100644 --- a/src/Collections-Tests/TIndexAccessForMultipliness.trait.st +++ b/src/Collections-Tests/TIndexAccessForMultipliness.trait.st @@ -22,6 +22,7 @@ TIndexAccessForMultipliness >> collectionWithSameAtEndAndBegining [ { #category : #'tests - fixture' } TIndexAccessForMultipliness >> test0FixtureIndexAccessFotMultipliness [ + self collectionWithSameAtEndAndBegining. self assert: self collectionWithSameAtEndAndBegining first = self collectionWithSameAtEndAndBegining last. self assert: self collectionWithSameAtEndAndBegining size > 1. @@ -37,9 +38,9 @@ TIndexAccessForMultipliness >> testIdentityIndexOfDuplicate [ "testing fixture here as this method may not be used by some collections testClass" self collectionWithNonIdentitySameAtEndAndBegining. collection := self collectionWithNonIdentitySameAtEndAndBegining. - self assert: collection first = collection last. + self assert: collection first equals: collection last. self deny: collection first == collection last. - 1 to: collection size do: [ :i | + collection withIndexDo: [:el :i | i > 1 & (i < collection size) ifTrue: [ self deny: (collection at: i) = collection first ] ]. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals but are not the same object" @@ -50,16 +51,16 @@ TIndexAccessForMultipliness >> testIdentityIndexOfDuplicate [ TIndexAccessForMultipliness >> testIdentityIndexOfIAbsentDuplicate [ | collection element elementCopy | - collection := self collectionWithNonIdentitySameAtEndAndBegining . + collection := self collectionWithNonIdentitySameAtEndAndBegining. element := collection last. elementCopy := element copy. - self deny: element == elementCopy . + self deny: element == elementCopy. self assert: (collection identityIndexOf: element - ifAbsent: [ 0 ]) = collection size. + ifAbsent: [ 0 ]) equals: collection size. self assert: (collection identityIndexOf: elementCopy - ifAbsent: [ 55 ]) = 55 + ifAbsent: [ 55 ]) equals: 55 ] { #category : #'tests - index accessing for multipliness' } @@ -71,7 +72,7 @@ TIndexAccessForMultipliness >> testIndexOfDuplicate [ " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'indexOf: should return the position of the first occurrence :'" - self assert: (collection indexOf: element) = 1 + self assert: (collection indexOf: element) equals: 1 ] { #category : #'tests - index accessing for multipliness' } @@ -85,7 +86,7 @@ TIndexAccessForMultipliness >> testIndexOfIfAbsentDuplicate [ 'indexOf:ifAbsent: should return the position of the first occurrence :'" self assert: (collection indexOf: element - ifAbsent: [ 55 ]) = 1 + ifAbsent: [ 55 ]) equals: 1 ] { #category : #'tests - index accessing for multipliness' } @@ -95,16 +96,16 @@ TIndexAccessForMultipliness >> testIndexOfStartingAtDuplicate [ collection := self collectionWithSameAtEndAndBegining. element := collection last. - " floatCollectionWithSameAtEndAndBegining first and last elements are equals - 'indexOf:ifAbsent:startingAt: should return the position of the first occurrence :'" + "floatCollectionWithSameAtEndAndBegining first and last elements are equals + 'indexOf:ifAbsent:startingAt:' should return the position of the first occurrence" self assert: (collection indexOf: element startingAt: 1 - ifAbsent: [ 55 ]) = 1. + ifAbsent: [ 55 ]) equals: 1. self assert: (collection indexOf: element startingAt: 2 - ifAbsent: [ 55 ]) = collection size + ifAbsent: [ 55 ]) equals: collection size ] { #category : #'tests - index accessing for multipliness' } @@ -116,24 +117,26 @@ TIndexAccessForMultipliness >> testLastIndexOfDuplicate [ " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf: should return the position of the last occurrence :'" - self assert: (collection lastIndexOf: element) = collection size + self assert: (collection lastIndexOf: element) equals: collection size ] { #category : #'tests - index accessing for multipliness' } TIndexAccessForMultipliness >> testLastIndexOfIfAbsentDuplicate [ + | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection first. - " floatCollectionWithSameAtEndAndBegining first and last elements are equals + "floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf: should return the position of the last occurrence :'" self assert: (collection lastIndexOf: element - ifAbsent: [ 55 ]) = collection size + ifAbsent: [ 55 ]) equals: collection size ] { #category : #'tests - index accessing for multipliness' } TIndexAccessForMultipliness >> testLastIndexOfStartingAtDuplicate [ + | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. @@ -143,9 +146,9 @@ TIndexAccessForMultipliness >> testLastIndexOfStartingAtDuplicate [ self assert: (collection lastIndexOf: element startingAt: collection size - ifAbsent: [ 55 ]) = collection size. + ifAbsent: [ 55 ]) equals: collection size. self assert: (collection lastIndexOf: element startingAt: collection size - 1 - ifAbsent: [ 55 ]) = 1 + ifAbsent: [ 55 ]) equals: 1 ] diff --git a/src/Collections-Tests/TIterateSequencedReadableTest.trait.st b/src/Collections-Tests/TIterateSequencedReadableTest.trait.st index 7537c828c73..e371e7bddac 100644 --- a/src/Collections-Tests/TIterateSequencedReadableTest.trait.st +++ b/src/Collections-Tests/TIterateSequencedReadableTest.trait.st @@ -20,20 +20,18 @@ TIterateSequencedReadableTest >> nonEmptyMoreThan1Element [ { #category : #'tests - fixture' } TIterateSequencedReadableTest >> test0FixtureIterateSequencedReadableTest [ - | res | - + | res | self nonEmptyMoreThan1Element. - self assert: self nonEmptyMoreThan1Element size > 1. - - + self assert: self nonEmptyMoreThan1Element size > 1. + self empty. - self assert: self empty isEmpty . + self assert: self empty isEmpty. res := true. self nonEmptyMoreThan1Element - detect: [ :each | (self nonEmptyMoreThan1Element occurrencesOf: each) > 1 ] + detect: [ :each | (self nonEmptyMoreThan1Element occurrencesOf: each) > 1 ] ifNone: [ res := false ]. - self assert: res = false. + self assert: res = false ] { #category : #'tests - iterate on sequenced reable collections' } @@ -48,7 +46,7 @@ TIterateSequencedReadableTest >> testAllButFirstDo [ [:i| self assert: (self nonEmptyMoreThan1Element at:(i +1))=(result at:i)]. - self assert: result size=(self nonEmptyMoreThan1Element size-1). + self assert: result size=(self nonEmptyMoreThan1Element size-1) ] { #category : #'tests - iterate on sequenced reable collections' } @@ -63,7 +61,7 @@ TIterateSequencedReadableTest >> testAllButLastDo [ [:i| self assert: (self nonEmptyMoreThan1Element at:(i ))=(result at:i)]. - self assert: result size=(self nonEmptyMoreThan1Element size-1). + self assert: result size=(self nonEmptyMoreThan1Element size-1) ] { #category : #'tests - iterate on sequenced reable collections' } @@ -82,12 +80,12 @@ TIterateSequencedReadableTest >> testCollectFromTo [ { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testDetectSequenced [ -" testing that detect keep the first element returning true for sequenceable collections " + "Testing that detect keep the first element returning true for sequenceable collections" | element result | - element := self nonEmptyMoreThan1Element at:1. - result:=self nonEmptyMoreThan1Element detect: [:each | each notNil ]. - self assert: result = element. + element := self nonEmptyMoreThan1Element at: 1. + result := self nonEmptyMoreThan1Element detect: [:each | each notNil ]. + self assert: result equals: element ] { #category : #'tests - iterate on sequenced reable collections' } @@ -98,54 +96,52 @@ TIterateSequencedReadableTest >> testDo [ TIterateSequencedReadableTest >> testFindFirst [ | element result | - element := self nonEmptyMoreThan1Element at:1. - result:=self nonEmptyMoreThan1Element findFirst: [:each | each =element]. + element := self nonEmptyMoreThan1Element at: 1. + result := self nonEmptyMoreThan1Element findFirst: [:each | each = element]. - self assert: result=1. + self assert: result equals: 1 ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testFindFirstNotIn [ - | result | + | result | + result := self empty findFirst: [:each | true ]. - result:=self empty findFirst: [:each | true]. - - self assert: result=0. + self assert: result equals: 0 ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testFindLast [ | element result | - element := self nonEmptyMoreThan1Element at:self nonEmptyMoreThan1Element size. - result:=self nonEmptyMoreThan1Element findLast: [:each | each =element]. + element := self nonEmptyMoreThan1Element at: self nonEmptyMoreThan1Element size. + result := self nonEmptyMoreThan1Element findLast: [:each | each =element]. - self assert: result=self nonEmptyMoreThan1Element size. + self assert: result equals: self nonEmptyMoreThan1Element size ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testFindLastNotIn [ - | result | + | result | + result := self empty findFirst: [:each | true ]. - result:=self empty findFirst: [:each | true]. - - self assert: result=0. + self assert: result equals: 0 ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testFromToDo [ | result | - result:= OrderedCollection new. + result:= OrderedCollection new. - self nonEmptyMoreThan1Element from: 1 to: (self nonEmptyMoreThan1Element size -1) do: [:each | result add: each]. + self nonEmptyMoreThan1Element from: 1 to: (self nonEmptyMoreThan1Element size -1) do: [:each | result add: each]. 1 to: (self nonEmptyMoreThan1Element size -1) do: - [:i| - self assert: (self nonEmptyMoreThan1Element at:i )=(result at:i)]. - self assert: result size=(self nonEmptyMoreThan1Element size-1). + [:i | self assert: (self nonEmptyMoreThan1Element at:i) = (result at:i) ]. + + self assert: result size = (self nonEmptyMoreThan1Element size - 1). ] { #category : #'tests - iterate on sequenced reable collections' } @@ -161,7 +157,7 @@ TIterateSequencedReadableTest >> testKeysAndValuesDo [ [:i| self assert: (result at:i)=((self nonEmptyMoreThan1Element at:i)+i)]" | indexes elements | - indexes:= OrderedCollection new. + indexes := OrderedCollection new. elements := OrderedCollection new. self nonEmptyMoreThan1Element keysAndValuesDo: @@ -171,80 +167,80 @@ TIterateSequencedReadableTest >> testKeysAndValuesDo [ (1 to: self nonEmptyMoreThan1Element size )do: [ :i | - self assert: (indexes at: i) = i. - self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i). + self assert: (indexes at: i) equals: i. + self assert: (elements at: i) equals: (self nonEmptyMoreThan1Element at: i). ]. - self assert: indexes size = elements size. - self assert: indexes size = self nonEmptyMoreThan1Element size . + self assert: indexes size equals: elements size. + self assert: indexes size equals: self nonEmptyMoreThan1Element size ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testKeysAndValuesDoEmpty [ + | result | result:= OrderedCollection new. - self empty keysAndValuesDo: - [:i :value| - result add: (value+i)]. + self empty keysAndValuesDo: + [:i :value| result add: (value+i) ]. - self assert: result isEmpty . + self assert: result isEmpty ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testPairsCollect [ | index result | - index:=0. + index := 0. - result:=self nonEmptyMoreThan1Element pairsCollect: + result := self nonEmptyMoreThan1Element pairsCollect: [:each1 :each2 | - self assert: ( self nonEmptyMoreThan1Element indexOf: each2 ) = (index := index + 2). - (self nonEmptyMoreThan1Element indexOf: each2) = ((self nonEmptyMoreThan1Element indexOf: each1) + 1). - ]. + self assert: (self nonEmptyMoreThan1Element indexOf: each2 ) equals: (index := index + 2). + (self nonEmptyMoreThan1Element indexOf: each2) = ((self nonEmptyMoreThan1Element indexOf: each1) + 1)]. result do: - [:each | self assert: each = true]. + [:each | self assert: each equals: true ] ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testPairsDo [ + | index | index:=1. self nonEmptyMoreThan1Element pairsDo: [:each1 :each2 | - self assert:(self nonEmptyMoreThan1Element at:index)=each1. - self assert:(self nonEmptyMoreThan1Element at:(index+1))=each2. - index:=index+2]. + self assert: (self nonEmptyMoreThan1Element at:index) equals: each1. + self assert: (self nonEmptyMoreThan1Element at:(index+1)) equals: each2. + index := index + 2 ]. self nonEmptyMoreThan1Element size odd - ifTrue:[self assert: index=self nonEmptyMoreThan1Element size] - ifFalse:[self assert: index=(self nonEmptyMoreThan1Element size+1)]. + ifTrue:[ self assert: index equals: self nonEmptyMoreThan1Element size ] + ifFalse:[ self assert: index equals: (self nonEmptyMoreThan1Element size+1) ] ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testReverseDo [ | result | - result:= OrderedCollection new. + result := OrderedCollection new. self nonEmpty reverseDo: [: each | result add: each]. 1 to: result size do: [:i| - self assert: (result at: i)=(self nonEmpty at:(self nonEmpty size-i+1))]. + self assert: (result at: i)=(self nonEmpty at:(self nonEmpty size-i+1))] ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testReverseDoEmpty [ | result | - result:= OrderedCollection new. - self empty reverseDo: [: each | result add: each]. + result := OrderedCollection new. + self empty reverseDo: [: each | result add: each ]. - self assert: result isEmpty . + self assert: result isEmpty ] { #category : #'tests - iterate on sequenced reable collections' } @@ -259,9 +255,9 @@ TIterateSequencedReadableTest >> testReverseWithDo [ firstCollection reverseWith: secondCollection do: [:a :b | - self assert: (firstCollection at: index) equals: a. - self assert: (secondCollection at: index) equals: b. - ( index := index - 1).] + self assert: (firstCollection at: index) equals: a. + self assert: (secondCollection at: index) equals: b. + (index := index - 1)] @@ -283,13 +279,14 @@ TIterateSequencedReadableTest >> testWithCollect [ self assert: (secondCollection at: index) equals: b. b]. - 1 to: result size do:[: i | self assert: (result at:i)= (secondCollection at: i)]. - self assert: result size = secondCollection size. + result withIndexDo: [:el :i | self assert: (result at:i) equals: (secondCollection at: i)]. + self assert: result size = secondCollection size ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testWithCollectError [ - self should: [self nonEmptyMoreThan1Element with: self empty collect:[:a :b | ]] raise: Error. + + self should: [ self nonEmptyMoreThan1Element with: self empty collect:[:a :b | ]] raise: Error ] { #category : #'tests - iterate on sequenced reable collections' } @@ -303,9 +300,9 @@ TIterateSequencedReadableTest >> testWithDo [ firstCollection with: secondCollection do: [:a :b | - ( index := index + 1). + index := index + 1. self assert: (firstCollection at: index) equals: a. - self assert: (secondCollection at: index) equals: b.] + self assert: (secondCollection at: index) equals: b ] ] @@ -313,7 +310,7 @@ TIterateSequencedReadableTest >> testWithDo [ { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testWithDoError [ - self should: [self nonEmptyMoreThan1Element with: self empty do:[:a :b | ]] raise: Error. + self should: [self nonEmptyMoreThan1Element with: self empty do:[:a :b | ]] raise: Error ] { #category : #'tests - iterate on sequenced reable collections' } @@ -323,38 +320,32 @@ TIterateSequencedReadableTest >> testWithIndexCollect [ index := 0. collection := self nonEmptyMoreThan1Element . result := collection withIndexCollect: [:each :i | - self assert: i = (index := index + 1). - self assert: i = (collection indexOf: each) . - each] . + self assert: i equals: (index := index + 1). + self assert: i equals: (collection indexOf: each). + each ]. - 1 to: result size do:[: i | self assert: (result at:i)= (collection at: i)]. - self assert: result size = collection size. + result withIndexDo: [:el :i | self assert: (result at:i) equals: (collection at: i)]. + self assert: result size equals: collection size ] { #category : #'tests - iterate on sequenced reable collections' } TIterateSequencedReadableTest >> testWithIndexDo [ - - "| result | - result:=Array new: self nonEmptyMoreThan1Element size. - self nonEmptyMoreThan1Element withIndexDo: [:each :i | result at:i put:(each+i)]. - - 1 to: result size do:[: i | self assert: (result at:i)= ((self nonEmptyMoreThan1Element at: i) + i)]" + | indexes elements | indexes:= OrderedCollection new. elements := OrderedCollection new. - self nonEmptyMoreThan1Element withIndexDo: + self nonEmptyMoreThan1Element withIndexDo: [:value :i | - indexes add: (i). - elements add: value]. + indexes add: (i). + elements add: value ]. - (1 to: self nonEmptyMoreThan1Element size )do: - [ :i | - self assert: (indexes at: i) = i. - self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i). - ]. + self nonEmptyMoreThan1Element withIndexDo: + [:el :i | + self assert: (indexes at: i) equals: i. + self assert: (elements at: i) equals: el ]. - self assert: indexes size = elements size. - self assert: indexes size = self nonEmptyMoreThan1Element size . + self assert: indexes size equals: elements size. + self assert: indexes size equals: self nonEmptyMoreThan1Element size ] diff --git a/src/Collections-Tests/TOccurrencesForMultiplinessTest.trait.st b/src/Collections-Tests/TOccurrencesForMultiplinessTest.trait.st index 012d94ba9a1..d56a2121db7 100644 --- a/src/Collections-Tests/TOccurrencesForMultiplinessTest.trait.st +++ b/src/Collections-Tests/TOccurrencesForMultiplinessTest.trait.st @@ -39,6 +39,7 @@ TOccurrencesForMultiplinessTest >> empty [ { #category : #'tests - fixture' } TOccurrencesForMultiplinessTest >> test0FixtureOccurrencesForMultiplinessTest [ + | cpt anElement collection | self collectionWithEqualElements. self collectionWithEqualElements. @@ -55,6 +56,7 @@ TOccurrencesForMultiplinessTest >> test0FixtureOccurrencesForMultiplinessTest [ { #category : #'tests - fixture' } TOccurrencesForMultiplinessTest >> test0FixtureOccurrencesTest [ + | tmp | self empty. self assert: self empty isEmpty. @@ -74,29 +76,31 @@ TOccurrencesForMultiplinessTest >> testOccurrencesOf [ | collection | collection := self collectionWithoutEqualElements . - collection do: [ :each | self assert: (collection occurrencesOf: each) = 1 ]. + collection do: [ :each | self assert: (collection occurrencesOf: each) equals: 1 ] ] { #category : #'tests - occurrencesOf' } TOccurrencesForMultiplinessTest >> testOccurrencesOfEmpty [ + | result | result := self empty occurrencesOf: (self collectionWithoutEqualElements anyOne). - self assert: result = 0 + self assert: result equals: 0 ] { #category : #'tests - occurrencesOf for multipliness' } TOccurrencesForMultiplinessTest >> testOccurrencesOfForMultipliness [ -| collection elem | -collection := self collectionWithEqualElements . -elem := self elementTwiceInForOccurrences . + | collection elem | + collection := self collectionWithEqualElements. + elem := self elementTwiceInForOccurrences. -self assert: (collection occurrencesOf: elem ) = 2. + self assert: (collection occurrencesOf: elem ) equals: 2. ] { #category : #'tests - occurrencesOf' } TOccurrencesForMultiplinessTest >> testOccurrencesOfNotIn [ + | result | result := self collectionWithoutEqualElements occurrencesOf: self elementNotInForOccurrences. - self assert: result = 0 + self assert: result equals: 0 ] diff --git a/src/Collections-Tests/TPrintOnSequencedTest.trait.st b/src/Collections-Tests/TPrintOnSequencedTest.trait.st index 8fd4beb34d1..7deca3a0f40 100644 --- a/src/Collections-Tests/TPrintOnSequencedTest.trait.st +++ b/src/Collections-Tests/TPrintOnSequencedTest.trait.st @@ -15,6 +15,7 @@ TPrintOnSequencedTest >> nonEmpty [ { #category : #'tests - fixture' } TPrintOnSequencedTest >> test0FixturePrintTest [ + self nonEmpty ] @@ -22,66 +23,63 @@ TPrintOnSequencedTest >> test0FixturePrintTest [ TPrintOnSequencedTest >> testPrintElementsOn [ | aStream result allElementsAsString | - result:=''. - aStream:= ReadWriteStream on: result. + result := ''. + aStream := ReadWriteStream on: result. - self nonEmpty printElementsOn: aStream . - allElementsAsString:=(result findBetweenSubstrings: ' ' ). - 1 to: allElementsAsString size do: - [:i | - self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString). - ]. + self nonEmpty printElementsOn: aStream. + allElementsAsString:=(result findBetweenSubstrings: ' '). + allElementsAsString withIndexDo: + [:el :i | self assert: el equals: ((self nonEmpty at: i)asString) ] ] { #category : #'tests - printing' } TPrintOnSequencedTest >> testPrintNameOn [ | aStream result | - result:=''. - aStream:= ReadWriteStream on: result. + result := ''. + aStream := ReadWriteStream on: result. - self nonEmpty printNameOn: aStream . + self nonEmpty printNameOn: aStream. Transcript show: result asString. self nonEmpty class name first isVowel - ifTrue:[ self assert: aStream contents =('an ',self nonEmpty class name ) ] - ifFalse:[self assert: aStream contents =('a ',self nonEmpty class name)]. + ifTrue:[ self assert: aStream contents equals: ('an ',self nonEmpty class name ) ] + ifFalse:[ self assert: aStream contents equals: ('a ',self nonEmpty class name)]. ] { #category : #'tests - printing' } TPrintOnSequencedTest >> testPrintOn [ + | aStream result allElementsAsString | - result:=''. - aStream:= ReadWriteStream on: result. + result := ''. + aStream := ReadWriteStream on: result. self nonEmpty printOn: aStream . allElementsAsString:=(result findBetweenSubstrings: ' ' ). - 1 to: allElementsAsString size do: - [:i | + allElementsAsString withIndexDo: + [:el :i | i=1 ifTrue:[ - self accessCollection class name first isVowel - ifTrue:[self assert: (allElementsAsString at:i)='an' ] - ifFalse:[self assert: (allElementsAsString at:i)='a'].]. + self accessCollection class name first isVowel + ifTrue:[self assert: el equals: 'an' ] + ifFalse:[self assert: el equals: 'a'].]. i=2 - ifTrue:[self assert: (allElementsAsString at:i)=self accessCollection class name]. + ifTrue:[self assert: el equals: self accessCollection class name]. i>2 - ifTrue:[self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString).]. - ]. + ifTrue:[self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString)]] ] { #category : #'tests - printing' } TPrintOnSequencedTest >> testPrintOnDelimiter [ + | aStream result allElementsAsString | - result:=''. - aStream:= ReadWriteStream on: result. + result := ''. + aStream := ReadWriteStream on: result. - self nonEmpty printOn: aStream delimiter: ', ' . + self nonEmpty printOn: aStream delimiter: ', '. - allElementsAsString:=(result findBetweenSubstrings: ', ' ). - 1 to: allElementsAsString size do: - [:i | - self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString). - ]. + allElementsAsString := (result findBetweenSubstrings: ', ' ). + allElementsAsString withIndexDo: + [:el :i | self assert: el equals: ((self nonEmpty at:i)asString)] ] { #category : #'tests - printing' } @@ -93,16 +91,15 @@ TPrintOnSequencedTest >> testPrintOnDelimiterLast [ self nonEmpty printOn: aStream delimiter: ', ' last: 'and'. - allElementsAsString:=(result findBetweenSubstrings: ', ' ). - 1 to: allElementsAsString size do: - [:i | + allElementsAsString:=(result findBetweenSubstrings: ', '). + allElementsAsString withIndexDo: + [:el :i | i<(allElementsAsString size-1 ) - ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString)]. + ifTrue: [self assert: (allElementsAsString at:i) equals: ((self nonEmpty at:i)asString)]. i=(allElementsAsString size-1) - ifTrue:[ self deny: (allElementsAsString at:i)=('and')asString]. + ifTrue:[ self deny: (allElementsAsString at:i) equals: ('and')asString]. i=(allElementsAsString size) - ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)]. - ]. + ifTrue: [self assert: (allElementsAsString at:i) equals: ((self nonEmpty at:(i-1))asString)]] ] { #category : #'tests - printing' } diff --git a/src/Collections-Tests/TRemoveByIndexTest.trait.st b/src/Collections-Tests/TRemoveByIndexTest.trait.st index daeffb0225d..cb658de2f58 100644 --- a/src/Collections-Tests/TRemoveByIndexTest.trait.st +++ b/src/Collections-Tests/TRemoveByIndexTest.trait.st @@ -20,6 +20,7 @@ self explicitRequirement { #category : #'tests - fixture' } TRemoveByIndexTest >> test0FixtureRemoveByIndexTest [ + self collectionWith5Elements. self assert: self collectionWith5Elements size = 5 ] @@ -27,96 +28,94 @@ TRemoveByIndexTest >> test0FixtureRemoveByIndexTest [ { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveAt [ -| collection element result oldSize | -collection := self collectionWith5Elements . -element := collection at: 3. -oldSize := collection size. + | collection element result oldSize | + collection := self collectionWith5Elements . + element := collection at: 3. + oldSize := collection size. -result := collection removeAt: 3. -self assert: result = element . -self assert: collection size = (oldSize - 1). + result := collection removeAt: 3. + self assert: result equals: element. + self assert: collection size equals: (oldSize - 1). ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveAtNotPresent [ -| | -self should: [self empty removeAt: 2] raise: Error. + self should: [self empty removeAt: 2] raise: Error ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveFirst [ -| collection element result oldSize | -collection := self collectionWith5Elements . -element := collection first. -oldSize := collection size. + | collection element result oldSize | + collection := self collectionWith5Elements. + element := collection first. + oldSize := collection size. -result := collection removeFirst. -self assert: result = element . -self assert: collection size = (oldSize - 1). + result := collection removeFirst. + self assert: result equals: element . + self assert: collection size equals: (oldSize - 1) ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveFirstNElements [ -| collection elements result oldSize | -collection := self collectionWith5Elements . -elements := {collection first. collection at:2}. -oldSize := collection size. + | collection elements result oldSize | + collection := self collectionWith5Elements . + elements := { collection first. collection at:2 }. + oldSize := collection size. -result := collection removeFirst: 2. -self assert: result = elements . -self assert: collection size = (oldSize - 2). + result := collection removeFirst: 2. + self assert: result equals: elements . + self assert: collection size equals: (oldSize - 2) ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveFirstNElementsNotPresent [ -self should: [self empty removeFirst: 2] raise: Error. + self should: [self empty removeFirst: 2] raise: Error ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveFirstNotPresent [ -self should: [self empty removeFirst] raise: Error. + self should: [self empty removeFirst] raise: Error ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveLast [ -| collection element result oldSize | -collection := self collectionWith5Elements . -element := collection last. -oldSize := collection size. + | collection element result oldSize | + collection := self collectionWith5Elements . + element := collection last. + oldSize := collection size. -result := collection removeLast. -self assert: result = element . -self assert: collection size = (oldSize - 1). + result := collection removeLast. + self assert: result equals: element . + self assert: collection size equals: (oldSize - 1) ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveLastNElements [ -| collection result oldSize elements | -collection := self collectionWith5Elements . -elements := { (collection at: (4)). collection last. }. -oldSize := collection size. - + | collection result oldSize elements | + collection := self collectionWith5Elements . + elements := { collection at: 4. collection last }. + oldSize := collection size. -result := (collection removeLast: 2). -self assert: result = elements. -self assert: collection size = (oldSize - 2). + result := (collection removeLast: 2). + self assert: result equals: elements. + self assert: collection size equals: (oldSize - 2) ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveLastNElementsNElements [ -self should: [self empty removeLast: 2] raise: Error. + self should: [self empty removeLast: 2] raise: Error ] { #category : #'tests - removing by index' } TRemoveByIndexTest >> testRemoveLastNotPresent [ -self should: [self empty removeLast] raise: Error. + self should: [self empty removeLast] raise: Error ] diff --git a/src/Collections-Tests/TRemoveTest.trait.st b/src/Collections-Tests/TRemoveTest.trait.st index 7220c9f1e32..aac5f1f376e 100644 --- a/src/Collections-Tests/TRemoveTest.trait.st +++ b/src/Collections-Tests/TRemoveTest.trait.st @@ -25,6 +25,7 @@ TRemoveTest >> nonEmptyWithoutEqualElements [ { #category : #'tests - fixture' } TRemoveTest >> test0FixtureTRemoveTest [ + | duplicate | self empty. self nonEmptyWithoutEqualElements. @@ -58,6 +59,7 @@ TRemoveTest >> testRemoveAllError [ | el aSubCollection | el := self elementNotIn. aSubCollection := self nonEmptyWithoutEqualElements copyWith: el. + self should: [ | res | res := self nonEmptyWithoutEqualElements removeAll: aSubCollection ] raise: Error @@ -66,12 +68,13 @@ TRemoveTest >> testRemoveAllError [ { #category : #'tests - remove' } TRemoveTest >> testRemoveAllFoundIn [ - | el aSubCollection res | + | el aSubCollection | el := self nonEmptyWithoutEqualElements anyOne. aSubCollection := (self nonEmptyWithoutEqualElements copyWithout: el) copyWith: self elementNotIn. - res := self nonEmptyWithoutEqualElements removeAllFoundIn: aSubCollection. - self assert: self nonEmptyWithoutEqualElements size = 1. - self nonEmptyWithoutEqualElements do: [ :each | self assert: each = el ] + self nonEmptyWithoutEqualElements removeAllFoundIn: aSubCollection. + + self assert: self nonEmptyWithoutEqualElements size equals: 1. + self nonEmptyWithoutEqualElements do: [ :each | self assert: each equals: el ] ] { #category : #'tests - remove' } @@ -81,8 +84,9 @@ TRemoveTest >> testRemoveAllSuchThat [ el := self nonEmptyWithoutEqualElements anyOne. aSubCollection := self nonEmptyWithoutEqualElements copyWithout: el. self nonEmptyWithoutEqualElements removeAllSuchThat: [ :each | aSubCollection includes: each ]. - self assert: self nonEmptyWithoutEqualElements size = 1. - self nonEmptyWithoutEqualElements do: [ :each | self assert: each = el ] + + self assert: self nonEmptyWithoutEqualElements size equals: 1. + self nonEmptyWithoutEqualElements do: [ :each | self assert: each equals: el ] ] { #category : #'tests - remove' } @@ -99,7 +103,7 @@ TRemoveTest >> testRemoveElementReallyRemovesElement [ | size | size := self nonEmptyWithoutEqualElements size. self nonEmptyWithoutEqualElements remove: self nonEmptyWithoutEqualElements anyOne. - self assert: size - 1 = self nonEmptyWithoutEqualElements size + self assert: size - 1 equals: self nonEmptyWithoutEqualElements size ] { #category : #'tests - remove' } @@ -117,5 +121,5 @@ TRemoveTest >> testRemoveIfAbsent [ | el res | el := self elementNotIn. res := self nonEmptyWithoutEqualElements remove: el ifAbsent: [ 33 ]. - self assert: res = 33 + self assert: res equals: 33 ] diff --git a/src/Collections-Tests/TSequencedElementAccessTest.trait.st b/src/Collections-Tests/TSequencedElementAccessTest.trait.st index 25b70a5d465..86b0184e951 100644 --- a/src/Collections-Tests/TSequencedElementAccessTest.trait.st +++ b/src/Collections-Tests/TSequencedElementAccessTest.trait.st @@ -33,6 +33,7 @@ TSequencedElementAccessTest >> subCollectionNotIn [ { #category : #'tests - fixture' } TSequencedElementAccessTest >> test0FixtureSequencedElementAccessTest [ + self moreThan4Elements. self assert: self moreThan4Elements size >= 4. self subCollectionNotIn. @@ -76,6 +77,7 @@ TSequencedElementAccessTest >> testAt [ self assert: (self accessCollection at: 1) = 1. self assert: (self accessCollection at: 2) = 2. " + | index | index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements at: index) = self elementInForElementAccessing @@ -97,6 +99,7 @@ TSequencedElementAccessTest >> testAtAll [ { #category : #'tests - element accessing' } TSequencedElementAccessTest >> testAtIfAbsent [ + | absent | absent := false. self moreThan4Elements @@ -115,12 +118,7 @@ TSequencedElementAccessTest >> testAtLast [ | index | self assert: (self moreThan4Elements atLast: 1) = self moreThan4Elements last. - "tmp:=1. - self do: - [:each | - each =self elementInForIndexAccessing - ifTrue:[index:=tmp]. - tmp:=tmp+1]." + index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements atLast: index) = (self moreThan4Elements at: self moreThan4Elements size - index + 1) ] @@ -165,9 +163,10 @@ TSequencedElementAccessTest >> testAtPin [ { #category : #'tests - element accessing' } TSequencedElementAccessTest >> testAtRandom [ + | result | - result := self nonEmpty atRandom . - self assert: (self nonEmpty includes: result). + result := self nonEmpty atRandom. + self assert: (self nonEmpty includes: result) ] { #category : #'tests - element accessing' } @@ -176,6 +175,7 @@ TSequencedElementAccessTest >> testAtWrap [ self assert: (self accessCollection at: 1) = 1. self assert: (self accessCollection at: 2) = 2. " + | index | index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: index) = self elementInForElementAccessing. @@ -202,6 +202,7 @@ TSequencedElementAccessTest >> testBeforeIfAbsent [ self assert: (self moreThan4Elements before: (self moreThan4Elements at: 1) ifAbsent: [ 99 ]) = 99. + self assert: (self moreThan4Elements before: (self moreThan4Elements at: 2) ifAbsent: [ 99 ]) = (self moreThan4Elements at: 1) @@ -210,20 +211,20 @@ TSequencedElementAccessTest >> testBeforeIfAbsent [ { #category : #'tests - element accessing' } TSequencedElementAccessTest >> testFirstSecondThird [ - self assert: self moreThan4Elements first = (self moreThan4Elements at: 1). - self assert: self moreThan4Elements second = (self moreThan4Elements at: 2). - self assert: self moreThan4Elements third = (self moreThan4Elements at: 3). - self assert: self moreThan4Elements fourth = (self moreThan4Elements at: 4) + self assert: self moreThan4Elements first equals: (self moreThan4Elements at: 1). + self assert: self moreThan4Elements second equals: (self moreThan4Elements at: 2). + self assert: self moreThan4Elements third equals: (self moreThan4Elements at: 3). + self assert: self moreThan4Elements fourth equals: (self moreThan4Elements at: 4) ] { #category : #'tests - element accessing' } TSequencedElementAccessTest >> testLast [ - self assert: self moreThan4Elements last = (self moreThan4Elements at: self moreThan4Elements size) + self assert: self moreThan4Elements last equals: (self moreThan4Elements at: self moreThan4Elements size) ] { #category : #'tests - element accessing' } TSequencedElementAccessTest >> testMiddle [ - self assert: self moreThan4Elements middle = (self moreThan4Elements at: self moreThan4Elements size // 2 + 1) + self assert: self moreThan4Elements middle equals: (self moreThan4Elements at: self moreThan4Elements size // 2 + 1) ] diff --git a/src/Collections-Tests/TSequencedStructuralEqualityTest.trait.st b/src/Collections-Tests/TSequencedStructuralEqualityTest.trait.st index 626d8ac17e6..60c60710038 100644 --- a/src/Collections-Tests/TSequencedStructuralEqualityTest.trait.st +++ b/src/Collections-Tests/TSequencedStructuralEqualityTest.trait.st @@ -22,11 +22,13 @@ TSequencedStructuralEqualityTest >> nonEmpty [ { #category : #'tests - fixture' } TSequencedStructuralEqualityTest >> test0TSequencedStructuralEqualityTest [ + self nonEmpty at: 1 "Ensures #nonEmpty is sequenceable" ] { #category : #'tests - fixture' } TSequencedStructuralEqualityTest >> test0TStructuralEqualityTest [ + self empty. self nonEmpty. self assert: self empty isEmpty. @@ -36,7 +38,7 @@ TSequencedStructuralEqualityTest >> test0TStructuralEqualityTest [ { #category : #'tests - equality' } TSequencedStructuralEqualityTest >> testEqualSign [ - self deny: (self empty = self nonEmpty). + self deny: (self empty = self nonEmpty) ] { #category : #'tests - equality' } @@ -44,15 +46,15 @@ TSequencedStructuralEqualityTest >> testEqualSignForSequenceableCollections [ self deny: (self nonEmpty = self nonEmpty asSet). self deny: (self nonEmpty reversed = self nonEmpty). - self deny: (self nonEmpty = self nonEmpty reversed). + self deny: (self nonEmpty = self nonEmpty reversed) ] { #category : #'tests - equality' } TSequencedStructuralEqualityTest >> testEqualSignIsTrueForEmptyButNonIdenticalCollections [ - self assert: (self empty = self empty copy). - self assert: (self empty copy = self empty). - self assert: (self empty copy = self empty copy). + self assert: self empty equals: self empty copy. + self assert: self empty copy equals: self empty. + self assert: self empty copy equals: self empty copy ] @@ -60,20 +62,20 @@ TSequencedStructuralEqualityTest >> testEqualSignIsTrueForEmptyButNonIdenticalCo { #category : #'tests - equality' } TSequencedStructuralEqualityTest >> testEqualSignIsTrueForNonIdenticalButEqualCollections [ - self assert: (self empty = self empty copy). - self assert: (self empty copy = self empty). - self assert: (self empty copy = self empty copy). + self assert: self empty equals: self empty copy. + self assert: self empty copy equals: self empty. + self assert: self empty copy equals: self empty copy. - self assert: (self nonEmpty = self nonEmpty copy). - self assert: (self nonEmpty copy = self nonEmpty). - self assert: (self nonEmpty copy = self nonEmpty copy). + self assert: self nonEmpty equals: self nonEmpty copy. + self assert: self nonEmpty copy equals: self nonEmpty. + self assert: self nonEmpty copy equals: self nonEmpty copy ] { #category : #'tests - equality' } TSequencedStructuralEqualityTest >> testEqualSignOfIdenticalCollectionObjects [ - self assert: (self empty = self empty). - self assert: (self nonEmpty = self nonEmpty). + self assert: self empty equals: self empty. + self assert: self nonEmpty equals: self nonEmpty ] @@ -83,7 +85,7 @@ TSequencedStructuralEqualityTest >> testHasEqualElements [ self deny: (self empty hasEqualElements: self nonEmpty). self deny: (self nonEmpty hasEqualElements: self nonEmpty asSet). self deny: (self nonEmpty reversed hasEqualElements: self nonEmpty). - self deny: (self nonEmpty hasEqualElements: self nonEmpty reversed). + self deny: (self nonEmpty hasEqualElements: self nonEmpty reversed) ] { #category : #'tests - equality' } @@ -95,13 +97,13 @@ TSequencedStructuralEqualityTest >> testHasEqualElementsIsTrueForNonIdenticalBut self assert: (self nonEmpty hasEqualElements: self nonEmpty copy). self assert: (self nonEmpty copy hasEqualElements: self nonEmpty). - self assert: (self nonEmpty copy hasEqualElements: self nonEmpty copy). + self assert: (self nonEmpty copy hasEqualElements: self nonEmpty copy) ] { #category : #'tests - equality' } TSequencedStructuralEqualityTest >> testHasEqualElementsOfIdenticalCollectionObjects [ self assert: (self empty hasEqualElements: self empty). - self assert: (self nonEmpty hasEqualElements: self nonEmpty). + self assert: (self nonEmpty hasEqualElements: self nonEmpty) ] diff --git a/src/Collections-Tests/TSetArithmetic.trait.st b/src/Collections-Tests/TSetArithmetic.trait.st index f51263cb838..1831b8e700f 100644 --- a/src/Collections-Tests/TSetArithmetic.trait.st +++ b/src/Collections-Tests/TSetArithmetic.trait.st @@ -45,11 +45,13 @@ TSetArithmetic >> nonEmpty [ { #category : #'tests - set arithmetic' } TSetArithmetic >> numberOfSimilarElementsInIntersection [ + ^ self collection occurrencesOf: self anotherElementOrAssociationIn ] { #category : #'tests - fixture' } TSetArithmetic >> test0FixtureSetAritmeticTest [ + self collection. self deny: self collection isEmpty. self nonEmpty. @@ -69,17 +71,17 @@ TSetArithmetic >> testDifference [ self assert: (self collectionWithoutEqualElements difference: self collectionWithoutEqualElements) isEmpty. self assert: (self empty difference: self collectionWithoutEqualElements) isEmpty. difference := (self collectionWithoutEqualElements difference: self empty). - self assert: difference size = self collectionWithoutEqualElements size. + self assert: difference size = self collectionWithoutEqualElements size. self collectionWithoutEqualElements do: [ :each | - self assert: (difference includes: each)]. + self assert: (difference includes: each) ]. ] { #category : #'tests - set arithmetic' } TSetArithmetic >> testDifferenceWithNonNullIntersection [ - "Answer the set theoretic difference of two collections." - " #(1 2 3) difference: #(2 4) - -> #(1 3)" + "Answer the set theoretic difference of two collections. + #(1 2 3) difference: #(2 4) -> #(1 3)" + | res overlapping | overlapping := self collectionClass with: self anotherElementOrAssociationNotIn @@ -110,6 +112,7 @@ TSetArithmetic >> testDifferenceWithSeparateCollection [ { #category : #'tests - set arithmetic' } TSetArithmetic >> testIntersectionBasic [ + | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self deny: inter isEmpty. @@ -122,8 +125,8 @@ TSetArithmetic >> testIntersectionEmpty [ | inter | inter := self empty intersection: self empty. self assert: inter isEmpty. - inter := self empty intersection: self collection . - self assert: inter = self empty. + inter := self empty intersection: self collection. + self assert: inter equals: self empty ] @@ -131,8 +134,8 @@ TSetArithmetic >> testIntersectionEmpty [ TSetArithmetic >> testIntersectionItself [ | result | - result := (self collectionWithoutEqualElements intersection: self collectionWithoutEqualElements). - self assert: result size = self collectionWithoutEqualElements size. + result := self collectionWithoutEqualElements intersection: self collectionWithoutEqualElements. + self assert: result size equals: self collectionWithoutEqualElements size. self collectionWithoutEqualElements do: [ :each| self assert: (result includes: each) ]. @@ -143,7 +146,7 @@ TSetArithmetic >> testIntersectionTwoSimilarElementsInIntersection [ | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). - self assert: (self collection occurrencesOf: self anotherElementOrAssociationIn) = self numberOfSimilarElementsInIntersection. + self assert: (self collection occurrencesOf: self anotherElementOrAssociationIn) equals: self numberOfSimilarElementsInIntersection. self assert: (inter includes: self anotherElementOrAssociationIn value) ] diff --git a/src/Collections-Tests/TSubCollectionAccess.trait.st b/src/Collections-Tests/TSubCollectionAccess.trait.st index 196d2cabc49..c482a51f7b1 100644 --- a/src/Collections-Tests/TSubCollectionAccess.trait.st +++ b/src/Collections-Tests/TSubCollectionAccess.trait.st @@ -14,6 +14,7 @@ TSubCollectionAccess >> moreThan3Elements [ { #category : #'tests - fixture' } TSubCollectionAccess >> test0FixtureSubcollectionAccessTest [ + self moreThan3Elements. self assert: self moreThan3Elements size > 2 ] @@ -47,7 +48,7 @@ TSubCollectionAccess >> testAllButLast [ col := self moreThan3Elements. abf := col allButLast. self deny: abf last = col last. - self assert: abf size + 1 = col size + self assert: abf size + 1 equals: col size ] { #category : #'tests - subcollections access' } @@ -67,8 +68,9 @@ TSubCollectionAccess >> testFirstNElements [ | result | result := self moreThan3Elements first: self moreThan3Elements size - 1. - 1 to: result size do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i) ]. - self assert: result size = (self moreThan3Elements size - 1). + result withIndexDo: [:el :i | self assert: el equals: (self moreThan3Elements at: i) ]. + + self assert: result size equals: (self moreThan3Elements size - 1). self should: [ self moreThan3Elements first: self moreThan3Elements size + 1 ] raise: SubscriptOutOfBounds ] @@ -77,10 +79,8 @@ TSubCollectionAccess >> testLastNElements [ | result | result := self moreThan3Elements last: self moreThan3Elements size - 1. - 1 - to: result size - do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i + 1) ]. - self assert: result size = (self moreThan3Elements size - 1). + result withIndexDo: [:el :i | self assert: el equals: (self moreThan3Elements at: i + 1) ]. + self assert: result size equals: (self moreThan3Elements size - 1). self should: [ self moreThan3Elements last: self moreThan3Elements size + 1 ] raise: Error