[squeak-dev] The Trunk: CollectionsTests-pre.306.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Apr 30 18:00:43 UTC 2019


Patrick Rein uploaded a new version of CollectionsTests to project The Trunk:
http://source.squeak.org/trunk/CollectionsTests-pre.306.mcz

==================== Summary ====================

Name: CollectionsTests-pre.306
Author: pre
Time: 30 April 2019, 7:59:37.201906 pm
UUID: 845c12d6-06a6-c641-b74b-b20354dd578e
Ancestors: CollectionsTests-nice.305

Recategorizes test methods in CollectionsTests

=============== Diff against CollectionsTests-nice.305 ===============

Item was changed:
+ ----- Method: ArrayTest>>testEmpty (in category 'tests') -----
- ----- Method: ArrayTest>>testEmpty (in category 'testing') -----
  testEmpty
  
  	self
  		assert: 0
  		equals: Array empty size
  		description: 'The empty Array should be empty indeed';
  		
  		assert: Array
  		equals: Array empty species 
  		description: 'The empty Array should be an Array';
  		
  		assert: Array empty
  		identical: Array empty 
  		description: 'The empty Array should be canonical';
  		
  		yourself
  		
  		
  !

Item was changed:
+ ----- Method: ArrayTest>>testIsArray (in category 'tests') -----
- ----- Method: ArrayTest>>testIsArray (in category 'testing') -----
  testIsArray
  	
  	self assert: example1 isArray!

Item was changed:
+ ----- Method: ArrayTest>>testIsLiteral (in category 'tests') -----
- ----- Method: ArrayTest>>testIsLiteral (in category 'testing') -----
  testIsLiteral
  	"We work with a copy of literalArray, to avoid corrupting the code."
  	
  	| aLiteralArray |
  	aLiteralArray := literalArray copy.
  	self assert: aLiteralArray isLiteral.
  	aLiteralArray at: 1 put: self class.
  	self deny: aLiteralArray isLiteral.
  	self deny: (literalArray as: WeakArray) isLiteral description: 'instances of Array subclasses are not literal'.!

Item was changed:
+ ----- Method: ArrayTest>>testLiteralEqual (in category 'tests') -----
- ----- Method: ArrayTest>>testLiteralEqual (in category 'testing') -----
  testLiteralEqual
  	self
  		deny: (example1 literalEqual: example1 asIntegerArray)!

Item was changed:
+ ----- Method: ArrayTest>>testLiteralStoreOn (in category 'tests') -----
- ----- Method: ArrayTest>>testLiteralStoreOn (in category 'testing') -----
  testLiteralStoreOn
  	"Test that a literal Array is stored and evaluated back unchanged"
  	
  	| anArray |
  	anArray := {true. false. nil. #a. 'a'. $a. -1. 0. 1. Float pi. Float halfPi. Float halfPi negated.}.
  	anArray := anArray copyWith: anArray.
  	self assert: anArray isLiteral.
  	self assert: (Compiler evaluate: anArray storeString) = anArray.!

Item was changed:
+ ----- Method: ArrayTest>>testNewWithSize (in category 'tests') -----
- ----- Method: ArrayTest>>testNewWithSize (in category 'testing') -----
  testNewWithSize
  	|array|
  	array := Array new: 5.
  	self assert: array size = 5.
  	1 to: 5 do: [:index | self assert: (array at: index) isNil]!

Item was changed:
+ ----- Method: ArrayTest>>testPremultiply (in category 'tests') -----
- ----- Method: ArrayTest>>testPremultiply (in category 'testing') -----
  testPremultiply
  	self assert: example1 +* #(2 ) = #(2 4 6 8 10 ) !

Item was changed:
+ ----- Method: ArrayTest>>testPrinting (in category 'tests') -----
- ----- Method: ArrayTest>>testPrinting (in category 'testing') -----
  testPrinting
  	self assert: '#(1 true 3 #four)' equals: literalArray printString.
  	self
  		assert: (literalArray = (Compiler evaluate: literalArray printString))
  		description: 'Literal array doesn''t print as a string that when evaluated returns an equivalent Array'.
  	self assert: '{1 . true . (3/4) . Color black . (2 to: 4) . 5}' equals: selfEvaluatingArray printString.
  	self
  		assert: (selfEvaluatingArray = (Compiler evaluate: selfEvaluatingArray printString))
  		description: 'Array doesn''t print as a string that when evaluated returns an equivalent Array'.
  	self assert: '{1 . a Set(1)}' equals: nonSEArray1 printString.
  	self assert: '{#Array=>Array}' equals: nonSEarray2 printString.
  !

Item was changed:
+ ----- Method: Ascii85ConverterTest>>setUp (in category 'running') -----
- ----- Method: Ascii85ConverterTest>>setUp (in category 'initialize-release') -----
  setUp
  	self decoded: 'Hi There!!'.
  	self encoded: '<~8802GBOu3q+T~>'.!

Item was changed:
+ ----- Method: AssociationTest>>testStoreStringEvaluatesToEqualValue (in category 'tests') -----
- ----- Method: AssociationTest>>testStoreStringEvaluatesToEqualValue (in category 'as yet unclassified') -----
  testStoreStringEvaluatesToEqualValue
  	self assert: 1 -> 2 equals: (Compiler evaluate: (1 -> 2) storeString).
  	self assert: false -> true equals: (Compiler evaluate: (false -> true) storeString).
  	self assert: #foo -> #bar equals: (Compiler evaluate: (#foo -> #bar) storeString).
  	self assert: #foo -> #+ equals: (Compiler evaluate: (#foo -> #+) storeString).
  	self assert: #+ -> #bar equals: (Compiler evaluate: (#+ -> #bar) storeString).!

Item was changed:
+ ----- Method: BagTest>>testAdd (in category 'tests - basic') -----
- ----- Method: BagTest>>testAdd (in category 'basic tests') -----
  testAdd
  	"self run: #testAdd"
  	"self debug: #testAdd"
  
  	| aBag |
  	aBag := Bag new.
  	aBag add: 'a'.
  	aBag add: 'b'.
  	
  	self assert: aBag size = 2.
  	aBag add: 'a'.
  	self assert: aBag size = 3.
  	self assert: (aBag occurrencesOf: 'a') = 2
  	
  !

Item was changed:
+ ----- Method: BagTest>>testAddWithOccurrences (in category 'tests - basic') -----
- ----- Method: BagTest>>testAddWithOccurrences (in category 'basic tests') -----
  testAddWithOccurrences
  	"self debug:#testAddWithOccurrences"
  	
  	| aBag |
   	aBag := Bag new.	
  	aBag add: 'a' withOccurrences: 3.
  	self assert: (aBag size = 3).
  	
  	
  	
  	
  		
  !

Item was changed:
+ ----- Method: BagTest>>testAsBag (in category 'tests - basic') -----
- ----- Method: BagTest>>testAsBag (in category 'basic tests') -----
  testAsBag
  
  	| aBag |
   
  	aBag := Bag new.	
  	
  	self assert: aBag asBag = aBag.!

Item was changed:
+ ----- Method: BagTest>>testAsSet (in category 'tests - basic') -----
- ----- Method: BagTest>>testAsSet (in category 'basic tests') -----
  testAsSet
  
  	| aBag aSet |
  	aBag := Bag new.	
  	aBag add:'a' withOccurrences: 4.
  	aBag add:'b' withOccurrences: 2.
  	aSet := aBag asSet.
  	self assert: aSet size = 2.
  	self assert: (aSet occurrencesOf: 'a') = 1 
  	!

Item was changed:
+ ----- Method: BagTest>>testCopy (in category 'tests - basic') -----
- ----- Method: BagTest>>testCopy (in category 'basic tests') -----
  testCopy
  	"self run: #testCopy"
  	
  	| aBag newBag |
  	aBag := Bag new.
  	aBag add:'a' withOccurrences: 4.
  	aBag add:'b' withOccurrences: 2.
  	newBag := aBag copy.
  	self assert: newBag = newBag.
  	self assert: newBag asSet size = 2.!

Item was changed:
+ ----- Method: BagTest>>testOccurrencesOf (in category 'tests - basic') -----
- ----- Method: BagTest>>testOccurrencesOf (in category 'basic tests') -----
  testOccurrencesOf
  	"self debug: #testOccurrencesOf"
  
  	| aBag |
   	aBag := Bag new.	
  	aBag add: 'a' withOccurrences: 3.
  	aBag add: 'b'.
  	aBag add: 'b'.
  	aBag add: 'b'.
  	aBag add: 'b'.	
  	self assert: (aBag occurrencesOf:'a') = 3.
  	self assert: (aBag occurrencesOf:'b') = 4.
  	self assert: (aBag occurrencesOf:'c') = 0.
  	self assert: (aBag occurrencesOf: nil) =0.
  	aBag add: nil.
  	self assert: (aBag occurrencesOf: nil) =1.
  	!

Item was changed:
+ ----- Method: Base64MimeConverterTest>>setUp (in category 'running') -----
- ----- Method: Base64MimeConverterTest>>setUp (in category 'initialize-release') -----
  setUp
  	message := 'Hi There!!' readStream.
  !

Item was changed:
+ ----- Method: BitSetTest>>testBitManipulationAPI (in category 'tests') -----
- ----- Method: BitSetTest>>testBitManipulationAPI (in category 'testing') -----
  testBitManipulationAPI
  
  	#(0 8 16 24 32) do: [ :each |
  		self testBitManipulationAPI: each ]!

Item was changed:
+ ----- Method: BitSetTest>>testBitManipulationAPI: (in category 'tests') -----
- ----- Method: BitSetTest>>testBitManipulationAPI: (in category 'testing') -----
  testBitManipulationAPI: capacity
  
  	self initializeBitset: capacity.
  	0 to: capacity - 1 do: [ :index |
  		self assert: 0 equals: (bitset bitAt: index).
  		self assert: #() equals: self bitsetElements.
  		self assert: false equals: (bitset clearBitAt: index).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self assert: false equals: (bitset clearBitAt: index).
  
  		self assert: true equals: (bitset setBitAt: index).
  		self assert: 1 equals: (bitset bitAt: index).
  		self assert: 1 equals: bitset size.
  		self assert: { index } equals: self bitsetElements.
  
  		self assert: false equals: (bitset setBitAt: index).
  		self assert: 1 equals: (bitset bitAt: index).
  		self assert: 1 equals: bitset size.
  		self assert: { index } equals: self bitsetElements.
  				
  		self assert: true equals: (bitset clearBitAt: index).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self assert: 0 equals: (bitset bitAt: index).
  
  		self assert: false equals: (bitset clearBitAt: index).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self assert: 0 equals: (bitset bitAt: index).
  		
  		self assert: capacity equals: bitset capacity ].
  	
  	self
  		should: [ bitset bitAt: -1 ] raise: Error;
  		should: [ bitset bitAt: capacity ] raise: Error.
  		
  	self
  		should: [ bitset setBitAt: -1 ] raise: Error;
  		should: [ bitset setBitAt: capacity ] raise: Error.
  
  	self
  		should: [ bitset clearBitAt: -1 ] raise: Error;
  		should: [ bitset clearBitAt: capacity ] raise: Error!

Item was changed:
+ ----- Method: BitSetTest>>testCopy (in category 'tests') -----
- ----- Method: BitSetTest>>testCopy (in category 'testing') -----
  testCopy
  
  	#(0 8 16 24 32) do: [ :each |
  		self testCopy: each ]!

Item was changed:
+ ----- Method: BitSetTest>>testCopy: (in category 'tests') -----
- ----- Method: BitSetTest>>testCopy: (in category 'testing') -----
  testCopy: n
  
  	| copy |
  	self initializeBitset: n.
  	copy := bitset copy.
  	self assert: copy equals: bitset.
  	self assert: copy hash equals: bitset hash.
  	self deny: bitset == copy.
  	self deny: bitset bytes == copy bytes!

Item was changed:
+ ----- Method: BitSetTest>>testDictionaryAPI (in category 'tests') -----
- ----- Method: BitSetTest>>testDictionaryAPI (in category 'testing') -----
  testDictionaryAPI
  
  	#(0 8 16 24 32) do: [ :each |
  		self testDictionaryAPI: each ]!

Item was changed:
+ ----- Method: BitSetTest>>testDictionaryAPI: (in category 'tests') -----
- ----- Method: BitSetTest>>testDictionaryAPI: (in category 'testing') -----
  testDictionaryAPI: capacity
  
  	self initializeBitset: capacity.
  	0 to: capacity - 1 do: [ :index |
  		self assert: 0 equals: (bitset at: index).
  		self assert: #() equals: self bitsetElements.
  		self assert: 0 equals: (bitset at: index put: 0).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self assert: 0 equals: (bitset at: index put: 0).
  
  		self assert: 1 equals: (bitset at: index put: 1).
  		self assert: 1 equals: (bitset at: index).
  		self assert: 1 equals: bitset size.
  		self assert: { index } equals: self bitsetElements.
  
  		self assert: 1 equals: (bitset at: index put: 1).
  		self assert: 1 equals: (bitset at: index).
  		self assert: 1 equals: bitset size.
  		self assert: { index } equals: self bitsetElements.
  				
  		self assert: 0 equals: (bitset at: index put: 0).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self assert: 0 equals: (bitset at: index).
  
  		self assert: 0 equals: (bitset at: index put: 0).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self assert: 0 equals: (bitset at: index).
  		
  		self assert: capacity equals: bitset capacity ].
  	
  	self
  		should: [ bitset at: capacity ] raise: Error;
  		should: [ bitset at: capacity put: 0 ] raise: Error;
  		should: [ bitset at: capacity put: 1 ] raise: Error.
  	self
  		should: [ bitset at: -1 ] raise: Error;
  		should: [ bitset at: -1 put: 0 ] raise: Error;
  		should: [ bitset at: -1 put: 1 ] raise: Error.
  
  	self
  		should: [ bitset at: 0 put: -1 ] raise: Error;			
  		should: [ bitset at: 0 put: 2 ] raise: Error;
  		should: [ bitset at: 0 put: nil ] raise: Error!

Item was changed:
+ ----- Method: BitSetTest>>testNew (in category 'tests') -----
- ----- Method: BitSetTest>>testNew (in category 'testing') -----
  testNew
  
  	self should: [ Bitset new ] raise: Error!

Item was changed:
+ ----- Method: BitSetTest>>testRemoveAll (in category 'tests') -----
- ----- Method: BitSetTest>>testRemoveAll (in category 'testing') -----
  testRemoveAll
  
  	#(0 8 16 24 32) do: [ :each |
  		self testRemoveAll: each ]!

Item was changed:
+ ----- Method: BitSetTest>>testRemoveAll: (in category 'tests') -----
- ----- Method: BitSetTest>>testRemoveAll: (in category 'testing') -----
  testRemoveAll: n
  
  	self initializeBitset: n.
  	0 to: n - 1 do: [ :index |
  		bitset setBitAt: index ].
  	self assert: n equals: bitset size.
  	self assert: (bitset bytes allSatisfy: [ :each | each = 255 ]).
  	bitset removeAll.
  	self assert: 0 equals: bitset size.
  	self assert: #() equals: self bitsetElements.
  	self assert: (bitset bytes allSatisfy: [ :each | each = 0 ]).
  !

Item was changed:
+ ----- Method: BitSetTest>>testSetAPI (in category 'tests') -----
- ----- Method: BitSetTest>>testSetAPI (in category 'testing') -----
  testSetAPI
  
  	#(0 8 16 24 32) do: [ :each |
  		self testSetAPI: each ]!

Item was changed:
+ ----- Method: BitSetTest>>testSetAPI: (in category 'tests') -----
- ----- Method: BitSetTest>>testSetAPI: (in category 'testing') -----
  testSetAPI: capacity
  
  	self initializeBitset: capacity.
  	self assert: capacity equals: capacity // 8 * 8 description: 'capacity must be a multiple of eight.'.
  	self assert: capacity equals: bitset capacity.
  	self assert: 0 equals: bitset size.
  	self assert: #() equals: self bitsetElements.
  	0 to: capacity - 1 do: [ :index |
  		self deny: (bitset includes: index).
  		self assert: #() equals: self bitsetElements.
  		self assert: nil equals: (bitset remove: index ifAbsent: [ nil ]).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self deny: (bitset includes: index).
  
  		self assert: index equals: (bitset add: index).
  		self assert: (bitset includes: index).
  		self assert: 1 equals: bitset size.
  		self assert: { index } equals: self bitsetElements.
  
  		self assert: index equals: (bitset add: index).
  		self assert: (bitset includes: index).
  		self assert: 1 equals: bitset size.
  		self assert: { index } equals: self bitsetElements.
  				
  		self assert: index equals: (bitset remove: index).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self deny: (bitset includes: index).
  
  		self assert: nil equals: (bitset remove: index ifAbsent: [ nil ]).
  		self assert: 0 equals: bitset size.
  		self assert: #() equals: self bitsetElements.
  		self deny: (bitset includes: index).
  		
  		self assert: capacity equals: bitset capacity  ].
  	
  	self 
  		deny: (bitset includes: -1);	
  		deny: (bitset includes: capacity).
  	
  	self 
  		should: [ bitset add: capacity ] raise: Error;
  		should: [ bitset add: -1 ] raise: Error;
  		should: [ bitset remove: capacity ] raise: Error;
  		should: [ bitset remove: -1 ] raise: Error!

Item was changed:
+ ----- Method: BitSetTest>>testSize (in category 'tests') -----
- ----- Method: BitSetTest>>testSize (in category 'testing') -----
  testSize
  
  	#(0 8 16 24 32) do: [ :each |
  		self testSize: each ]!

Item was changed:
+ ----- Method: BitSetTest>>testSize: (in category 'tests') -----
- ----- Method: BitSetTest>>testSize: (in category 'testing') -----
  testSize: n
  
  	self initializeBitset: n.
  	0 to: n - 1 do: [ :index |
  		self assert: index equals: bitset size.
  		bitset setBitAt: index ].
  	self assert: n equals: bitset size.
  	0 to: n - 1 do: [ :index |
  		self assert: n - index equals: bitset size.
  		bitset clearBitAt: index ].
  	self assertBitsetIsEmpty!

Item was changed:
+ ----- Method: ByteArrayTest>>byteArrayFor:bits:bigEndian: (in category 'tests - platform independent access') -----
- ----- Method: ByteArrayTest>>byteArrayFor:bits:bigEndian: (in category 'testing - platform independent access') -----
  byteArrayFor: signedValue bits: bits bigEndian: bigEndian
  
  	| unsignedValue size result |
  	unsignedValue := signedValue negative
  		ifTrue: [ signedValue + (1 bitShift: bits) ]
  		ifFalse: [ signedValue ].
  	size := bits // 8.
  	result := ByteArray new: size.
  	1 to: size do: [ :index |
  		result at: index put: (unsignedValue digitAt: index) ].
  	bigEndian ifTrue: [ result reverseInPlace ].
  	^result
  	!

Item was changed:
+ ----- Method: ByteArrayTest>>testEmpty (in category 'tests') -----
- ----- Method: ByteArrayTest>>testEmpty (in category 'testing') -----
  testEmpty
  
  	self
  		assert: 0
  		equals: ByteArray empty size
  		description: 'The empty ByteArray should be empty indeed';
  		
  		assert: ByteArray
  		equals: ByteArray empty species 
  		description: 'The empty ByteArray should be a ByteArray';
  		
  		assert: ByteArray empty
  		identical: ByteArray empty 
  		description: 'The empty ByteArray should be canonical';
  		
  		yourself
  		
  		
  !

Item was changed:
+ ----- Method: ByteArrayTest>>testFallbackReplaceFromToWith (in category 'tests') -----
- ----- Method: ByteArrayTest>>testFallbackReplaceFromToWith (in category 'testing') -----
  testFallbackReplaceFromToWith
  	| teststring ba sz cm |
  	teststring := 'Test string' asByteArray.
  	sz := teststring byteSize.
  	ba := ByteArray new: sz.
  	cm := SequenceableCollection compiledMethodAt: #replaceFrom:to:with:startingAt:.
  	self shouldnt: [cm valueWithReceiver: ba arguments: {1. sz. teststring. 1}]
  		raise: Exception
  		description: 'Primitive 105 should be optional for ByteArray'
  !

Item was changed:
+ ----- Method: ByteArrayTest>>testHex (in category 'tests - hex') -----
- ----- Method: ByteArrayTest>>testHex (in category 'hex tests') -----
  testHex
  	self assert: #[122 43 213 7] hex = '7a2bd507'.
  	self assert: (UUID fromString: '97c1f2dd-f920-9948-b329-319a30c16386') hex
  					= '97c1f2ddf9209948b329319a30c16386'.!

Item was changed:
+ ----- Method: ByteArrayTest>>testIsLiteral (in category 'tests - hex') -----
- ----- Method: ByteArrayTest>>testIsLiteral (in category 'hex tests') -----
  testIsLiteral
  	self assert: #[122 43 213 7] isLiteral description: 'ByteArray instances are literal'.
  	self deny: thisContext method isLiteral description: 'ByteArray sub instances are not literal'!

Item was changed:
+ ----- Method: ByteArrayTest>>testPlatformIndepentendIntegerAccessorsAtBitBorders (in category 'tests - platform independent access') -----
- ----- Method: ByteArrayTest>>testPlatformIndepentendIntegerAccessorsAtBitBorders (in category 'testing - platform independent access') -----
  testPlatformIndepentendIntegerAccessorsAtBitBorders
  
  	#(
  		shortAt:put:bigEndian: shortAt:bigEndian: false 16
  		longAt:put:bigEndian: longAt:bigEndian: false 32
  		long64At:put:bigEndian: long64At:bigEndian: false 64
  		unsignedShortAt:put:bigEndian: unsignedShortAt:bigEndian: true 16
  		unsignedLongAt:put:bigEndian: unsignedLongAt:bigEndian: true 32
  		unsignedLong64At:put:bigEndian: unsignedLong64At:bigEndian: true 64		
  	) groupsDo: [ :setter :getter :unsigned :storageBits |
  		self
  			verifyPlatformIndepentendIntegerAccessorsAtBitBordersSetter: setter
  			getter: getter
  			unsigned: unsigned
  			storageBits: storageBits ]!

Item was changed:
+ ----- Method: ByteArrayTest>>testPlatformIndepentendIntegerAccessorsWithRandomValues (in category 'tests - platform independent access') -----
- ----- Method: ByteArrayTest>>testPlatformIndepentendIntegerAccessorsWithRandomValues (in category 'testing - platform independent access') -----
  testPlatformIndepentendIntegerAccessorsWithRandomValues
  
  	| random |
  	random := Random seed: 36rSqueak.
  	#(
  		shortAt:put:bigEndian: shortAt:bigEndian: false 16
  		longAt:put:bigEndian: longAt:bigEndian: false 32
  		long64At:put:bigEndian: long64At:bigEndian: false 64
  		unsignedShortAt:put:bigEndian: unsignedShortAt:bigEndian: true 16
  		unsignedLongAt:put:bigEndian: unsignedLongAt:bigEndian: true 32
  		unsignedLong64At:put:bigEndian: unsignedLong64At:bigEndian: true 64		
  	) groupsDo: [ :setter :getter :unsigned :storageBits |
  		self
  			verifyPlatformIndepentendIntegerAccessorsWithRandomValuesSetter: setter
  			getter: getter
  			unsigned: unsigned
  			storageBits: storageBits
  			random: random ]!

Item was changed:
+ ----- Method: ByteArrayTest>>testReadHexFrom (in category 'tests - hex') -----
- ----- Method: ByteArrayTest>>testReadHexFrom (in category 'hex tests') -----
  testReadHexFrom
  	self assert: (ByteArray readHexFrom: '7a2bd507') = #[122 43 213 7].
  	self assert: (UUID readHexFrom: '97c1f2ddf9209948b329319a30c16386')
  					= (UUID fromString: '97c1f2dd-f920-9948-b329-319a30c16386').!

Item was changed:
+ ----- Method: ByteArrayTest>>verifyPlatformIndepentendIntegerAccessorsAtBitBordersSetter:getter:unsigned:storageBits: (in category 'tests - platform independent access') -----
- ----- Method: ByteArrayTest>>verifyPlatformIndepentendIntegerAccessorsAtBitBordersSetter:getter:unsigned:storageBits: (in category 'testing - platform independent access') -----
  verifyPlatformIndepentendIntegerAccessorsAtBitBordersSetter: setter getter: getter unsigned: unsigned storageBits: storageBits
  
  	| byteArray minValue maxValue baseValues |
  	byteArray := ByteArray new: storageBits // 8 * 2.
  	unsigned
  		ifTrue: [
  			minValue := 0.
  			maxValue := 1 << storageBits - 1.
  			baseValues := #(0 1) ]
  		ifFalse: [
  			minValue := -1 << (storageBits - 1).
  			maxValue := 1 << (storageBits - 1) - 1.
  			baseValues := #(-1 0 1) ].
  	#(true false) do: [ :bigEndian |
  		0 to: storageBits - 1 do: [ :bits |
  			baseValues do: [ :baseValue |
  				| centerValue |
  				centerValue := baseValue << bits.
  				centerValue - 1 to: centerValue + 1 do: [ :value |
  					(value between: minValue and: maxValue) ifTrue: [
  						self
  							verifyPlatformIndepentendIntegerAccessorsMatch: byteArray
  							for: value
  							setter: setter
  							getter: getter
  							storageBits: storageBits
  							bigEndian: bigEndian  ] ] ] ] ]
  					!

Item was changed:
+ ----- Method: ByteArrayTest>>verifyPlatformIndepentendIntegerAccessorsMatch:for:setter:getter:storageBits:bigEndian: (in category 'tests - platform independent access') -----
- ----- Method: ByteArrayTest>>verifyPlatformIndepentendIntegerAccessorsMatch:for:setter:getter:storageBits:bigEndian: (in category 'testing - platform independent access') -----
  verifyPlatformIndepentendIntegerAccessorsMatch: byteArray for: value setter: setter getter: getter storageBits: storageBits bigEndian: bigEndian
  	
  	| expectedSetterResult getterResult bytes |
  	expectedSetterResult := self byteArrayFor: value bits: storageBits bigEndian: bigEndian.
  	bytes := storageBits // 8.
  	1 to: byteArray size - bytes + 1 do: [ :index |
  		byteArray
  			perform: setter
  			with: index
  			with: value
  			with: bigEndian.
  		1 to: bytes do: [ :byteIndex |
  			self
  				assert: (expectedSetterResult at: byteIndex)
  				equals: (byteArray at: index + byteIndex - 1) ].
  		getterResult := byteArray
  			perform: getter
  			with: index
  			with: bigEndian.
  		self assert: value equals: getterResult ]!

Item was changed:
+ ----- Method: ByteArrayTest>>verifyPlatformIndepentendIntegerAccessorsWithRandomValuesSetter:getter:unsigned:storageBits:random: (in category 'tests - platform independent access') -----
- ----- Method: ByteArrayTest>>verifyPlatformIndepentendIntegerAccessorsWithRandomValuesSetter:getter:unsigned:storageBits:random: (in category 'testing - platform independent access') -----
  verifyPlatformIndepentendIntegerAccessorsWithRandomValuesSetter: setter getter: getter unsigned: unsigned storageBits: storageBits random: random
  
  	| byteArray randomMax randomOffset |
  	byteArray := ByteArray new: storageBits // 8 * 2.
  	randomMax := 1 << storageBits.
  	randomOffset := unsigned
  		ifTrue: [ -1 ]
  		ifFalse: [ -1 << (storageBits - 1) - 1 ].
  	10000 timesRepeat: [
  		| value |
  		value := (random nextInt: randomMax) + randomOffset.
  		#(true false) do: [ :bigEndian |
  			self
  				verifyPlatformIndepentendIntegerAccessorsMatch: byteArray
  				for: value
  				setter: setter
  				getter: getter
  				storageBits: storageBits
  				bigEndian: bigEndian ] ]!

Item was changed:
+ ----- Method: CharacterSetComplementTest>>testIncludes (in category 'tests') -----
- ----- Method: CharacterSetComplementTest>>testIncludes (in category 'testing') -----
  testIncludes
  	| set complement |
  	set := 'abc' as: CharacterSet.
  	complement := set complement.
  	self assert: (set noneSatisfy: [:e | complement includes: e]).
  	self assert: (($d to: $z) allSatisfy: [:e | complement includes: e]).!

Item was changed:
+ ----- Method: CharacterSetComplementTest>>testPrintString (in category 'tests') -----
- ----- Method: CharacterSetComplementTest>>testPrintString (in category 'testing') -----
  testPrintString
  	|s|
  	s := CharacterSet separators complement printString.
  	self assert: (s includesSubstring: 'complement') description: 'Doesn''t describe its fundamental characteristic'.
  	self assert: (s includesSubstring: 'Character space') description: 'Doesn''t mention an important separator'.!

Item was changed:
+ ----- Method: CharacterSetComplementTest>>testReject (in category 'tests') -----
- ----- Method: CharacterSetComplementTest>>testReject (in category 'testing') -----
  testReject
  	| set complement subset |
  	set := 'abc' as: CharacterSet.
  	complement := set complement.
  	subset := complement reject: [:c | c isVowel].
  	self assert: (subset includes: $z). "Not a vowel, it is in the subset"
  	self deny: (subset includes: $e). "a vowel should be rejected"
  	self deny: (subset includes: $b). "Not a vowel, but not in the original set"!

Item was changed:
+ ----- Method: CharacterSetComplementTest>>testSelect (in category 'tests') -----
- ----- Method: CharacterSetComplementTest>>testSelect (in category 'testing') -----
  testSelect
  	| set complement digits |
  	set := 'abc012' as: CharacterSet.
  	complement := set complement.
  	digits := complement select: [:c | c isDigit].
  	self assert: (digits includes: $9).
  	self deny: (digits includes: $1).
  	self deny: (digits includes: $z).!

Item was changed:
+ ----- Method: CharacterSetTest>>testComplement (in category 'tests') -----
- ----- Method: CharacterSetTest>>testComplement (in category 'testing') -----
  testComplement
  	| set complement |
  	set := 'abc' as: CharacterSet.
  	complement := set complement.
  	self assert: (set noneSatisfy: [:e | complement includes: e]).
  	self assert: (($d to: $z) allSatisfy: [:e | complement includes: e]).!

Item was changed:
+ ----- Method: CharacterSetTest>>testCopy (in category 'tests') -----
- ----- Method: CharacterSetTest>>testCopy (in category 'testing') -----
  testCopy
      | theOriginal theCopy |
      theOriginal := CharacterSet newFrom: 'abc'.
      theCopy := theOriginal copy.
      theCopy remove: $a.
      ^self assert: (theOriginal includes: $a) description: 'Changing the copy should not change the original'.!

Item was changed:
+ ----- Method: CharacterSetTest>>testIncludes (in category 'tests') -----
- ----- Method: CharacterSetTest>>testIncludes (in category 'testing') -----
  testIncludes
  	| set |
  	set := 'abc' as: CharacterSet.
  	self assert: (($a to: $c) allSatisfy: [:e | set includes: e]).
  	self assert: (($d to: $z) noneSatisfy: [:e | set includes: e]).!

Item was changed:
+ ----- Method: CharacterSetTest>>testIntersection (in category 'tests') -----
- ----- Method: CharacterSetTest>>testIntersection (in category 'testing') -----
  testIntersection
  	| intersection |
  	intersection := ('abc' as: CharacterSet) intersection: ('bcde' as: CharacterSet).
  	self assert: intersection = ('bc' as: CharacterSet)!

Item was changed:
+ ----- Method: CharacterSetTest>>testIntersectionWithComplement (in category 'tests') -----
- ----- Method: CharacterSetTest>>testIntersectionWithComplement (in category 'testing') -----
  testIntersectionWithComplement
  	| intersection intersection2 |
  	intersection := ('abcd' as: CharacterSet) intersection: ('cdef' as: CharacterSet) complement.
  	self assert: intersection = ('ab' as: CharacterSet).
  	intersection2 := ('cdef' as: CharacterSet) complement intersection: ('abcd' as: CharacterSet).
  	self assert: intersection2 = intersection. "Intersection is symmetric"!

Item was changed:
+ ----- Method: CharacterSetTest>>testUnion (in category 'tests') -----
- ----- Method: CharacterSetTest>>testUnion (in category 'testing') -----
  testUnion
  	| union |
  	union := ('abc' as: CharacterSet) union: ('bcde' as: CharacterSet).
  	self assert: union = ('abcde' as: CharacterSet)!

Item was changed:
+ ----- Method: CharacterSetTest>>testUnionWithComplement (in category 'tests') -----
- ----- Method: CharacterSetTest>>testUnionWithComplement (in category 'testing') -----
  testUnionWithComplement
  	| union union2 |
  	union := ('abc' as: CharacterSet) union: ('bcde' as: CharacterSet) complement.
  	self assert: union = ('de' as: CharacterSet) complement.
  	union2 := ('bcde' as: CharacterSet) complement union: ('abc' as: CharacterSet).
  	self assert: union2 = union. "union is symmetric"!

Item was changed:
+ ----- Method: DictionaryTest>>testAddAssociation (in category 'tests - association') -----
- ----- Method: DictionaryTest>>testAddAssociation (in category 'association tests') -----
  testAddAssociation
  	"self run:#testAddAssociation"
  	"self debug:#testAddAssociation"
  	
  	| dict |
  	dict := Dictionary new.
  	dict at: #a put: 1.
  	dict at: #b put: 2.
  	self assert: (dict at: #a) = 1.
  	self assert: (dict at: #b) = 2.
  	
  	dict at: #a put: 10.
  	dict at: #c put: 2.
  	
  	self assert: (dict at: #a) = 10.
  	self assert: (dict at: #b) = 2.
  	self assert: (dict at: #c) = 2
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testAssociationsSelect (in category 'tests - association') -----
- ----- Method: DictionaryTest>>testAssociationsSelect (in category 'association tests') -----
  testAssociationsSelect
  	| answer d |
  	d := Dictionary new.
  	d at: (Array with: #hello with: #world)
  	  put: #fooBar.
  	d at: Smalltalk put: #'Smalltalk is the key'.
  	d at: #Smalltalk put: Smalltalk.
  	answer := d
  				associationsSelect: [:assoc | assoc key == #Smalltalk
  						and: [assoc value == Smalltalk]].
  	self
  		should: [answer isKindOf: Dictionary].
  	self
  		should: [answer size = 1].
  	self
  		should: [(answer at: #Smalltalk)
  				== Smalltalk].
  	answer := d
  				associationsSelect: [:assoc | assoc key == #NoSuchKey
  						and: [assoc value == #NoSuchValue]].
  	self
  		should: [answer isKindOf: Dictionary].
  	self
  		should: [answer size = 0]!

Item was changed:
+ ----- Method: DictionaryTest>>testAtError (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testAtError (in category 'basic tests') -----
  testAtError
  	"self run: #testAtError"
  	
  	| dict |
  	dict := Dictionary new.
  	dict at: #a put: 666.
  	self shouldnt: [ dict at: #a ] raise: KeyNotFound.
  	self should: [ dict at: #b ] raise: KeyNotFound.
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testAtIfAbsent (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testAtIfAbsent (in category 'basic tests') -----
  testAtIfAbsent
  	"self run: #testAtIfAbsent"
  	
  	| dict |
  	dict := Dictionary new.
  	dict at: #a put: 666.
  	
  	self assert: (dict at: #a ifAbsent: [nil]) = 666.
  	
  	self assert: (dict at: #b ifAbsent: [nil]) isNil.
  
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testAtIfPresentIfAbsent (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testAtIfPresentIfAbsent (in category 'basic tests') -----
  testAtIfPresentIfAbsent
  	"Test at:ifPresent:ifAbsent:"
  	| dict present absent |
  	dict := Dictionary new.
  	present := absent := false.
  	dict at: #foo ifPresent:[:v| present := true] ifAbsent:[absent := true].
  	self deny: present.
  	self assert: absent.
  
  	dict at: #foo put: #bar.
  	present := absent := false.
  	dict at: #foo ifPresent:[:v| present := true] ifAbsent:[absent := true].
  	self assert: present.
  	self deny: absent.
  
  	present := absent := false.
  	dict at: #foo ifPresent:[:v| present := true. nil] ifAbsent:[absent := true].
  	self assert: present.
  	self deny: absent.
  !

Item was changed:
+ ----- Method: DictionaryTest>>testAtIfPresentIfAbsentPut (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testAtIfPresentIfAbsentPut (in category 'basic tests') -----
  testAtIfPresentIfAbsentPut
  	"Test at:ifPresent:ifAbsentPut:"
  	| dict present absent |
  	dict := Dictionary new.
  	present := absent := false.
  	self assert: (dict at: #foo ifPresent:[:v| present := true. v] ifAbsentPut:[absent := true. #present])
  		equals: #present.
  	self deny: present.
  	self assert: absent.
  
  	present := absent := false.
  	self assert: (dict at: #foo ifPresent:[:v| present := true. v] ifAbsentPut:[absent := true. #absent])
  		equals: #present.
  	self assert: present.
  	self deny: absent.!

Item was changed:
+ ----- Method: DictionaryTest>>testAtNil (in category 'tests - implementation') -----
- ----- Method: DictionaryTest>>testAtNil (in category 'implementation tests') -----
  testAtNil
  	"(self run: #testAtNil)"
  	"nil is a valid key in squeak. In VW nil is not a valid key"
  	"Ansi 1.9 p, 168
      		5.7.2.5 Message: at: key put: newElement
      		Synopsis
      			Store newElement at key in the receiver. Answer newElement.
      		Definition: <abstractDictionary>
      		If lookup succeeds for key, then newElement replaces the element previously stored at key.
      		Otherwise, the newElement is stored at the new key. In either case, subsequent successful
      		lookups for key will answer newElement.  Answer newElement.
  
      		The result is undefined if the key is nil.
  
  		This clearly indicates that different smalltalks where doing different assumptions."
  	
  	
  	
  	| dict1  |
  	dict1 := Dictionary new.
  	dict1 at: nil put: #none.
  	self assert: (dict1 at: nil) = #none. 
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testAtPut (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testAtPut (in category 'basic tests') -----
  testAtPut
  	"self run: #testAtPut"
  	"self debug: #testAtPut"
  	
  	| adictionary |
  	adictionary := Dictionary new.
  	adictionary at: #a put: 3.
  	self assert: (adictionary at: #a) = 3.
  	adictionary at: #a put: 3.
  	adictionary at: #a put: 4.
  	self assert: (adictionary at: #a) = 4.
  	adictionary at: nil put: 666.
  	self assert: (adictionary at: nil) = 666!

Item was changed:
+ ----- Method: DictionaryTest>>testAtPutNil (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testAtPutNil (in category 'basic tests') -----
  testAtPutNil
  	"self run: #testAtPut"
  	"self debug: #testAtPut"
  	
  	| dict |
  	dict := Dictionary new.
  	dict at: nil put: 1.
  	self assert: (dict at: nil) = 1.
  	dict at: #a put: nil.
  	self assert: (dict at: #a) = nil.
  	dict at: nil put: nil.
  	self assert: (dict at: nil) = nil.
  	
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testCollect (in category 'tests - collection protocol') -----
- ----- Method: DictionaryTest>>testCollect (in category 'testing') -----
  testCollect
  	"Ensure that Dictionary>>collect: answers a dictionary not something else"
  	| dict expected result |
  	dict := Dictionary newFromPairs:{
  		#first.		1.
  		#second.	2.
  		#third.		3.
  		#fourth.	4.
  		#fifth.		5.
  	}.
  	result := dict collect:[:each| each asWords].
  	expected := Dictionary newFromPairs:{
  		#first.		'one'.
  		#second.	'two'.
  		#third.		'three'.
  		#fourth.	'four'.
  		#fifth.		'five'.
  	}.
  	self assert: result = expected.!

Item was changed:
+ ----- Method: DictionaryTest>>testDictionaryConcatenation (in category 'tests - keys and value') -----
- ----- Method: DictionaryTest>>testDictionaryConcatenation (in category 'keys and value tests') -----
  testDictionaryConcatenation
  	"self run: #testDictionaryConcatenation"
  	
  	
  	| dict1 dict2 dict3 |
  	dict1 := Dictionary new.
  	dict1 at: #a put: 'Nicolas' ; at: #b put: 'Damien'. 
  	
  	dict2 := Dictionary new.
  	dict2 at: #a put: 'Christophe' ; at: #c put: 'Anthony'.
  	dict3 := dict1, dict2.
  	
  	self assert: (dict3 at: #a) = 'Christophe'.
  	self assert: (dict3 at: #b) = 'Damien'.
  	self assert: (dict3 at: #c) = 'Anthony'.
  	
  
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testIncludesAssociation (in category 'tests - association') -----
- ----- Method: DictionaryTest>>testIncludesAssociation (in category 'association tests') -----
  testIncludesAssociation
  	"self run:#testIncludesAssociation"
  	
  	| dict |
  	dict := Dictionary new.
  	dict at: #a put: 1.
  	dict at: #b put: 2.
  	self assert: (dict includesAssociation: (#a -> 1)).
  	self assert: (dict includesAssociation: (#b -> 2)).
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testIncludesAssociationNoValue (in category 'tests - association') -----
- ----- Method: DictionaryTest>>testIncludesAssociationNoValue (in category 'association tests') -----
  testIncludesAssociationNoValue
  	"self run:#testIncludesAssociationNoValue"
  	"self debug:#testIncludesAssociationNoValue"
  	
  	| dict a1 a3 |
  	a1 := Association key: #Italie.
  	a3 := Association key: #France value: 'Paris'.
  	
  	self assert: (a1 key = #Italie).
  	self assert: (a1 value isNil).
  	
  	dict := Dictionary new.
  	dict add: a1.
  	dict add: a3.
  	self assert: (dict includesKey: #France).
  	self assert: (dict includesKey: #Italie).
  	self assert: (dict at: #Italie) isNil.
  	self assert: (dict at: #France) = 'Paris'
  
  	
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testIncludesKey (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testIncludesKey (in category 'basic tests') -----
  testIncludesKey
  	"self run:#testIncludesKey"
  	"self debug:#testIncludesKey"
  	
  	| dict a1 a2 a3 |
  	a1 := Association key: 'Italie'.
  	a2 := Association new.
  	a3 := Association key: 'France' value: 'Paris'.
  	
  	dict := Dictionary new.
  	dict add: a1 .
  	dict add: a2.
  	dict add: a3.
  	self assert: (dict includesKey: #France).
  	self assert: (dict includesKey: 'France').
  	self assert: (dict includesKey: #Italie).
  	self assert: (dict includesKey: nil).	
  		
  	self assert: (dict at: 'France' ) = 'Paris'.
  !

Item was changed:
+ ----- Method: DictionaryTest>>testIntegrityOfDictionaries (in category 'tests - integrity') -----
- ----- Method: DictionaryTest>>testIntegrityOfDictionaries (in category 'integrity tests') -----
  testIntegrityOfDictionaries
  	#(
  		Dictionary
  		IdentityDictionary
  		SystemDictionary
  		LiteralDictionary
  		PluggableDictionary
  		WeakValueDictionary) do: [ :dictionaryClassName |
  			Smalltalk at: dictionaryClassName ifPresent: [ :dictionaryClass |
  				dictionaryClass allInstancesDo: [ :dictionary |
  					dictionary keysAndValuesDo: [ :key :value |
  						self assert: (dictionary at: key) == value ].
  					dictionary array doWithIndex: [ :association :index |
  		                        association ifNotNil: [
  	 	                               self assert: (dictionary scanFor: association key) = index ] ] ] ] ]!

Item was changed:
+ ----- Method: DictionaryTest>>testKeyAtValue (in category 'tests - keys and value') -----
- ----- Method: DictionaryTest>>testKeyAtValue (in category 'keys and value tests') -----
  testKeyAtValue
  	"self run: #testKeyAtValue"
  	"self debug: #testKeyAtValue"
  	
  	| dict |
  	dict := Dictionary new.
  	dict at: #a put: 1.
  	dict at: #b put: 2.
  	dict at: #c put: 1.
  	
  	self assert: (dict keyAtValue: 2) = #b.
  	"which ever is answered depends on hashing, and hashing is improved in Spur."
  	self assert: ((dict keyAtValue: 1) = #a or: [(dict keyAtValue: 1) = #c]).
  	"ugly may be a bug, why not have a set #a and #c?  cuz that would be keys at value."
  	
  	self should: [dict keyAtValue: 0] raise: Error
  	
  	
  !

Item was changed:
+ ----- Method: DictionaryTest>>testKeys (in category 'tests - keys and value') -----
- ----- Method: DictionaryTest>>testKeys (in category 'keys and value tests') -----
  testKeys
  
  	"self run:#testKeys "
  	
  	| a1 a2  dict | 
  	a1 := Association key: 'France' value: 'Paris'.
  	a2 := Association key: 'Italie' value: 'Rome'.
  	dict := Dictionary new.
  	dict add: a1.
  	dict add: a2.
  	 		
  	self assert: (dict keys size) = 2.
  	
  	self assert: (dict keys includes: #France)
  	
  	
  
  
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testKeysDo (in category 'tests - keys and value') -----
- ----- Method: DictionaryTest>>testKeysDo (in category 'keys and value tests') -----
  testKeysDo
  	"self run: #testKeysDo"
  	"self debug: #testKeysDo"
  	
  	| dict res |
  	dict := Dictionary new.
  	
  	dict at: #a put: 33.
  	dict at: #b put: 66.
  	
  	res := OrderedCollection new.
  	dict keysDo: [ :each | res add: each].
  	
  	self assert: res asSet = #(a b) asSet.
  
  
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testMethodDictionaries (in category 'tests - integrity') -----
- ----- Method: DictionaryTest>>testMethodDictionaries (in category 'integrity tests') -----
  testMethodDictionaries
  	MethodDictionary allInstancesDo: [ :dictionary |
  		dictionary keysAndValuesDo: [ :key :value |
  			self assert: (dictionary at: key) == value ].
  		1 to: dictionary basicSize do: [ :index |
  			(dictionary basicAt: index)
  				ifNil: [ self assert: (dictionary array at: index) isNil ]
  				ifNotNil: [ :key |
  					self assert: (dictionary scanFor: key) = index ] ] ]!

Item was changed:
+ ----- Method: DictionaryTest>>testNewFromIsolation (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testNewFromIsolation (in category 'basic tests') -----
  testNewFromIsolation
  	"self run:#testNewFromIsolation"
  	"self debug:#testNewFromIsolation"
  	
  	| dict1 dict2 |
  	dict1 := Dictionary new.
  	dict1 at: #one put: 'foo'; at: #two put: 0 at 0.
  	dict2 := Dictionary newFrom: dict1.
  	dict2 at: #one put: 'bar'.
  
  	self assert: (dict1 at: #one) = 'foo'.
  !

Item was changed:
+ ----- Method: DictionaryTest>>testOccurrencesOf (in category 'tests - basic') -----
- ----- Method: DictionaryTest>>testOccurrencesOf (in category 'basic tests') -----
  testOccurrencesOf
  	"self run:#testOccurrencesOf"
  	
  	| dict |
  	dict := Dictionary new.
  	dict at: #a put: 1.
  	dict at: #b put: 2.
  	dict at: #c put: 1.
  	dict at: #d put: 3.
  	dict at: nil put: nil.
  	dict at: #z put: nil.
  	
  	
  	self assert: (dict occurrencesOf: 1 ) = 2.
  	self assert: (dict occurrencesOf: nil ) = 2.
  	
  	
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testPseudoVariablesAreValidKeys (in category 'tests - implementation') -----
- ----- Method: DictionaryTest>>testPseudoVariablesAreValidKeys (in category 'implementation tests') -----
  testPseudoVariablesAreValidKeys
  	"(self run: #testPseudoVariablesAreValidKeys)"
  	"true and false are valid keys"
  	
  	| dict1  |
  	dict1 := Dictionary new.
  	dict1 at: true put: #true.
  	self assert: (dict1 at: true) = #true.
  		
  	dict1 at: false put: #false.
  	self assert: (dict1 at: false) = #false.!

Item was changed:
+ ----- Method: DictionaryTest>>testReject (in category 'tests - collection protocol') -----
- ----- Method: DictionaryTest>>testReject (in category 'testing') -----
  testReject
  	"Ensure that Dictionary>>reject: answers a dictionary not something else"
  	| dict expected result |
  	dict := Dictionary newFromPairs:{
  		#first.		1.
  		#second.	2.
  		#third.		3.
  		#fourth.	4.
  		#fifth.		5.
  	}.
  	result := dict reject:[:each| each odd].
  	expected := Dictionary newFromPairs:{
  		#second.	2.
  		#fourth.	4.
  	}.
  	self assert: result = expected.!

Item was changed:
+ ----- Method: DictionaryTest>>testRemoveKey (in category 'tests - keys and value') -----
- ----- Method: DictionaryTest>>testRemoveKey (in category 'keys and value tests') -----
  testRemoveKey
  		"self run:#testRemoveKey "
  
  	| dict | 
  	dict := Dictionary new.
  	dict at: #a put: 1.
  	dict at: #b put: 2.
  	 
  	self assert: (dict keys size) = 2.
  	dict removeKey: #a.
  	self assert: dict keys size  = 1.
  
  	self should: [dict at: #a] raise: Error.
  	self assert: (dict at: #b) = 2
  
  
  	
  	!

Item was changed:
+ ----- Method: DictionaryTest>>testSelect (in category 'tests - collection protocol') -----
- ----- Method: DictionaryTest>>testSelect (in category 'testing') -----
  testSelect
  	"Ensure that Dictionary>>select: answers a dictionary not something else"
  	| dict expected result |
  	dict := Dictionary newFromPairs:{
  		#first.		1.
  		#second.	2.
  		#third.		3.
  		#fourth.	4.
  		#fifth.		5.
  	}.
  	result := dict select:[:each| each odd].
  	expected := Dictionary newFromPairs:{
  		#first.		1.
  		#third.		3.
  		#fifth.		5.
  	}.
  	self assert: result = expected.
  	result at: #first put: 0.
  	self assert: (dict at: #first) = 1 "No side effects"!

Item was changed:
+ ----- Method: DictionaryTest>>testValues (in category 'tests - keys and value') -----
- ----- Method: DictionaryTest>>testValues (in category 'keys and value tests') -----
  testValues
  	"self run:#testValues "
  	
  	| a1 a2 a3 dict | 
  	a1 := Association key: 'France' value: 'Paris'.
  	a2 := Association key: 'Italie' value: 'Rome'.
  	dict := Dictionary new.
  	dict add: a1.
  	dict add: a2.
  	 
  	self assert: (dict values size ) = 2.
  	self assert: (dict values includes: 'Paris').
  	
  	a3 := Association new.
  	dict add: a3.
  	self assert: (dict values size ) = 3.
  	self assert: (dict values includes: nil).
  	
  	
  	
  	
  	
  	
  
  
  	
  	!

Item was changed:
+ ----- Method: DoubleByteArrayTest>>testAllPossibleValues (in category 'tests') -----
- ----- Method: DoubleByteArrayTest>>testAllPossibleValues (in category 'testing') -----
  testAllPossibleValues
  	| doubleByteArray |
  	doubleByteArray := (1 to: 65535) as: DoubleByteArray.
  	1 to: doubleByteArray size do: [:i |
  		self assert: (doubleByteArray at: i) = i]!

Item was changed:
+ ----- Method: DoubleByteArrayTest>>testAtOutOfBounds (in category 'tests') -----
- ----- Method: DoubleByteArrayTest>>testAtOutOfBounds (in category 'testing') -----
  testAtOutOfBounds
  	"self debug: #testAtOutOfBounds"
  	"Do the test more than once to make sure the jitted code is tested."
  	1 to: 5 do:
  		[:iteration|
  		 self 
  			should: [(DoubleByteArray with: 0) at: 2]
  			raise: Error.
  		 self 
  			should: [(DoubleByteArray with: 0) at: -1]
  			raise: Error]!

Item was changed:
+ ----- Method: DoubleByteArrayTest>>testAtPutOutOfBounds (in category 'tests') -----
- ----- Method: DoubleByteArrayTest>>testAtPutOutOfBounds (in category 'testing') -----
  testAtPutOutOfBounds
  	"self debug: #testAtPutOutOfBounds"
  	"Do the test more than once to make sure the jitted code is tested."
  	1 to: 5 do:
  		[:iteration|
  		 self 
  			should: [(DoubleByteArray with: 0) at: 2 put: 1]
  			raise: Error.
  		 self 
  			should: [(DoubleByteArray with: 0) at: -1 put: 1]
  			raise: Error]!

Item was changed:
+ ----- Method: DoubleByteArrayTest>>testByteSize (in category 'tests') -----
- ----- Method: DoubleByteArrayTest>>testByteSize (in category 'testing') -----
  testByteSize
  	self assert: (DoubleByteArray new: 1) byteSize = 2 "2 bytes are 16 bits"!

Item was changed:
+ ----- Method: DoubleByteArrayTest>>testCannotPutNegativeValue (in category 'tests') -----
- ----- Method: DoubleByteArrayTest>>testCannotPutNegativeValue (in category 'testing') -----
  testCannotPutNegativeValue
  	self should: [DoubleByteArray with: -1] raise: Error!

Item was changed:
+ ----- Method: DoubleByteArrayTest>>testCannotPutTooLargeValue (in category 'tests') -----
- ----- Method: DoubleByteArrayTest>>testCannotPutTooLargeValue (in category 'testing') -----
  testCannotPutTooLargeValue
  	| maxValue |
  	maxValue := 1 << 16 - 1.
  	self assert: (DoubleByteArray with: maxValue) first = maxValue.
  	self should: [DoubleByteArray with: maxValue + 1] raise: Error!

Item was changed:
+ ----- Method: DoubleByteArrayTest>>testElementSize (in category 'tests') -----
- ----- Method: DoubleByteArrayTest>>testElementSize (in category 'testing') -----
  testElementSize
  	self assert: DoubleByteArray new bytesPerElement = 2 "2 bytes are 16 bits"!

Item was changed:
+ ----- Method: DoubleWordArrayTest>>testAtOutOfBounds (in category 'tests') -----
- ----- Method: DoubleWordArrayTest>>testAtOutOfBounds (in category 'testing') -----
  testAtOutOfBounds
  	"self debug: #testAtOutOfBounds"
  	"Do the test more than once to make sure the jitted code is tested."
  	1 to: 5 do:
  		[:iteration|
  		 self 
  			should: [(DoubleWordArray with: 0) at: 2]
  			raise: Error.
  		 self 
  			should: [(DoubleWordArray with: 0) at: -1]
  			raise: Error]!

Item was changed:
+ ----- Method: DoubleWordArrayTest>>testAtPutOutOfBounds (in category 'tests') -----
- ----- Method: DoubleWordArrayTest>>testAtPutOutOfBounds (in category 'testing') -----
  testAtPutOutOfBounds
  	"self debug: #testAtPutOutOfBounds"
  	"Do the test more than once to make sure the jitted code is tested."
  	1 to: 5 do:
  		[:iteration|
  		 self 
  			should: [(DoubleWordArray with: 0) at: 2 put: 1]
  			raise: Error.
  		 self 
  			should: [(DoubleWordArray with: 0) at: -1 put: 1]
  			raise: Error]!

Item was changed:
+ ----- Method: DoubleWordArrayTest>>testByteSize (in category 'tests') -----
- ----- Method: DoubleWordArrayTest>>testByteSize (in category 'testing') -----
  testByteSize
  	self assert: (DoubleWordArray new: 1) byteSize = 8 "8 bytes are 64 bits"!

Item was changed:
+ ----- Method: DoubleWordArrayTest>>testCannotPutNegativeValue (in category 'tests') -----
- ----- Method: DoubleWordArrayTest>>testCannotPutNegativeValue (in category 'testing') -----
  testCannotPutNegativeValue
  	self should: [DoubleWordArray with: -1] raise: Error!

Item was changed:
+ ----- Method: DoubleWordArrayTest>>testCannotPutTooLargeValue (in category 'tests') -----
- ----- Method: DoubleWordArrayTest>>testCannotPutTooLargeValue (in category 'testing') -----
  testCannotPutTooLargeValue
  	| maxValue |
  	maxValue := 1 << 64 - 1.
  	self assert: (DoubleWordArray with: maxValue) first = maxValue.
  	self should: [DoubleWordArray with: maxValue + 1] raise: Error!

Item was changed:
+ ----- Method: DoubleWordArrayTest>>testElementSize (in category 'tests') -----
- ----- Method: DoubleWordArrayTest>>testElementSize (in category 'testing') -----
  testElementSize
  	self assert: DoubleWordArray new bytesPerElement = 8 "8 bytes are 64 bits"!

Item was changed:
+ ----- Method: DoubleWordArrayTest>>testSomeValues (in category 'tests') -----
- ----- Method: DoubleWordArrayTest>>testSomeValues (in category 'testing') -----
  testSomeValues
  	| dwArray int next |
  	next := [:x | x - 3 * x sqrtFloor + 5].
  	int := 0.
  	dwArray := DoubleWordArray new: 1.
  	[int highBit < 64]
  		whileTrue:
  			[dwArray at: 1 put: int.
  			self assert: (dwArray at: 1) = int.
  			int := next value: int].
  	self should: [dwArray at: 1 put: int] raise: Error!

Item was changed:
+ ----- Method: FloatArrayTest>>testArithmeticCoercion (in category 'tests') -----
- ----- Method: FloatArrayTest>>testArithmeticCoercion (in category 'testing') -----
  testArithmeticCoercion
  	"This test is related to http://bugs.squeak.org/view.php?id=6782"
  	
  	self should: [3.0 / (FloatArray with: 2.0) = (FloatArray with: 1.5)].
  	self should: [3.0 * (FloatArray with: 2.0) = (FloatArray with: 6.0)].
  	self should: [3.0 + (FloatArray with: 2.0) = (FloatArray with: 5.0)].
  	self should: [3.0 - (FloatArray with: 2.0) = (FloatArray with: 1.0)].!

Item was changed:
+ ----- Method: FloatArrayTest>>testFloatArrayPluginPrimitiveAt (in category 'tests') -----
- ----- Method: FloatArrayTest>>testFloatArrayPluginPrimitiveAt (in category 'testing') -----
  testFloatArrayPluginPrimitiveAt
  	"if FloatArrayPlugin primitive are not here, this test is dumb.
  	Otherwise, it will compare primitive and #fromIEEE32Bit:"
  	
  	#(
  		"regular numbers no truncation or rounding"
  		2r0.0 2r1.0 2r1.1 2r1.00000000000000000000001
  		2r1.0e-10 2r1.1e-10 2r1.00000000000000000000001e-10
  		2r1.0e10 2r1.1e10 2r1.00000000000000000000001e10
  		
  		"smallest float32 before gradual underflow"
  		2r1.0e-126
  		
  		"biggest float32"
  		2r1.11111111111111111111111e127
  		
  		"overflow"
  		2r1.11111111111111111111111e128
  		
  		"gradual underflow"
  		2r0.11111111111111111111111e-126
  		2r0.00000000000000000000001e-126
  		
  		"with rounding mode : tests on 25 bits"
  		
  		2r1.0000000000000000000000001
  		2r1.0000000000000000000000010
  		2r1.0000000000000000000000011
  		2r1.0000000000000000000000100
  		2r1.0000000000000000000000101
  		2r1.0000000000000000000000110
  		2r1.0000000000000000000000111
  		2r1.1111111111111111111111001
  		2r1.1111111111111111111111010
  		2r1.1111111111111111111111011
  		2r1.1111111111111111111111101
  		2r1.1111111111111111111111110
  		2r1.1111111111111111111111111
  		
  		"overflow"
  		2r1.1111111111111111111111110e127
  		
  		"gradual underflow"
  		2r0.1111111111111111111111111e-126
  		2r0.1111111111111111111111110e-126
  		2r0.1111111111111111111111101e-126
  		2r0.1111111111111111111111011e-126
  		2r0.1111111111111111111111010e-126
  		2r0.1111111111111111111111001e-126
  		2r0.0000000000000000000000111e-126
  		2r0.0000000000000000000000110e-126
  		2r0.0000000000000000000000101e-126
  		2r0.0000000000000000000000011e-126
  		2r0.0000000000000000000000010e-126
  		2r0.0000000000000000000000001e-126
  		2r0.0000000000000000000000010000000000000000000000000001e-126
  		) do: [:e |
  			self assert: ((FloatArray with: e) at: 1) = (Float fromIEEE32Bit: ((FloatArray with: e) basicAt: 1)).
  			self assert: ((FloatArray with: e negated) at: 1) = (Float fromIEEE32Bit: ((FloatArray with: e negated) basicAt: 1))].
  		
  	"special cases"
  	(Array with: Float infinity with: Float negativeInfinity with: Float negativeZero)
  		do: [:e | self assert: ((FloatArray with: e) at: 1) = (Float fromIEEE32Bit: ((FloatArray with: e) basicAt: 1))].
  		
  	"Cannot compare NaN"
  	(Array with: Float nan)
  		do: [:e | self assert: (Float fromIEEE32Bit: ((FloatArray with: e) basicAt: 1)) isNaN].!

Item was changed:
+ ----- Method: FloatArrayTest>>testFloatArrayPluginPrimitiveAtPut (in category 'tests') -----
- ----- Method: FloatArrayTest>>testFloatArrayPluginPrimitiveAtPut (in category 'testing') -----
  testFloatArrayPluginPrimitiveAtPut
  	"if FloatArrayPlugin primitive are not here, this test is dumb.
  	Otherwise, it will compare primitive and #asIEEE32BitWord"
  	
  	#(
  		"regular numbers no truncation or rounding"
  		2r0.0 2r1.0 2r1.1 2r1.00000000000000000000001
  		2r1.0e-10 2r1.1e-10 2r1.00000000000000000000001e-10
  		2r1.0e10 2r1.1e10 2r1.00000000000000000000001e10
  		
  		"smallest float32 before gradual underflow"
  		2r1.0e-126
  		
  		"biggest float32"
  		2r1.11111111111111111111111e127
  		
  		"overflow"
  		2r1.11111111111111111111111e128
  		
  		"gradual underflow"
  		2r0.11111111111111111111111e-126
  		2r0.00000000000000000000001e-126
  		
  		"with rounding mode : tests on 25 bits"
  		
  		2r1.0000000000000000000000001
  		2r1.0000000000000000000000010
  		2r1.0000000000000000000000011
  		2r1.0000000000000000000000100
  		2r1.0000000000000000000000101
  		2r1.0000000000000000000000110
  		2r1.0000000000000000000000111
  		2r1.1111111111111111111111001
  		2r1.1111111111111111111111010
  		2r1.1111111111111111111111011
  		2r1.1111111111111111111111101
  		2r1.1111111111111111111111110
  		2r1.1111111111111111111111111
  		
  		"overflow"
  		2r1.1111111111111111111111110e127
  		
  		"gradual underflow"
  		2r0.1111111111111111111111111e-126
  		2r0.1111111111111111111111110e-126
  		2r0.1111111111111111111111101e-126
  		2r0.1111111111111111111111011e-126
  		2r0.1111111111111111111111010e-126
  		2r0.1111111111111111111111001e-126
  		2r0.0000000000000000000000111e-126
  		2r0.0000000000000000000000110e-126
  		2r0.0000000000000000000000101e-126
  		2r0.0000000000000000000000011e-126
  		2r0.0000000000000000000000010e-126
  		2r0.0000000000000000000000001e-126
  		2r0.0000000000000000000000010000000000000000000000000001e-126
  		) do: [:e |
  			self assert: ((FloatArray with: e) basicAt: 1) = e asIEEE32BitWord.
  			self assert: ((FloatArray with: e negated) basicAt: 1) = e negated asIEEE32BitWord].
  		
  	"special cases"
  	(Array with: Float infinity with: Float negativeInfinity with: Float negativeZero with: Float nan)
  		do: [:e | self assert: ((FloatArray with: e) basicAt: 1) = e asIEEE32BitWord].
  		!

Item was changed:
+ ----- Method: FloatArrayTest>>testVectorOperations (in category 'tests') -----
- ----- Method: FloatArrayTest>>testVectorOperations (in category 'testing') -----
  testVectorOperations
  	
  	"Test primtive cases 'receiver size = argument size'."
  	self assert: (FloatArray withAll: {2.0. 2.0}) equals: (FloatArray withAll: {4.0. 6.0}) / (FloatArray withAll: {2.0. 3.0}).
  	self assert: (FloatArray withAll: {8.0. 9.0}) equals: (FloatArray withAll: {4.0. 4.5}) * (FloatArray withAll: {2.0. 2.0}).
  	self assert: (FloatArray withAll: {6.0. 9.0}) equals: (FloatArray withAll: {4.0. 6.0}) + (FloatArray withAll: {2.0. 3.0}).
  	self assert: (FloatArray withAll: {2.0. 3.0}) equals: (FloatArray withAll: {4.0. 6.0}) - (FloatArray withAll: {2.0. 3.0}).
  	self assert: 26 equals: ((FloatArray withAll: {4.0. 6.0}) dot: (FloatArray withAll: {2.0. 3.0})).
  	
  	"Test corner cases where 'receiver size < argument size'."
  	self should: [(FloatArray withAll: {4.0. 6.0}) / (FloatArray withAll: {2.0. 3.0. 42.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0}) * (FloatArray withAll: {2.0. 3.0. 42.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0}) + (FloatArray withAll: {2.0. 3.0. 42.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0}) - (FloatArray withAll: {2.0. 3.0. 42.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0}) dot: (FloatArray withAll: {2.0. 3.0. 42.0})] raise: Error.
  	
  	"Test corner cases where 'receiver size > argument size'."
  	self should: [(FloatArray withAll: {4.0. 6.0. 42.0}) / (FloatArray withAll: {2.0. 3.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0. 42.0}) * (FloatArray withAll: {2.0. 3.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0. 42.0}) + (FloatArray withAll: {2.0. 3.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0. 42.0}) - (FloatArray withAll: {2.0. 3.0})] raise: Error.
  	self should: [(FloatArray withAll: {4.0. 6.0. 42.0}) dot: (FloatArray withAll: {2.0. 3.0})] raise: Error.
  
  
  
  !

Item was changed:
+ ----- Method: GeneratorTest>>testAtEnd (in category 'tests') -----
- ----- Method: GeneratorTest>>testAtEnd (in category 'testing') -----
  testAtEnd
  	| generator |
  	generator := self numbersBetween: 1 and: 3.
  	self deny: generator atEnd.
  	generator next.
  	self deny: generator atEnd.
  	generator next.
  	self deny: generator atEnd.
  	generator next.
  	self assert: generator atEnd!

Item was changed:
+ ----- Method: GeneratorTest>>testClose (in category 'tests') -----
- ----- Method: GeneratorTest>>testClose (in category 'testing') -----
  testClose
  	| generator doEnsure notEnsure |
  	doEnsure := notEnsure := 0.
  	[ generator := Generator on: [ :g |
  		[ g yield: 1; yield: 2 ]
  			ensure: [ doEnsure := doEnsure + 1 ] ].
  	self assert: doEnsure = 0; assert: notEnsure = 0.
  	self assert: generator peek = 1.
  	self assert: doEnsure = 0; assert: notEnsure = 0.
  	generator close.
  	self assert: doEnsure = 1; assert: notEnsure = 0 ]
  		ensure: [ notEnsure := notEnsure + 1 ].
  	self assert: doEnsure = 1; assert: notEnsure = 1!

Item was changed:
+ ----- Method: GeneratorTest>>testContents (in category 'tests') -----
- ----- Method: GeneratorTest>>testContents (in category 'testing') -----
  testContents
  	| generator |
  	generator := self numbersBetween: 1 and: 3.
  	self assert: generator contents = #(1 2 3)!

Item was changed:
+ ----- Method: GeneratorTest>>testEmpty (in category 'tests') -----
- ----- Method: GeneratorTest>>testEmpty (in category 'testing') -----
  testEmpty
  	| generator |
  	generator := Generator on: [ :g | ].
  	self assert: generator atEnd.
  	self assert: generator peek isNil.
  	self assert: generator next isNil!

Item was changed:
+ ----- Method: GeneratorTest>>testEnsure (in category 'tests') -----
- ----- Method: GeneratorTest>>testEnsure (in category 'testing') -----
  testEnsure
  	| generator |
  	generator := Generator on: [ :g |
  		[ g yield: 1; yield: 2 ]
  			ensure: [ g yield: 3 ] ].
  	self assert: generator upToEnd asArray = #( 1 2 3 )!

Item was changed:
+ ----- Method: GeneratorTest>>testErrorPropagation (in category 'tests') -----
- ----- Method: GeneratorTest>>testErrorPropagation (in category 'testing') -----
  testErrorPropagation
  	"Ensure that errors in the generator block are properly propagated"
  	| generator |
  	generator := Generator on: [ :g | g yield: 1. g error: 'yo'].
  	self should:[generator next] raise: Error.
  !

Item was changed:
+ ----- Method: GeneratorTest>>testFibonacci (in category 'tests') -----
- ----- Method: GeneratorTest>>testFibonacci (in category 'testing') -----
  testFibonacci
  	| generator |
  	generator := self fibonacciSequence.
  	self assert: (generator next: 10) asArray = #( 1 1 2 3 5 8 13 21 34 55 )!

Item was changed:
+ ----- Method: GeneratorTest>>testNext (in category 'tests') -----
- ----- Method: GeneratorTest>>testNext (in category 'testing') -----
  testNext
  	| generator |
  	generator := self numbersBetween: 1 and: 3.
  	self assert: generator next = 1.
  	self assert: generator next = 2.
  	self assert: generator next = 3.
  	self assert: generator next isNil!

Item was changed:
+ ----- Method: GeneratorTest>>testPeek (in category 'tests') -----
- ----- Method: GeneratorTest>>testPeek (in category 'testing') -----
  testPeek
  	| generator |
  	generator := self numbersBetween: 1 and: 3.
  	self assert: generator peek = 1.
  	self assert: generator peek = 1.
  	generator next.
  	self assert: generator peek = 2!

Item was changed:
+ ----- Method: GeneratorTest>>testReset (in category 'tests') -----
- ----- Method: GeneratorTest>>testReset (in category 'testing') -----
  testReset
  	| generator |
  	generator := self numbersBetween: 1 and: 3.
  	self assert: generator next = 1.
  	self assert: generator next = 2.
  	generator reset.
  	self assert: generator next = 1.
  	self assert: generator next = 2.
  	self assert: generator next = 3.
  	self assert: generator next = nil.
  	generator reset.
  	self assert: generator next = 1!

Item was changed:
+ ----- Method: GeneratorTest>>testResetUnwind (in category 'tests') -----
- ----- Method: GeneratorTest>>testResetUnwind (in category 'testing') -----
  testResetUnwind
  	"Just like close, just using reset"
  	| generator doEnsure notEnsure |
  	doEnsure := notEnsure := 0.
  	[ generator := Generator on: [ :g |
  		[ g yield: 1; yield: 2 ]
  			ensure: [ doEnsure := doEnsure + 1 ] ].
  	self assert: doEnsure = 0; assert: notEnsure = 0.
  	self assert: generator peek = 1.
  	self assert: doEnsure = 0; assert: notEnsure = 0.
  	generator reset.
  	self assert: doEnsure = 1; assert: notEnsure = 0 ]
  		ensure: [ notEnsure := notEnsure + 1 ].
  	self assert: doEnsure = 1; assert: notEnsure = 1!

Item was changed:
+ ----- Method: GeneratorTest>>testSimple (in category 'tests') -----
- ----- Method: GeneratorTest>>testSimple (in category 'testing') -----
  testSimple
  	| generator |
  	generator := Generator on: [ :g | g yield: 1; yield: 2 ].
  	self assert: generator upToEnd asArray = #( 1 2 )!

Item was changed:
+ ----- Method: HashedCollectionTest>>testCapacity (in category 'tests - integrity') -----
- ----- Method: HashedCollectionTest>>testCapacity (in category 'test - integrity') -----
  testCapacity
  
  	| inconsistentCollections |
  	inconsistentCollections := HashedCollection allSubInstances reject: [ :each |
  		each class == MethodDictionary "MethodDictionary is the only HashedCollection which doesn't have prime array size"
  			ifTrue: [ each capacity isPowerOfTwo ]
  			ifFalse: [ each capacity isPrime ] ].
  	self assert: inconsistentCollections isEmpty!

Item was changed:
+ ----- Method: HashedCollectionTest>>testGoodPrimeAtLeast (in category 'tests - class - sizing') -----
- ----- Method: HashedCollectionTest>>testGoodPrimeAtLeast (in category 'test - class - sizing') -----
  testGoodPrimeAtLeast
  
  	| primes |
  	primes := HashedCollection goodPrimes.
  	primes do: [ :each |
  		self assert: (HashedCollection goodPrimeAtLeast: each) = each.
  		self assert: (HashedCollection goodPrimeAtLeast: each - 1) = each.
  		self assert: (HashedCollection goodPrimeAtLeast: each + 1) > each ].
  	(0 to: 1000) do: [ :each |
  		| goodPrime |
  		goodPrime := HashedCollection goodPrimeAtLeast: each.
  		self assert: goodPrime isPrime.
  		self assert: goodPrime >= each.
  		self assert: (primes detect: [ :ea | ea >= each ] ifNone: [ each + 1 ]) = goodPrime ].
  	self assert: (HashedCollection goodPrimeAtLeast: primes last + 1) odd!

Item was changed:
+ ----- Method: HashedCollectionTest>>testGoodPrimes (in category 'tests - class - sizing') -----
- ----- Method: HashedCollectionTest>>testGoodPrimes (in category 'test - class - sizing') -----
  testGoodPrimes
  
  	self testPrimes: HashedCollection goodPrimes!

Item was changed:
+ ----- Method: HashedCollectionTest>>testPrimes: (in category 'tests - class - sizing') -----
- ----- Method: HashedCollectionTest>>testPrimes: (in category 'test - class - sizing') -----
  testPrimes: primes
  
  	| badPrimes |
  	badPrimes := #(3 5 71 139 479 5861 277421). "These primes are less than the hashMultiply constant (1664525) and 1664525 \\ prime is close to 0 (mod prime). The following snippet reproduces these numbers: 
  	| hashMultiplyConstant |
  	hashMultiplyConstant := 1 hashMultiply.
  	(Integer primesUpTo: hashMultiplyConstant) select: [ :each |
  		| remainder |
  		remainder := hashMultiplyConstant \\ each.
  		remainder <= 1 or: [ remainder + 1 = each ] ]."
  	self assert: primes isSorted.
  	primes do: [ :each |
  		self assert: each isPrime.
  		self deny: (each > 2069 and: [ badPrimes includes: each ]) ].
  	self assert: (
  		primes select: [ :p |
  			| result |
  			result := false.
  			p > 2069 ifTrue: [
  			1 to: 8 do: [ :k |
  				1 to: 32 do: [ :a |
  					(p gcd: (256 raisedTo: k) + a) = 1 ifFalse: [
  						result := true ].
  					(p gcd: (256 raisedTo: k) - a) = 1 ifFalse: [
  						result := true ] ] ] ].
  			result ]) isEmpty.!

Item was changed:
+ ----- Method: HashedCollectionTest>>testSizeFor (in category 'tests - class - sizing') -----
- ----- Method: HashedCollectionTest>>testSizeFor (in category 'test - class - sizing') -----
  testSizeFor
  
  	#(
  		0 1 5 10 30 57 89 578 1234 1912 2411 2591 5627 7849
  		10999 61356 68602 73189 79868 86789 239984 239985 501175 661865 841558
  		9669391 15207345 19827345 23469817 27858432 65223175 106650047
  		157687845 190892299 234947087 264782114 269617510 270995400 
  		392236508 456647275 468699153 606865011 606997796 617927086
  		837938371 880614337 989233852 1000473294 1060034095) do: [ :each |
  			| size |
  			size := HashedCollection sizeFor: each.
  			size <= HashedCollection goodPrimes last ifTrue: [
  				self assert: size isPrime ].
  			self assert: size odd.
  			self assert: size * 3 // 4 >= each ]!

Item was changed:
+ ----- Method: LinkedListTest>>test01add (in category 'tests') -----
- ----- Method: LinkedListTest>>test01add (in category 'testing') -----
  test01add
  	self assert: list isEmpty.
  	list add: link1.
  	self assert: list size = 1.
  	self assert: list first = link1.
  	
  	list add: link2.
  	self assert: list size = 2.
  	self assert: list first = link1.
  	self assert: list second = link2.
  	
  	list add: link3.
  	self assert: list size = 3.
  	self assert: list first = link1.
  	self assert: list second = link2.
  	self assert: list third = link3.
  	
  	list add: link4.
  	self assert: list size = 4.
  	self assert: list first = link1.
  	self assert: list second = link2.
  	self assert: list third = link3.
  	self assert: list fourth = link4!

Item was changed:
+ ----- Method: LinkedListTest>>test02addLast (in category 'tests') -----
- ----- Method: LinkedListTest>>test02addLast (in category 'testing') -----
  test02addLast
  	self assert: list isEmpty.
  	
  	list addLast: link1.
  	self assert: list size = 1.
  	self assert: list first = link1.
  	
  	list addLast: link2.
  	self assert: list size = 2.
  	self assert: list first = link1.
  	self assert: list second = link2.
  	
  	list addLast: link3.
  	self assert: list size = 3.
  	self assert: list first = link1.
  	self assert: list second = link2.
  	self assert: list third = link3.
  	
  	list addLast: link4.
  	self assert: list size = 4.
  	self assert: list first = link1.
  	self assert: list second = link2.
  	self assert: list third = link3.
  	self assert: list fourth = link4!

Item was changed:
+ ----- Method: LinkedListTest>>test03addFirst (in category 'tests') -----
- ----- Method: LinkedListTest>>test03addFirst (in category 'testing') -----
  test03addFirst
  	self assert: list isEmpty.
  	
  	list addFirst: link1.
  	self assert: list size = 1.
  	self assert: list first = link1.
  	
  	list addFirst: link2.
  	self assert: list size = 2.
  	self assert: list first = link2.
  	self assert: list second = link1.
  	
  	list addFirst: link3.
  	self assert: list size = 3.
  	self assert: list first = link3.
  	self assert: list second = link2.
  	self assert: list third = link1.
  	
  	list addFirst: link4.
  	self assert: list size = 4.
  	self assert: list first = link4.
  	self assert: list second = link3.
  	self assert: list third = link2.
  	self assert: list fourth = link1!

Item was changed:
+ ----- Method: LinkedListTest>>test04addBefore (in category 'tests') -----
- ----- Method: LinkedListTest>>test04addBefore (in category 'testing') -----
  test04addBefore
  	self assert: list isEmpty.
  	
  	list add: link1.
  	self assert: list size = 1.
  	self assert: list first == link1.
  	
  	list add: link2 before: link1.
  	self assert: list size = 2.
  	self assert: list first == link2.
  	self assert: list second == link1.
  	
  	list add: link3 before: link1.
  	self assert: list size = 3.
  	self assert: list first == link2.
  	self assert: list second == link3.
  	self assert: list third == link1.
  	
  	list add: link4 before: link1.
  	self assert: list size = 4.
  	self assert: list first == link2.
  	self assert: list second == link3.
  	self assert: list third == link4.
  	self assert: list fourth == link1!

Item was changed:
+ ----- Method: LinkedListTest>>test05addBefore (in category 'tests') -----
- ----- Method: LinkedListTest>>test05addBefore (in category 'testing') -----
  test05addBefore
  	self assert: list isEmpty.
  	
  	list add: link1.
  	self assert: list size = 1.
  	self assert: list first == link1.
  	
  	list add: link2 before: link1.
  	self assert: list size = 2.
  	self assert: list first == link2.
  	self assert: list second == link1.
  	
  	list add: link3 before: link2.
  	self assert: list size = 3.
  	self assert: list first == link3.
  	self assert: list second == link2.
  	self assert: list third == link1.
  	
  	list add: link4 before: link3.
  	self assert: list size = 4.
  	self assert: list first == link4.
  	self assert: list second == link3.
  	self assert: list third == link2.
  	self assert: list fourth == link1!

Item was changed:
+ ----- Method: LinkedListTest>>test06addAfter (in category 'tests') -----
- ----- Method: LinkedListTest>>test06addAfter (in category 'testing') -----
  test06addAfter
  	self assert: list isEmpty.
  	
  	list add: link1.
  	self assert: list size = 1.
  	self assert: list first == link1.
  	
  	list add: link2 after: link1.
  	self assert: list size = 2.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	
  	list add: link3 after: link2.
  	self assert: list size = 3.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link3.
  	
  	list add: link4 after: link3.
  	self assert: list size = 4.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link3.
  	self assert: list fourth == link4!

Item was changed:
+ ----- Method: LinkedListTest>>test07addAfter (in category 'tests') -----
- ----- Method: LinkedListTest>>test07addAfter (in category 'testing') -----
  test07addAfter
  	self assert: list isEmpty.
  	
  	list add: link1.
  	self assert: list size = 1.
  	self assert: list first == link1.
  	
  	list add: link2 after: link1.
  	self assert: list size = 2.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	
  	list add: link3 after: link1.
  	self assert: list size = 3.
  	self assert: list first == link1.
  	self assert: list second == link3.
  	self assert: list third == link2.
  	
  	list add: link4 after: link1.
  	self assert: list size = 4.
  	self assert: list first == link1.
  	self assert: list second == link4.
  	self assert: list third == link3.
  	self assert: list fourth == link2!

Item was changed:
+ ----- Method: LinkedListTest>>test08addAfter (in category 'tests') -----
- ----- Method: LinkedListTest>>test08addAfter (in category 'testing') -----
  test08addAfter
  	| l first |
  	l := LinkedList new.
  	first := self class new n: 1.
  	
  	l add: first.
  	l add: (self class new n: 3).
  
  	self assert: (l collect:[:e | e n]) asArray  = #(1 3).
  	
  	l add: (self class new n: 2) after: first.
  
  	self assert: (l collect:[:e | e n]) asArray  = #(1 2 3).!

Item was changed:
+ ----- Method: LinkedListTest>>test09addAfter (in category 'tests') -----
- ----- Method: LinkedListTest>>test09addAfter (in category 'testing') -----
  test09addAfter
  	| l last |
  	l := LinkedList new.
  	last := self class new n: 2.
  	l add: (self class new n: 1).
  	l add: last.
  	
  	self assert: (l collect:[:e | e n]) asArray  = #(1 2).
  	 
  	l add: (self class new n: 3) after: last.
  
  	self assert: (l collect:[:e | e n]) asArray  = #(1 2 3).!

Item was changed:
+ ----- Method: LinkedListTest>>test0FixtureIterateTest (in category 'tests - fixture') -----
- ----- Method: LinkedListTest>>test0FixtureIterateTest (in category 'test - fixture') -----
  test0FixtureIterateTest
  	| res |
  	self collectionWithoutNilElements.
  	self assert: (self collectionWithoutNilElements occurrencesOf: nil) = 0.
  	res := true.
  	self collectionWithoutNilElements
  		detect: [ :each | (self collectionWithoutNilElements occurrencesOf: each) > 1 ]
  		ifNone: [ res := false ].
  	self assert: res = false!

Item was changed:
+ ----- Method: LinkedListTest>>test10removeFirst (in category 'tests') -----
- ----- Method: LinkedListTest>>test10removeFirst (in category 'testing') -----
  test10removeFirst
  	list add: link1.
  	list add: link2.
  	list add: link3.
  	list add: link4.
  	
  	self assert: list size = 4.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link3.
  	self assert: list fourth == link4.
  	
  	list removeFirst.
  	self assert: list size = 3.
  	self assert: list first == link2.
  	self assert: list second == link3.
  	self assert: list third == link4.
  	
  	list removeFirst.
  	self assert: list size = 2.
  	self assert: list first == link3.
  	self assert: list second == link4.
  	
  	list removeFirst.
  	self assert: list size = 1.
  	self assert: list first == link4.
  	
  	list removeFirst.
  	self assert: list isEmpty!

Item was changed:
+ ----- Method: LinkedListTest>>test11removeLast (in category 'tests') -----
- ----- Method: LinkedListTest>>test11removeLast (in category 'testing') -----
  test11removeLast
  	list add: link1.
  	list add: link2.
  	list add: link3.
  	list add: link4.
  	
  	self assert: list size = 4.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link3.
  	self assert: list fourth == link4.
  	
  	list removeLast.
  	self assert: list size = 3.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link3.
  	
  	list removeLast.
  	self assert: list size = 2.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	
  	list removeLast.
  	self assert: list size = 1.
  	self assert: list first == link1.
  	
  	list removeFirst.
  	self assert: list isEmpty!

Item was changed:
+ ----- Method: LinkedListTest>>test12remove (in category 'tests') -----
- ----- Method: LinkedListTest>>test12remove (in category 'testing') -----
  test12remove
  	list add: link1.
  	list add: link2.
  	list add: link3.
  	list add: link4.
  	
  	self assert: list size = 4.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link3.
  	self assert: list fourth == link4.
  	
  	list remove: link3.
  	self assert: list size = 3.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link4.
  	
  	list remove: link2.
  	self assert: list size = 2.
  	self assert: list first == link1.
  	self assert: list second == link4.
  	
  	list remove: link1.
  	self assert: list size = 1.
  	self assert: list first == link4.
  	
  	list remove: link4.
  	self assert: list isEmpty!

Item was changed:
+ ----- Method: LinkedListTest>>test13remove (in category 'tests') -----
- ----- Method: LinkedListTest>>test13remove (in category 'testing') -----
  test13remove
  	list add: link1.
  	list add: link2.
  	list add: link3.
  	list add: link4.
  	
  	self assert: list size = 4.
  	self assert: list first == link1.
  	self assert: list second == link2.
  	self assert: list third == link3.
  	self assert: list fourth == link4.
  	
  	list remove: link1.
  	self assert: list size = 3.
  	self assert: list first == link2.
  	self assert: list second == link3.
  	self assert: list third == link4.
  	
  	list remove: link4.
  	self assert: list size = 2.
  	self assert: list first == link2.
  	self assert: list second == link3.
  	
  	list remove: link2.
  	self assert: list size = 1.
  	self assert: list first == link3.
  	
  	list remove: link3.
  	self assert: list isEmpty!

Item was changed:
+ ----- Method: LinkedListTest>>test14removeIfAbsent (in category 'tests') -----
- ----- Method: LinkedListTest>>test14removeIfAbsent (in category 'testing') -----
  test14removeIfAbsent
  	list add: link1.
  	
  	self assert: list size = 1.
  	self assert: list first == link1.
  	
  	list remove: link1.
  	self assert: list isEmpty.
  	
  	[list remove: link1]
  		on: Error
  		do: [^ self].
  		
  	"The execution should not get here. If yes, something went wrong."
  	self assert: false!

Item was changed:
+ ----- Method: LinkedListTest>>test22addAll (in category 'tests') -----
- ----- Method: LinkedListTest>>test22addAll (in category 'testing') -----
  test22addAll
  	| link5 link6 link7 link8 listToBeAdded |
  	link5 := Link new.
  	link6 := Link new.
  	link7 := Link new.
  	link8 := Link new.
  	
  	list
  		add: link1;
  		add: link2;
  		add: link3;
  		add: link4.
  		
  	listToBeAdded := LinkedList new.
  	listToBeAdded
  		add: link5;
  		add: link6;
  		add: link7;
  		add: link8.
  		
  	list addAll: listToBeAdded.
  	
  	self should: [(list at: 1) == link1].
  	self should: [(list at: 2) == link2].
  	self should: [(list at: 3) == link3].
  	self should: [(list at: 4) == link4].
  	self should: [(list at: 5) == link5].
  	self should: [(list at: 6) == link6].
  	self should: [(list at: 7) == link7].
  	self should: [(list at: 8) == link8].!

Item was changed:
+ ----- Method: LinkedListTest>>testEqualSign (in category 'tests - equality') -----
- ----- Method: LinkedListTest>>testEqualSign (in category 'test - equality') -----
  testEqualSign
  	"self debug: #testEqualSign"
  
  	self deny: (self empty = self nonEmpty).!

Item was changed:
+ ----- Method: LinkedListTest>>testEqualSignIsTrueForNonIdenticalButEqualCollections (in category 'tests - equality') -----
- ----- Method: LinkedListTest>>testEqualSignIsTrueForNonIdenticalButEqualCollections (in category 'test - equality') -----
  testEqualSignIsTrueForNonIdenticalButEqualCollections
  	"self debug: #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 nonEmpty = self nonEmpty copy). 
  	self assert: (self nonEmpty copy = self nonEmpty).
  	self assert: (self nonEmpty copy = self nonEmpty copy).!

Item was changed:
+ ----- Method: LinkedListTest>>testEqualSignOfIdenticalCollectionObjects (in category 'tests - equality') -----
- ----- Method: LinkedListTest>>testEqualSignOfIdenticalCollectionObjects (in category 'test - equality') -----
  testEqualSignOfIdenticalCollectionObjects
  	"self debug: #testEqualSignOfIdenticalCollectionObjects"
  	
  	self assert: (self empty = self empty). 
  	self assert: (self nonEmpty = self nonEmpty). 
  	!

Item was changed:
+ ----- Method: LinkedListTest>>testRemoveAll (in category 'tests') -----
- ----- Method: LinkedListTest>>testRemoveAll (in category 'testing') -----
  testRemoveAll
  	| list2 |
  	list add: link1.
  	list add: link2.
  	list add: link3.
  	list add: link4.
  	list2 := list copy.
  	list removeAll.
  	
  	self assert: list size = 0.
  	self assert: list2 size = 4 description: 'the copy has not been modified'!

Item was changed:
+ ----- Method: MatrixTest>>setUp (in category 'running') -----
- ----- Method: MatrixTest>>setUp (in category 'testing') -----
  setUp
  	matrix1 := Matrix new: 2.
  	matrix1 at:1 at:1 put: 1.
  	matrix1 at:1 at:2 put: 3.
  	matrix1 at:2 at:1 put: 2.
  	matrix1 at:2 at:2 put: 4.
  	
  	matrix2 := Matrix new: 2.
  	matrix2 at:1 at:1 put: 3.
  	matrix2 at:1 at:2 put: 7.
  	matrix2 at:2 at:1 put: 4.
  	matrix2 at:2 at:2 put: 8.!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAdd (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAdd (in category 'testsAdding') -----
  testAdd
  	| l |
  	l := #(1 2 3 4) asOrderedCollection.
  	l add: 88.
  	self assert: (l =  #(1 2 3 4 88) asOrderedCollection).
  	l add: 99.
  	self assert: (l =  #(1 2 3 4 88 99) asOrderedCollection). 
  
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddAfter (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddAfter (in category 'testsAdding') -----
  testAddAfter
  
  	| l |
  	l := #(1 2 3 4) asOrderedCollection.
  	l add: 88 after: 1.
  	self assert: (l =  #(1 88 2 3 4) asOrderedCollection).
  	l add: 99 after: 2.
  	self assert: (l =  #(1 88 2 99 3 4) asOrderedCollection). 
  
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddAfterIndex (in category 'tests - public methods') -----
- ----- Method: OrderedCollectionTest>>testAddAfterIndex (in category 'testing-public methods') -----
  testAddAfterIndex
  	"self run: #testAddAfterIndex"
  	| l |
  	l := #(1 2 3 4) asOrderedCollection.
  	l add: 77 afterIndex: 0.
  	self assert: (l =  #(77 1 2 3 4) asOrderedCollection).
  	l add: 88 afterIndex: 2.
  	self assert: (l =  #(77 1 88 2 3 4) asOrderedCollection). 
  	l add: 99 afterIndex: l size.
  	self assert: (l =  #(77 1 88 2 3 4 99) asOrderedCollection). 
  	self should:[l add: 666 afterIndex: -1] raise: Error.
  	self should:[l add: 666 afterIndex: l size+1] raise: Error.
  	
  	"Now make room by removing first two and last two elements,
  	and see if the illegal bounds test still fails"
  	(l first: 2) , (l last: 2) reversed do: [:e | l remove: e].
  	self should: [l add: 666 afterIndex: -1] raise: Error.
  	self should: [l add: 666 afterIndex: l size+1] raise: Error.!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddAll (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddAll (in category 'testsAdding') -----
  testAddAll
  	"Allows one to add each element of an orderedCollection at the end of another
  	orderedCollection "
  	"self run:#testAddAll" 
  	
  	| c1 c2 |
  	c1 := #(1 2 3 4 ) asOrderedCollection.
  	c2 := #(5 6 7 8 9 ) asOrderedCollection.
  	c1 addAll: c2.
  	self assert: c1 = #(1 2 3 4 5 6 7 8 9) asOrderedCollection!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddAllFirst (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddAllFirst (in category 'testsAdding') -----
  testAddAllFirst
  	"Allows one to add each element of an orderedCollection at the beginning of another
  	orderedCollection "
  	"self run:#testAddAllFirst" 
  	
  	| c1 c2 |
  	c1 := #(1 2 3 4 ) asOrderedCollection.
  	c2 := #(5 6 7 8 9 ) asOrderedCollection.
  	c2 addAllFirst: c1.
  	self assert: c2 = #(1 2 3 4 5 6 7 8 9) asOrderedCollection!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddAllFirstUnlessAlreadyPresent (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddAllFirstUnlessAlreadyPresent (in category 'testsAdding') -----
  testAddAllFirstUnlessAlreadyPresent
  	"Allows one to add each element of an orderedCollection at the beginning of
  	another orderedCollection preserving the order but no duplicate element"
  	"self run:#testAddAllFirstUnlessAlreadyPresent" 
  	
  	| c1 c2 c3 |
  	c1 := #(1 2 3 4 ) asOrderedCollection.
  	c2 := #(5 6 7 8 9 ) asOrderedCollection.
  	c3 := #(0 1 ) asOrderedCollection.
  	c2 addAllFirstUnlessAlreadyPresent: c1.
  	self assert: c2 = #(1 2 3 4 5 6 7 8 9 ) asOrderedCollection.
  	c1 addAllFirstUnlessAlreadyPresent: c3.
  	self deny: c1 = #(0 1 1 2 3 4 ) asOrderedCollection.
  	self assert: c1 = #(0 1 2 3 4 ) asOrderedCollection.
  	!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddAllLast (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddAllLast (in category 'testsAdding') -----
  testAddAllLast
  	"Allows one to add each element of an orderedCollection at the beginning of another
  	orderedCollection "
  	"self run:#testAddAllLast" 
  	
  	| c1 c2 |
  	c1 := #(1 2 3 4 ) asOrderedCollection.
  	c2 := #(5 6 7 8 9 ) asOrderedCollection.
  	c1 addAllLast: c2.
  	self assert: c1 = #(1 2 3 4 5 6 7 8 9) asOrderedCollection!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddBefore (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddBefore (in category 'testsAdding') -----
  testAddBefore
  
  	| l |
  	l := #(1 2 3 4) asOrderedCollection.
  	l add: 88 before: 1.
  	self assert: (l =  #(88 1 2 3 4) asOrderedCollection).
  	l add: 99 before: 2.
  	self assert: (l =  #(88 1 99 2 3 4) asOrderedCollection). 
  
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddBeforeAndRemove (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddBeforeAndRemove (in category 'testsAdding') -----
  testAddBeforeAndRemove
  
  	| l initialCollection |
  	l := #(1 2 3 4) asOrderedCollection.
  	initialCollection := l shallowCopy.
  	l add: 88 before: 1.
  	self assert: (l =  #(88 1 2 3 4) asOrderedCollection).
  	l add: 99 before: 2.
  	self assert: (l =  #(88 1 99 2 3 4) asOrderedCollection). 
  	l remove: 99.
  	l remove: 88.
  	self assert: l = initialCollection.
  
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddBeforeIndex (in category 'tests - public methods') -----
- ----- Method: OrderedCollectionTest>>testAddBeforeIndex (in category 'testing-public methods') -----
  testAddBeforeIndex
  	"self run: #testAddBeforeIndex"
  	| l |
  	l := #(1 2 3 4) asOrderedCollection.
  	l add: 77 beforeIndex: 1.
  	self assert: (l =  #(77 1 2 3 4) asOrderedCollection).
  	l add: 88 beforeIndex: 3.
  	self assert: (l =  #(77 1 88 2 3 4) asOrderedCollection). 
  	l add: 99 beforeIndex: l size+1.
  	self assert: (l =  #(77 1 88 2 3 4 99) asOrderedCollection). 
  	self should:[l add: 666 beforeIndex: 0] raise: Error.
  	self should:[l add: 666 beforeIndex: l size+2] raise: Error.
  	
  	"Now make room by removing first two and last two elements,
  	and see if the illegal bounds test still fails"
  	(l first: 2) , (l last: 2) reversed do: [:e | l remove: e].
  	self should:[l add: 666 beforeIndex: 0] raise: Error.
  	self should:[l add: 666 beforeIndex: l size+2] raise: Error.
  
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddDuplicateItem1 (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddDuplicateItem1 (in category 'testsAdding') -----
  testAddDuplicateItem1
  	| collection |
  	collection := #('Jim' 'Mary' 'John' 'Andrew' ) asOrderedCollection.
  	collection add: 'John' before: 'John'.
  	self
  		assert: ((collection asBag occurrencesOf: 'John')
  					= 2
  				and: [(collection at: (collection indexOf: 'John')
  							+ 1)
  						= (collection
  								at: (collection indexOf: 'John'))])!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddFirst (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddFirst (in category 'testsAdding') -----
  testAddFirst
  	| l |
  	l := #(1 2 3 4) asOrderedCollection.
  	l addFirst: 88.
  	self assert: (l =  #(88 1 2 3 4) asOrderedCollection).
  	l addFirst: 99.
  	self assert: (l =  #(99 88 1 2 3 4) asOrderedCollection). 
  
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddItem1 (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddItem1 (in category 'testsAdding') -----
  testAddItem1
  
     | collection size |
     collection := #('Jim' 'Mary' 'John' 'Andrew' ) asOrderedCollection.
     size := collection size.
     collection add: 'James' before: 'Jim'.
     collection add: 'Margaret' before: 'Andrew'.
     self assert: size + 2 = collection size.
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddItem2 (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddItem2 (in category 'testsAdding') -----
  testAddItem2
  	| collection |
  	collection := #('Jim' 'Mary' 'John' 'Andrew' ) asOrderedCollection.
  	collection add: 'James' before: 'Jim'.
  	collection add: 'Margaret' before: 'Andrew'.
  	self assert: (collection indexOf: 'James')
  			+ 1
  			= (collection indexOf: 'Jim').
  	self assert: (collection indexOf: 'Margaret')
  			+ 1
  			= (collection indexOf: 'Andrew')!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAddLast (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAddLast (in category 'testsAdding') -----
  testAddLast
  	| l |
  	l := #(1 2 3 4) asOrderedCollection.
  	l addLast: 88.
  	self assert: (l =  #(1 2 3 4 88) asOrderedCollection).
  	l addLast: 99.
  	self assert: (l =  #(1 2 3 4 88 99) asOrderedCollection). 
  
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAt (in category 'tests - accessing') -----
- ----- Method: OrderedCollectionTest>>testAt (in category 'testsAccessing') -----
  testAt
  	| collection |
  	collection := #('Jim' 'Mary' 'John' 'Andrew' ) asOrderedCollection.
  	self assert: (collection at:1) = 'Jim'.
  	self assert: (collection at:2) = 'Mary'!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAtIfAbsentPut (in category 'tests - adding') -----
- ----- Method: OrderedCollectionTest>>testAtIfAbsentPut (in category 'testsAdding') -----
  testAtIfAbsentPut
  	"Allows one to add an element at an index if no element exist at this index"
  	"self run:#testAtIfAbsentPut" 
  	
  	| c |
  	c := #(1 2 3 4 ) asOrderedCollection.
  	c at: 2 ifAbsentPut: [5].
  	self assert: #(1 2 3 4 ) asOrderedCollection equals: c.
  	c at: 5 ifAbsentPut: [5].
  	self assert: #(1 2 3 4 5 ) asOrderedCollection equals: c.
  	c at: 7 ifAbsentPut: [7].
  	self assert: #(1 2 3 4 5 nil 7 ) asOrderedCollection equals: c.!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testAtPut (in category 'tests - accessing') -----
- ----- Method: OrderedCollectionTest>>testAtPut (in category 'testsAccessing') -----
  testAtPut
  	"Allows one to replace an element but not at an off range index"
  	"self run:#testAtPut"
  	| c |
  	c := #(1 2 3 4 ) asOrderedCollection.
  	c at: 2 put: 5.
  	self assert: c = #(1 5 3 4 ) asOrderedCollection.
  	self
  		should: [c at: 5 put: 8]
  		raise: Error.
  	self deny: c = #(1 5 3 4 8 ) asOrderedCollection!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testCapacity (in category 'tests - accessing') -----
- ----- Method: OrderedCollectionTest>>testCapacity (in category 'testsAccessing') -----
  testCapacity
  	"Allows one to check the current capacity of an Ordered collection"
  	"self run:#testCapacity"
  	
  	| c1 c2 c3 |
  	c1 := #(1 2 ) asOrderedCollection.
  	self assert: (c1 capacity =  2).
  	c2 := OrderedCollection new: 10.
  	c2 add: 3.
  	self assert: (c2 capacity = 10).	
  	c3 := OrderedCollection new.
  	self deny: (c3 capacity =  0).
  	!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testCollect (in category 'tests - enumerating') -----
- ----- Method: OrderedCollectionTest>>testCollect (in category 'testsEnumerating') -----
  testCollect
  	"Allows one to collect some element of a collection into another collection"
  	"self run: #testCollect"
  	 
  	| c1 c2 res |
  	c1 := #(-1 2 -3 4) asOrderedCollection.
  	c2 := #(1 2 3 4) asOrderedCollection.
  	res := c1 collect: [:each | each abs].
  	self assert: (c2 = res).!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testCollectFromTo (in category 'tests - enumerating') -----
- ----- Method: OrderedCollectionTest>>testCollectFromTo (in category 'testsEnumerating') -----
  testCollectFromTo
  	"Allows one to collect some element of a collection into another collection between a first index and an end index for the collect"
  	"self run: #testCollectFromTo"
  	
  	| c1 res |
  	c1 := #(-1 2 -3 4 -5 6 -7 8) asOrderedCollection.
  	res := c1 collect: [:each | each abs] from: 1 to: 3.
  	self assert: (res = #(1 2 3) asOrderedCollection).
  	self should: [c1 collect: [:each | each abs] from: 10 to: 13] raise: Error.
  	self should: [c1 collect: [:each | each abs] from: 5 to: 2] raise: Error.!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testCopyEmpty (in category 'tests - copying') -----
- ----- Method: OrderedCollectionTest>>testCopyEmpty (in category 'testsCopying') -----
  testCopyEmpty
  	"Allows one to create a copy of the receiver that contains no elements"
  	"self run:#testCopyEmpty"
  	
  	| c1 c2 |
  	c1 := #(1 2 3 4 ) asOrderedCollection.
  	c2 := c1 copyEmpty.
  	self assert: (c2 size = 0).!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testCopyFromTo (in category 'tests - copying') -----
- ----- Method: OrderedCollectionTest>>testCopyFromTo (in category 'testsCopying') -----
  testCopyFromTo
  	"Allows one to create a copy of the receiver that contains elements from position start to end"
  	"self run: #testCopyFromTo"
  	
  	| c1 c2 c3 | 
  	c1 := #(1 2 3 4) asOrderedCollection.
  	c2 := (c1 copyFrom: 1 to: 2).
  	self assert: c2 = #(1 2) asOrderedCollection.
  	self should: [c1 copyFrom: 10 to: 20] raise: Error.
  	
  	c3 := c1 copyFrom: 4 to: 2.
  	self assert: c3 isEmpty.
  	
  	self should: [c1 copyFrom: 4 to: 5 ] raise: Error.
  	
  	
  	
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testCopyReplaceFromToWith (in category 'tests - copying') -----
- ----- Method: OrderedCollectionTest>>testCopyReplaceFromToWith (in category 'testsCopying') -----
  testCopyReplaceFromToWith
  	"Allows one to create a copy from the receiver which elements between start and end of the 	receiver being replace by 	element of the collection after with:"
  	"self run:#testCopyReplaceFromToWith"
  
  	| c1 c2 c3 c4 |
  	c1 := #(1 2 3 4) asOrderedCollection.
  	c2 := #(5 6 7 8 9) asOrderedCollection.
  	c3 := (c2 copyReplaceFrom: 1 to: 2 with: c1).
  	self assert: c3 = #(1 2 3 4 7 8 9) asOrderedCollection.
  	self should: [c2 copyReplaceFrom: 3 to: 1 with: c1] raise: Error.
  	
  	c4 := (c2 copyReplaceFrom: 10 to: 25 with: c1).
  	self assert: c4 = #(5 6 7 8 9 1 2 3 4) asOrderedCollection.
  	
  	!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testCopyWith (in category 'tests - copying') -----
- ----- Method: OrderedCollectionTest>>testCopyWith (in category 'testsCopying') -----
  testCopyWith
  	"Allows one to create a copy of the receiver that contains the new element at the end"
  	"self run: #testCopyWith"
  	
  	| c1 | 
  	c1 := #(1 2 3 4) asOrderedCollection.
  	c1 := c1 copyWith: 6.
  	self assert: c1 = #(1 2 3 4 6) asOrderedCollection.
  	
  	
  
  	
  	
  	
  !

Item was changed:
+ ----- Method: OrderedCollectionTest>>testForceToPadding (in category 'tests - copying') -----
- ----- Method: OrderedCollectionTest>>testForceToPadding (in category 'testsCopying') -----
  testForceToPadding
  	"This is a non regression bug for http://bugs.squeak.org/view.php?id=7296"
  	
  	| c1 c2 paddingElement |
  	"source collection"
  	c1 := #(5 3 7 2 ) asOrderedCollection.
  	paddingElement := nil.
  	
  	"force length to longer"
  	c2 := c1 forceTo: 10 paddingWith: paddingElement.
  	self assert: (c1 ~~ c2) description: 'forceTo:paddingWith: should modify a copy'.
  	self assert: (c2 size = 10).
  	self assert: (c2 copyFrom: 1 to: c1 size) = c1.
  	self assert: ((c1 size + 1 to: c2 size) allSatisfy: [:i | (c2 at: i) = paddingElement]).
  	
  	"force length to shorter"
  	c2 := c1 forceTo: 3 paddingWith: paddingElement.
  	self assert: (c1 ~~ c2) description: 'forceTo:paddingWith: should modify a copy'.
  	self assert: (c2 size = 3).
  	self assert: (c2 copyFrom: 1 to: 3) = (c1 copyFrom: 1 to: 3).
  	
  	"SAME TEST BUT PADDING AT START FOLLOWING..."
  	
  	"force length to longer"
  	c2 := c1 forceTo: 10 paddingStartWith: paddingElement.
  	self assert: (c1 ~~ c2) description: 'forceTo:paddingStartWith: should modify a copy'.
  	self assert: (c2 size = 10).
  	self assert: (c2 copyFrom: c2 size - c1 size + 1 to: c2 size) = c1.
  	self assert: ((1 to: c2 size - c1 size) allSatisfy: [:i | (c2 at: i) = paddingElement]).
  	
  	"force length to shorter"
  	c2 := c1 forceTo: 3 paddingStartWith: paddingElement.
  	self assert: (c1 ~~ c2) description: 'forceTo:paddingStartWith: should modify a copy'.
  	self assert: (c2 size = 3).
  	self assert: (c2 copyFrom: 1 to: 3) = (c1 copyFrom: 1 to: 3).!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testIndexOf (in category 'tests - enumerating') -----
- ----- Method: OrderedCollectionTest>>testIndexOf (in category 'testsEnumerating') -----
  testIndexOf
  	| collection indices |
  	collection := #('Jim' 'Mary' 'John' 'Andrew' ) asOrderedCollection.
  	indices := collection
  				collect: [:item | collection indexOf: item].
  	self assert: (1 to: 4) asOrderedCollection = indices!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testIndexOfWithDuplicates (in category 'tests - enumerating') -----
- ----- Method: OrderedCollectionTest>>testIndexOfWithDuplicates (in category 'testsEnumerating') -----
  testIndexOfWithDuplicates
  
     | collection indices bagOfIndices |
     collection := #('Jim' 'Mary' 'John' 'Andrew' 'Mary' 'John' 'Jim' 'Micheal') asOrderedCollection.
     indices := collection collect: [:item | collection indexOf: item].
     self assert: indices asSet size = collection asSet size.
     bagOfIndices := indices asBag.
     self assert: (indices asSet 
                      allSatisfy: [:index | (bagOfIndices occurrencesOf: index)
  	                                       = (collection occurrencesOf: (collection at: index))]).
  
    "  indexOf:  returns the index of the first occurrence of an item.
       For an item with n occurrences, the index of its first occurrence
       is found  n  times. "!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testOverlappingPairsCollect (in category 'tests - enumerating') -----
- ----- Method: OrderedCollectionTest>>testOverlappingPairsCollect (in category 'testsEnumerating') -----
  testOverlappingPairsCollect
  
  	| o |
  	o := #(5 4 3 2 1) asOrderedCollection.
  	self
  		assert: #(9 7 5 3) asOrderedCollection
  		equals: (o overlappingPairsCollect: [ :a :b | a + b ])!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testRemoveAll (in category 'tests - removing') -----
- ----- Method: OrderedCollectionTest>>testRemoveAll (in category 'testsRemoving') -----
  testRemoveAll
  	"Allows one to remove all elements of a collection" 
  	
  	| c1 c2 s2 |
  	c1 := #(2 3 4 6) asOrderedCollection.
  	c1 addAll: (1 to: 200).
  	c2 := c1 copy.
  	s2 := c2 size.
  	
  	c1 removeAll.
  	
  	self assert: c1 size = 0.
  	self assert: c2 size = s2 description: 'the copy has not been modified'
  	!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testRemoveAllSuchThat (in category 'tests - removing') -----
- ----- Method: OrderedCollectionTest>>testRemoveAllSuchThat (in category 'testsRemoving') -----
  testRemoveAllSuchThat
  	| collection |
  	collection := (1 to: 10) asOrderedCollection.
  	collection
  		removeAllSuchThat: [:e | e even].
  	self assert: collection = (1 to: 10 by: 2) asOrderedCollection!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testRemoveAt (in category 'tests - removing') -----
- ----- Method: OrderedCollectionTest>>testRemoveAt (in category 'testsRemoving') -----
  testRemoveAt
  	"Allows one to remove an element from a collection at an index"
  	"self run:#testRemoveAt" 
  	
  	| c1 |
  	c1 := #(2 3 4 6) asOrderedCollection.
  	c1 removeAt: 2.
  	self assert: (c1 = #(2 4 6) asOrderedCollection).
  	self should: [c1 removeAt: 10] raise: Error.
  	self should: [c1 removeAt: -1] raise: Error.
  	!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testRemoveFirst (in category 'tests - removing') -----
- ----- Method: OrderedCollectionTest>>testRemoveFirst (in category 'testsRemoving') -----
  testRemoveFirst
  	"Allows one to remove n element of a collection at the first"
  	"self run:#testRemoveFirst" 
  	
  	| c1 |
  	c1 := #(2 3 4 6) asOrderedCollection.
  	c1 removeFirst: 1.
  	self assert: (c1 = #(3 4 6) asOrderedCollection).
  	c1 removeFirst: 2.
  	self assert: (c1 = #(6) asOrderedCollection).
  	self should: [c1 removeFirst: 10] raise: Error.
  	
  	!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testRemoveIfAbsent (in category 'tests - removing') -----
- ----- Method: OrderedCollectionTest>>testRemoveIfAbsent (in category 'testsRemoving') -----
  testRemoveIfAbsent
  	"Allows one to remove an element from a collection and to copy it in another collection."
  	"If the element isn't in the first collection, the second collection copy the element after ifAbsent"
  	"self run:#testRemoveIfAbsent"
  	
  	| c1 c2 |
  	c1 := #(1 2 3 4) asOrderedCollection.
  	c2 := OrderedCollection new.
  	
  	c2 add: (c1 remove: 2 ifAbsent: [6]).
  	self assert: (c1 = #(1 3 4) asOrderedCollection).
  	self assert: (c2 = #(2) asOrderedCollection).
  	
  	c2 add: (c1 remove: 18 ifAbsent: [6]).
  	self assert: (c1 = #(1 3 4) asOrderedCollection).
  	self assert: (c2 = #(2 6) asOrderedCollection).!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testRemoveLast (in category 'tests - removing') -----
- ----- Method: OrderedCollectionTest>>testRemoveLast (in category 'testsRemoving') -----
  testRemoveLast
  	"Allows one to remove n element of a collection at the end"
  	"self run:#testRemoveLast" 
  	
  	| c1 |
  	c1 := #(2 3 4 6) asOrderedCollection.
  	c1 removeLast: 1.
  	self assert: (c1 = #(2 3 4) asOrderedCollection).
  	c1 removeLast: 2.
  	self assert: (c1 = #(2) asOrderedCollection).
  	self should: [c1 removeLast: 10] raise: Error.!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testReversed (in category 'tests - copying') -----
- ----- Method: OrderedCollectionTest>>testReversed (in category 'testsCopying') -----
  testReversed
  	| collection1 collection2 |
  	collection1 := #('Jim' 'Mary' 'John' 'Andrew' ) asOrderedCollection.
  	collection2 := collection1 reversed.
  	self assert: collection2 first = 'Andrew'.
  	self assert: collection2 last = 'Jim'!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testSize (in category 'tests - accessing') -----
- ----- Method: OrderedCollectionTest>>testSize (in category 'testsAccessing') -----
  testSize
  	"Allows one to check the size of an Ordered collection"
  	"self run:#testSize"
  	
  	| c1 c2 |
  	c1 := #(1 2 ) asOrderedCollection.
  	self assert: (c1 size =  2).
  	
  	c2 := OrderedCollection new.
  	self assert: (c2 size = 0)
  	!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testStreamContents (in category 'tests - streaming') -----
- ----- Method: OrderedCollectionTest>>testStreamContents (in category 'testStreaming') -----
  testStreamContents
  	| oc |
  	self shouldnt: [oc := OrderedCollection streamContents: [:stream | 1 to: 3 do: [:i | stream nextPut: i]]]
  		raise: Error
  		description: 'it should be possible to stream over an OrderedCollection'.
  	self assert: oc class = OrderedCollection.
  	self assert: oc = (1 to: 3) asOrderedCollection.!

Item was changed:
+ ----- Method: OrderedCollectionTest>>testWithCollect (in category 'tests - enumerating') -----
- ----- Method: OrderedCollectionTest>>testWithCollect (in category 'testsEnumerating') -----
  testWithCollect
  	"Allows one to collect some element of two collections into another collection with element corresponding to the condition in the blocks"
  	"self run: #testWithCollect"
  	
  	| c1 c2 res |
  	c1 := #(-1 2 -3 4 -5 6 -7 8) asOrderedCollection.
  	c2 := #(-9 10 -11 12 -13 14 -15 16) asOrderedCollection.
  	res := c1 with: c2 collect: [:each1 :each2 | each1 < each2
  		ifTrue: [each1]
  		ifFalse: [each2]].
  	self assert: (res = #(-9 2 -11 4 -13 6 -15 8) asOrderedCollection).
  	!

Item was changed:
+ ----- Method: QFormatMimeConverterTest>>testDecode (in category 'tests') -----
- ----- Method: QFormatMimeConverterTest>>testDecode (in category 'running') -----
  testDecode
  
  	| encodedString decodedString |
  	encodedString := '=E0'.
  	decodedString := QEncodingMimeConverter mimeDecode: encodedString as: WideString.
  	self assert: 'à' equals: decodedString.
  	
  	encodedString := 'H=FC_Th=F6r=E4!!'.
  	decodedString := QEncodingMimeConverter mimeDecode: encodedString as: WideString.
  	self assert: 'Hü Thörä!!' equals: decodedString.
  	
  	encodedString := 'H=FC=20Th=F6r=E4!!'.
  	decodedString := QEncodingMimeConverter mimeDecode: encodedString as: WideString.
  	self assert: 'Hü Thörä!!' equals: decodedString.!

Item was changed:
+ ----- Method: QFormatMimeConverterTest>>testEncodeSimpleString (in category 'tests') -----
- ----- Method: QFormatMimeConverterTest>>testEncodeSimpleString (in category 'running') -----
  testEncodeSimpleString
  
  	| encodedString |
  	encodedString := QEncodingMimeConverter mimeEncode: message.
  	self assert: '=?UTF-8?Q?H=C3=BC?= =?UTF-8?Q?Th=C3=B6r=C3=A4!!?=' equals: encodedString.
  	!

Item was changed:
+ ----- Method: QFormatMimeConverterTest>>testEncodeSimpleStringWithQuestionMark (in category 'tests') -----
- ----- Method: QFormatMimeConverterTest>>testEncodeSimpleStringWithQuestionMark (in category 'running') -----
  testEncodeSimpleStringWithQuestionMark
  
  	| encodedString |
  	encodedString := QEncodingMimeConverter mimeEncode: 'Is üt?'.
  	self assert: 'Is =?UTF-8?Q?=C3=BCt=3F?=' equals: encodedString.
  	!

Item was changed:
+ ----- Method: QFormatMimeConverterTest>>testRoundtrip (in category 'tests') -----
- ----- Method: QFormatMimeConverterTest>>testRoundtrip (in category 'running') -----
  testRoundtrip
  
  	| result start |
  	start := 'Is üt?'.
  	result := ((QEncodingMimeConverter mimeEncode: start) as: String) decodeMimeHeader.
  	self assert: start equals: result.
  	!

Item was changed:
+ ----- Method: RWBinaryOrTextStreamTest>>expectedFailures (in category 'failures') -----
- ----- Method: RWBinaryOrTextStreamTest>>expectedFailures (in category 'testing') -----
  expectedFailures
  
  	^#(
  		testExisting "This is more like a request for new behavior than a bug."
  	)!

Item was changed:
+ ----- Method: SetTest>>testAdd (in category 'tests - original tests') -----
- ----- Method: SetTest>>testAdd (in category 'Sunit original tests') -----
  testAdd
  	empty add: 5.
  	self assert: (empty includes: 5).!

Item was changed:
+ ----- Method: SetTest>>testGrow (in category 'tests - original tests') -----
- ----- Method: SetTest>>testGrow (in category 'Sunit original tests') -----
  testGrow
  	empty addAll: (1 to: 100).
  	self assert: (empty size = 100).
  			!

Item was changed:
+ ----- Method: SetTest>>testIfAbsentAdd (in category 'tests - original tests') -----
- ----- Method: SetTest>>testIfAbsentAdd (in category 'Sunit original tests') -----
  testIfAbsentAdd
  	| it |
  	it := 5.
  	self deny: (empty includes: it).
  	self assert: (empty ifAbsentAdd: it).
  	self assert: (empty includes: it).
  	self deny: (empty ifAbsentAdd: it).
  	self assert: (empty includes: it)!

Item was changed:
+ ----- Method: SetTest>>testIllegal (in category 'tests - original tests') -----
- ----- Method: SetTest>>testIllegal (in category 'Sunit original tests') -----
  testIllegal
  	self 
  		should: [empty at: 5] raise: TestResult error.
  	self 
  		should: [empty at: 5 put: #abc] raise: TestResult error.
  			!

Item was changed:
+ ----- Method: SetTest>>testIncludes (in category 'tests - original tests') -----
- ----- Method: SetTest>>testIncludes (in category 'Sunit original tests') -----
  testIncludes
  	self assert: (full includes: 5).
  	self assert: (full includes: #abc).
  	self deny: (full includes: 3).
  			!

Item was changed:
+ ----- Method: SetTest>>testOccurrences (in category 'tests - original tests') -----
- ----- Method: SetTest>>testOccurrences (in category 'Sunit original tests') -----
  testOccurrences
  	self assert: ((empty occurrencesOf: 0) = 0).
  	self assert: ((full occurrencesOf: 5) = 1).
  	full add: 5.
  	self assert: ((full occurrencesOf: 5) = 1).!

Item was changed:
+ ----- Method: SetTest>>testRemove (in category 'tests - original tests') -----
- ----- Method: SetTest>>testRemove (in category 'Sunit original tests') -----
  testRemove
  	full remove: 5.
  	self assert: (full includes: #abc).
  	self deny: (full includes: 5).!

Item was changed:
+ ----- Method: SharedQueue2Test>>testBasics (in category 'tests') -----
- ----- Method: SharedQueue2Test>>testBasics (in category 'testing') -----
  testBasics
  	| q |
  	q := SharedQueue2 new.
  
  	self should: [ q nextOrNil = nil ].
  
  	q nextPut: 5.
  	self should: [ q nextOrNil = 5 ].
  	self should: [ q nextOrNil = nil ].
  
  !

Item was changed:
+ ----- Method: SharedQueue2Test>>testContention1 (in category 'tests') -----
- ----- Method: SharedQueue2Test>>testContention1 (in category 'testing') -----
  testContention1
  	"here is a test case that breaks the standard SharedQueue from Squeak 3.8"
  
  	| q r1 r2 |
  	q := SharedQueue2 new.
  	q nextPut: 5.
  	q nextPut: 10.
  
  	self should: [ q nextOrNil = 5 ].
  
  	[ r1 := q next ] fork.
  	[ r2 := q next ] fork.
  	Processor  yield.   "let the above two threads block"
  	
  	q nextPut: 10.
  	Processor yield.
  
  	self should: [ r1 = 10 ].
  	self should: [ r2 = 10 ].
  	self should: [ q nextOrNil = nil ].
  !

Item was changed:
+ ----- Method: SharedQueue2Test>>testNextOrNilSuchThat (in category 'tests') -----
- ----- Method: SharedQueue2Test>>testNextOrNilSuchThat (in category 'testing') -----
  testNextOrNilSuchThat
  	| q item |
  	q := SharedQueue2 new.
  	q nextPut: 5.
  	q nextPut: 6.
  
  	item := q nextOrNilSuchThat: [ :x | x even ].
  	self should: [ item = 6 ].
  
  	self should: [ q nextOrNil = 5 ].
  	self should: [ q nextOrNil = nil ].
  !

Item was changed:
+ ----- Method: StackTest>>testEmptyError (in category 'tests') -----
- ----- Method: StackTest>>testEmptyError (in category 'test') -----
  testEmptyError
  
  	| aStack |
  	aStack := Stack new.
  	self should: [ aStack top ] raise: Error.
  	self should: [ aStack pop] raise: Error.
  	
  	aStack push: 'element'.
  	
  	self assert: 'element' equals: aStack top.
  	self assert: 'element' equals:  aStack pop.
  	
  	
  	"The stack is empty again due to previous pop"
  	self should: [ aStack top ] raise: Error.
  	self should: [ aStack pop] raise: Error.!

Item was changed:
+ ----- Method: StackTest>>testPop (in category 'tests') -----
- ----- Method: StackTest>>testPop (in category 'test') -----
  testPop
  
  	| aStack res elem |
  	elem := 'anElement'.	
  	aStack := Stack new.
  	self assert: aStack isEmpty.
  	
  	aStack push: 'a'.
  	aStack push: elem.
  	res := aStack pop.	
  	self assert: res = elem.
  	self assert: res == elem.
  	
  	self assert: aStack size = 1.
  	aStack pop.
  	self assert: aStack isEmpty.
  
  !

Item was changed:
+ ----- Method: StackTest>>testPush (in category 'tests') -----
- ----- Method: StackTest>>testPush (in category 'test') -----
  testPush
  	
  	| aStack |
  	aStack := Stack new.
  	aStack push: 'a'.
  	self assert: aStack size = 1.	
  	aStack push: 'b'.
  	self assert: aStack size = 2.
  	!

Item was changed:
+ ----- Method: StackTest>>testSize (in category 'tests') -----
- ----- Method: StackTest>>testSize (in category 'test') -----
  testSize
  	
  	| aStack |
  	aStack := Stack new.
  	self assert: aStack size = 0.
  	aStack push: 'a'.
  	self assert: aStack size = 1.
  	aStack push: 'b'.
  	self assert: aStack size = 2.
  	aStack pop.
  	self assert: aStack size = 1.
  	aStack pop.
  	self assert: aStack size = 0.
  
   
  	
  
  
  !

Item was changed:
+ ----- Method: StackTest>>testTop (in category 'tests') -----
- ----- Method: StackTest>>testTop (in category 'test') -----
  testTop
  
  	| aStack |
  	aStack := Stack new.
  	self assert: aStack isEmpty.
  	aStack push: 'a'.
  	aStack push: 'b'.
  	self assert: aStack top = 'b'.
  	self assert: aStack top = 'b'.
  	self assert: aStack size = 2.!

Item was changed:
+ ----- Method: StringTest>>setUp (in category 'running') -----
- ----- Method: StringTest>>setUp (in category 'initialize-release') -----
  setUp
  	string := 'Hi, I am a String'!

Item was changed:
+ ----- Method: TextAlignmentTest>>setUp (in category 'running') -----
- ----- Method: TextAlignmentTest>>setUp (in category 'initialize-release') -----
  setUp
  	super setUp.
  	prototypes add: TextAlignment centered;
  		 add: TextAlignment justified;
  		 add: TextAlignment leftFlush;
  		 add: TextAlignment rightFlush !

Item was changed:
+ ----- Method: TextAttributesScanningTest>>expectedFailures (in category 'failures') -----
- ----- Method: TextAttributesScanningTest>>expectedFailures (in category 'running') -----
  expectedFailures
  	"Tests for text attributes that are apparently unused, and that may be candidates
  	for removal from the image"
  	^#(
  		testTextAnchor
  		testTextIndent
  		testTextMessageLink
  		testTextPlusJumpStart
  		testTextPlusJumpEnd
  		
  		"Actually failing tests which document bugs to be fixed (pre)"
  		testTextFontReferenceForBoldFont
  		testTextFontReferenceTTCForBoldFont
  		)!

Item was changed:
+ ----- Method: TextEmphasisTest>>setUp (in category 'running') -----
- ----- Method: TextEmphasisTest>>setUp (in category 'initialize-release') -----
  setUp
  	super setUp.
  	prototypes add: TextEmphasis bold;
  		 add: TextEmphasis italic;
  		 add: TextEmphasis narrow;
  		 add: TextEmphasis normal;
  		 add: TextEmphasis struckOut;
  		 add: TextEmphasis underlined !

Item was changed:
+ ----- Method: TextFontChangeTest>>setUp (in category 'running') -----
- ----- Method: TextFontChangeTest>>setUp (in category 'initialize-release') -----
  setUp
  	"create the prototypes for testing"
  	super setUp.
  	prototypes add: TextFontChange defaultFontChange.
  	prototypes add: TextFontChange font1.
  	prototypes add: TextFontChange font2.
  	prototypes add: TextFontChange font3.
  	prototypes add: TextFontChange font4.
  	prototypes
  		add: (TextFontChange fontNumber: 6) !

Item was changed:
+ ----- Method: WeakSetTest>>testAddIncludesSizeReclaim (in category 'tests') -----
- ----- Method: WeakSetTest>>testAddIncludesSizeReclaim (in category 'testing') -----
  testAddIncludesSizeReclaim
  	| ws o2 o3 |
  	o2 := 1/2.
  	o3 := '123' copy.
  	ws := WeakSet new.
  	ws add: o2.
  	ws add: o3.
  	self assert: ws size = 2.
  	self assert: (ws includes: o2).
  	self assert: (ws includes: o3).
  	
  	"inclusion test does use equality, not identity"
  	self assert: (ws includes: o3 copy) description: 'WeakSet are not WeakIdentitySet'.
  	
  	"only one copy is added"
  	ws add: o3 copy.
  	self assert: ws size = 2.
  	
  	"reclame objects so that slots of ws are nilled out"
  	o2 := o3 := nil.
  	Smalltalk garbageCollect.
  	self deny: (ws includes: 1/2).
  	self deny: (ws includes: '123' copy).
  	
  	"fast #size is not updated automatically by dead object reclamation
  	But there is a slowSize trying to tell the truth"
  	self assert: ws slowSize = 0.!

Item was changed:
+ ----- Method: WeakSetTest>>testCollisions (in category 'tests') -----
- ----- Method: WeakSetTest>>testCollisions (in category 'testing') -----
  testCollisions
  
  	| ws o1 o2 o5 on remember forget |
  
  	"create a weak set"
  	ws := WeakSet new: 15.
  	
  	"select some fractions wanting same place in ws array"
  	o1 := (2 to: 200) select: [:i | (ws scanFor: 1 / i) = 1].
  	o2 := (2 to: 200) select: [:i | (ws scanFor: 1 / i) = 2].
  	o5 := (2 to: 200) select: [:i | (ws scanFor: 1 / i) = 5].
  	on := (2 to: 200) select: [:i | (ws scanFor: 1 / i) = (ws array size - 1)].
  	
  	"Add some fractions to the weak set, and remember a pointer for a few of them"
  	remember := OrderedCollection new.
  	forget := OrderedCollection new.
  	ws add: (remember add: 1 / o1 first).
  	ws add: (forget add: 1 / on second).
  	ws add: (forget add: 1 / o1 second).
  	ws add: (forget add: 1 / o5 second).
  	ws add: (forget add: 1 / o2 second).
  	ws add: (forget add: 1 / o1 third).
  	ws add: (remember add: 1 / o2 first).
  	ws add: (forget add: 1 / o5 third).
  	ws add: (forget add: 1 / on third).
  	ws add: (remember add: 1 / o2 fourth).
  	ws add: (remember add: 1 / on first).
  	ws add: (remember add: 1 / o5 first).
  	
  	"forget and reclaim all entries but those in remember"
  	forget := nil.
  	Smalltalk garbageCollect.
  	
  	remember do: [:m | self assert: (ws includes: m)].
  	ws add: 1/on second.
  	remember do: [:m | self assert: (ws includes: m)].
  	
  	ws add: (remember add: 1 / o1 fourth).
  	ws add: (remember add: 1 / on fourth).
  	remember remove: (ws remove: (1 / o5 first)).
  	remember remove: (ws remove: (1 / on first)).
  	remember remove: (ws remove: (1 / o2 first)).
  	remember remove: (ws remove: (1 / o1 first)).
  	remember do: [:m | self assert: (ws includes: m)].
  	ws add: 1/on second.
  	ws add: 1/o5 second.
  	remember do: [:m | self assert: (ws includes: m)].
  	!

Item was changed:
+ ----- Method: WeakSetTest>>testDoDontIterateOnReclaimedObjects (in category 'tests') -----
- ----- Method: WeakSetTest>>testDoDontIterateOnReclaimedObjects (in category 'testing') -----
  testDoDontIterateOnReclaimedObjects
  
  	| ws o1 o2 size |
  	ws := WeakSet new.
  	2 to: 20 do: [:i | ws add: 1 / i].
  	
  	o1 := 3.0.
  	o2 := 4.0.
  	ws add: o1; add: o2.
  	
  	"Reclaim memory"
  	Smalltalk garbageCollect.
  	
  	size := 0.
  	ws do: [:each |
  		size := size + 1.
  		self deny: each isNil].
  	
  	self assert: size = 2!

Item was changed:
+ ----- Method: WeakSetTest>>testGrowWhenNecessary (in category 'tests') -----
- ----- Method: WeakSetTest>>testGrowWhenNecessary (in category 'testing') -----
  testGrowWhenNecessary
  	| ws objs initialSize |
  	objs := (2 to: 20) collect: [:i | 1 / i].
  	ws := WeakSet new: 5.
  	initialSize := ws array size.
  	1 to: objs size do: [:k | ws add: (objs at: k)].
  	self assert: ws array size > initialSize
  		description: 'The WeakSet grown because not enough room were preallocated'.!

Item was changed:
+ ----- Method: WeakSetTest>>testIncludesNil (in category 'tests') -----
- ----- Method: WeakSetTest>>testIncludesNil (in category 'testing') -----
  testIncludesNil
  
  	| ws |
  	ws := WeakSet new.
  	self deny: (ws includes: nil).
  	
  	"After reclamation, should not includes nil: nil counts for nothing"
  	ws add: 1/2.
  	ws add: 1/3.
  	Smalltalk garbageCollect.
  	self deny: (ws includes: nil).!

Item was changed:
+ ----- Method: WideCharacterSetTest>>testAddingToCharacterSet (in category 'tests') -----
- ----- Method: WideCharacterSetTest>>testAddingToCharacterSet (in category 'testing') -----
  testAddingToCharacterSet
  
  	| cs wcs wc |
  	cs := CharacterSet newFrom: 'aeiouy'.
  	wcs := cs copy.
  	wc := 4452 asCharacter.
  	
  	self shouldnt: [wcs add: wc] raise: Error description: 'adding a WideCharacter to an ordinary CharacterSet should turn it into a WideCharacterSet'.
  
  	self assert: (wcs size = (cs size + 1)) description: 'We just added a Character, size should be increased by one'.
  	self deny: (wcs = cs) description: 'We just added a Character, sets should not be equal'.
  	self deny: (cs = wcs) description: 'We just added a Character, sets should not be equal'.
  	self assert: (cs allSatisfy: [:char | wcs includes: char]) description: 'Each character of the original CharacterSet should be included in the WideCharacterSet'.
  	self assert: (wcs hasWideCharacters) description: 'We just added a WideCharacter, so this WideCharacterSet definitely has one'.
  	self assert: (wcs includes: wc) description: 'We just added this WideCharacter, so this WideCharacterSet should include it'.
  	
  	wcs add: wc.
  	self assert: (wcs size = (cs size + 1)) description: 'We just added a Character already included in the set, size should be unchanged'.
  	
  	wcs remove: wc.
  	self assert: (wcs size = cs size) description: 'We added then removed a Character, now size should be equal to original'.
  	self deny: (wcs hasWideCharacters) description: 'We just removed the only WideCharacter, so this WideCharacterSet definitely has no WideCharacter'.
  	
  	self assert: (wcs = cs) description: 'A WideCharacterSet can be equal to an Ordinary CharacterSet'.
  	self assert: (cs = wcs) description: 'An ordinary CharacterSet can be equal to a WideCharacterSet'.
  	self assert: (cs hash = wcs hash) description: 'If some objects are equal, then they should have same hash code'.
  	
  	!

Item was changed:
+ ----- Method: WideCharacterSetTest>>testCreation (in category 'tests') -----
- ----- Method: WideCharacterSetTest>>testCreation (in category 'testing') -----
  testCreation
  	"By now, only creation method is newFrom:"
  
  	| cs1 wcs1 cs2 wcs2 byteString wideString |
  	byteString := 'aeiouy'.
  	wideString := 'aeiouy' copyWith: 340 asCharacter.
  
  	cs1 := CharacterSet newFrom: byteString.
  	wcs1 := WideCharacterSet newFrom: byteString.
  	self assert: (wcs1 = cs1).
  	self assert: (wcs1 size = byteString "asSet" size).
  	
  	cs2 := CharacterSet newFrom: wideString.
  	wcs2 := WideCharacterSet newFrom: wideString.
  	self assert: (wcs2 = cs2).
  	self assert: (wcs2 size = wideString "asSet" size).
  	
  	self assert: ((byteString indexOfAnyOf: wcs1) = 1) description: 'This should used optimized byteArrayMap method'.
  	self assert: ((byteString indexOfAnyOf: wcs2) = 1) description: 'This should used optimized byteArrayMap method'.
  	
  	self assert: (('bcd' indexOfAnyOf: wcs1) = 0) description: 'This should used optimized byteArrayMap method'.
  	self assert: (('bcd' indexOfAnyOf: wcs2) = 0) description: 'This should used optimized byteArrayMap method'.!

Item was changed:
+ ----- Method: WordArrayTest>>testAtOutOfBounds (in category 'tests') -----
- ----- Method: WordArrayTest>>testAtOutOfBounds (in category 'testing') -----
  testAtOutOfBounds
  	"self debug: #testAtOutOfBounds"
  	"Do the test more than once to make sure the jitted code is tested."
  	1 to: 5 do:
  		[:iteration|
  		 self 
  			should: [(WordArray with: 0) at: 2]
  			raise: Error.
  		 self 
  			should: [(WordArray with: 0) at: -1]
  			raise: Error]!

Item was changed:
+ ----- Method: WordArrayTest>>testAtPutOutOfBounds (in category 'tests') -----
- ----- Method: WordArrayTest>>testAtPutOutOfBounds (in category 'testing') -----
  testAtPutOutOfBounds
  	"self debug: #testAtPutOutOfBounds"
  	"Do the test more than once to make sure the jitted code is tested."
  	1 to: 5 do:
  		[:iteration|
  		 self 
  			should: [(WordArray with: 0) at: 2 put: 1]
  			raise: Error.
  		 self 
  			should: [(WordArray with: 0) at: -1 put: 1]
  			raise: Error]!

Item was changed:
+ ----- Method: WordArrayTest>>testByteSize (in category 'tests') -----
- ----- Method: WordArrayTest>>testByteSize (in category 'testing') -----
  testByteSize
  	self assert: (WordArray new: 1) byteSize = 4 "4 bytes are 32 bits"!

Item was changed:
+ ----- Method: WordArrayTest>>testCannotPutNegativeValue (in category 'tests') -----
- ----- Method: WordArrayTest>>testCannotPutNegativeValue (in category 'testing') -----
  testCannotPutNegativeValue
  	self should: [WordArray with: -1] raise: Error!

Item was changed:
+ ----- Method: WordArrayTest>>testCannotPutTooLargeValue (in category 'tests') -----
- ----- Method: WordArrayTest>>testCannotPutTooLargeValue (in category 'testing') -----
  testCannotPutTooLargeValue
  	| maxValue |
  	maxValue := 1 << 32 - 1.
  	self assert: (WordArray with: maxValue) first = maxValue.
  	self should: [WordArray with: maxValue + 1] raise: Error!

Item was changed:
+ ----- Method: WordArrayTest>>testElementSize (in category 'tests') -----
- ----- Method: WordArrayTest>>testElementSize (in category 'testing') -----
  testElementSize
  	self assert: WordArray new bytesPerElement = 4 "4 bytes are 32 bits"!

Item was changed:
+ ----- Method: WordArrayTest>>testSomeValues (in category 'tests') -----
- ----- Method: WordArrayTest>>testSomeValues (in category 'testing') -----
  testSomeValues
  	| wArray int next |
  	next := [:x | x - 3 * x sqrtFloor + 5].
  	int := 0.
  	wArray := WordArray new: 1.
  	[int highBit < 32]
  		whileTrue:
  			[wArray at: 1 put: int.
  			self assert: (wArray at: 1) = int.
  			int := next value: int].
  	self should: [wArray at: 1 put: int] raise: Error!



More information about the Squeak-dev mailing list