[Pkg] The Trunk: CollectionsTests-topa.271.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Dec 6 13:32:53 UTC 2016


Tobias Pape uploaded a new version of CollectionsTests to project The Trunk:
http://source.squeak.org/trunk/CollectionsTests-topa.271.mcz

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

Name: CollectionsTests-topa.271
Author: topa
Time: 6 December 2016, 2:32:47.436831 pm
UUID: aeb6cba0-f935-4514-b77b-5dfd977d737e
Ancestors: CollectionsTests-nice.270

Adopt improved and vastly expanded Linked List tests from our relatives.

=============== Diff against CollectionsTests-nice.270 ===============

Item was changed:
  ClassTestCase subclass: #LinkedListTest
+ 	instanceVariableNames: 'nextLink n list link1 link2 link3 link4 nonEmpty otherList link collectionWithNil collectionWithoutNil nonEmpty1Element collectionWithoutEqualElements elementNotIn elementIn sameAtendAndBegining collection5Elements collectResult'
- 	instanceVariableNames: 'nextLink n list link1 link2 link3 link4'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'CollectionsTests-Sequenceable'!
  
  !LinkedListTest commentStamp: 'mk 8/3/2005 11:55' prior: 0!
  A set of test cases which thoroughly test functionality of the LinkedList class.!

Item was added:
+ ----- Method: LinkedListTest>>accessCollection (in category 'requirements') -----
+ accessCollection
+ 	^collectionWithoutEqualElements !

Item was added:
+ ----- Method: LinkedListTest>>anotherElementNotIn (in category 'requirements') -----
+ anotherElementNotIn
+ " return an element included  in 'collection' "
+ 	^ elementNotIn !

Item was added:
+ ----- Method: LinkedListTest>>anotherElementOrAssociationIn (in category 'requirements') -----
+ anotherElementOrAssociationIn
+ 	" return an element (or an association for Dictionary ) present  in 'collection' "
+ 	^ self collection anyOne!

Item was added:
+ ----- Method: LinkedListTest>>anotherElementOrAssociationNotIn (in category 'requirements') -----
+ anotherElementOrAssociationNotIn
+ 	" return an element (or an association for Dictionary )not present  in 'collection' "
+ 	^ elementNotIn !

Item was added:
+ ----- Method: LinkedListTest>>assertNoDuplicates:whenConvertedTo: (in category 'tests - converting') -----
+ assertNoDuplicates: aCollection whenConvertedTo: aClass 
+ 	| result |
+ 	result := self collectionWithEqualElements asIdentitySet.
+ 	self assert: (result class includesBehavior: IdentitySet).
+ 	self collectionWithEqualElements do: [ :initial | self assert: (result occurrencesOf: initial) = 1 ]!

Item was added:
+ ----- Method: LinkedListTest>>assertNonDuplicatedContents:whenConvertedTo: (in category 'tests - converting') -----
+ assertNonDuplicatedContents: aCollection whenConvertedTo: aClass 
+ 	| result |
+ 	result := aCollection perform: ('as' , aClass name) asSymbol.
+ 	self assert: (result class includesBehavior: aClass).
+ 	result do: 
+ 		[ :each | 
+ 		self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ].
+ 	^ result!

Item was added:
+ ----- Method: LinkedListTest>>assertSameContents:whenConvertedTo: (in category 'tests - converting') -----
+ assertSameContents: aCollection whenConvertedTo: aClass 
+ 	| result |
+ 	result := self assertNonDuplicatedContents: aCollection whenConvertedTo: aClass.
+ 	self assert: result size = aCollection size!

Item was added:
+ ----- Method: LinkedListTest>>collection (in category 'requirements') -----
+ collection
+ 	^ self nonEmpty!

Item was added:
+ ----- Method: LinkedListTest>>collectionClass (in category 'requirements') -----
+ collectionClass
+ " return the class to be used to create instances of the class tested"
+ 	^ LinkedList!

Item was added:
+ ----- Method: LinkedListTest>>collectionMoreThan1NoDuplicates (in category 'requirements') -----
+ collectionMoreThan1NoDuplicates
+ 	" return a collection of size 5 without equal elements"
+ 	^ collectionWithoutEqualElements!

Item was added:
+ ----- Method: LinkedListTest>>collectionNotIncluded (in category 'requirements') -----
+ collectionNotIncluded
+ " return a collection for wich each element is not included in 'nonEmpty' "
+ 	^ collectionWithoutNil !

Item was added:
+ ----- Method: LinkedListTest>>collectionWith1TimeSubcollection (in category 'requirements') -----
+ collectionWith1TimeSubcollection
+ " return a collection including 'oldSubCollection'  only one time "
+ 	^ self oldSubCollection !

Item was added:
+ ----- Method: LinkedListTest>>collectionWithCopyNonIdentical (in category 'requirements') -----
+ collectionWithCopyNonIdentical
+ 	" return a collection that include elements for which 'copy' return a different object (this is not the case of SmallInteger)"
+ 	^ collectionWithoutEqualElements!

Item was added:
+ ----- Method: LinkedListTest>>collectionWithElement (in category 'requirements') -----
+ collectionWithElement
+ 	"Returns a collection that already includes what is returned by #element."
+ 	^ self collection!

Item was added:
+ ----- Method: LinkedListTest>>collectionWithElementsToRemove (in category 'requirements') -----
+ collectionWithElementsToRemove
+ " return a collection of elements included in 'nonEmpty'  "
+ 	^ self nonEmpty !

Item was added:
+ ----- Method: LinkedListTest>>collectionWithSortableElements (in category 'requirements') -----
+ collectionWithSortableElements
+ 	" return a collection only including elements that can be sorted (understanding '<' )"
+ 	^ collection5Elements !

Item was added:
+ ----- Method: LinkedListTest>>collectionWithoutEqualElements (in category 'requirements') -----
+ collectionWithoutEqualElements
+ 
+ " return a collection not including equal elements "
+ 	^collectionWithoutEqualElements !

Item was added:
+ ----- Method: LinkedListTest>>collectionWithoutNilElements (in category 'requirements') -----
+ collectionWithoutNilElements
+ " return a collection that doesn't includes a nil element "
+ 	^collectionWithoutNil !

Item was added:
+ ----- Method: LinkedListTest>>containsAll:of:andOf: (in category 'tests - set arithmetic') -----
+ containsAll: union of: one andOf: another
+ 			
+ 	self assert: (one allSatisfy: [:each | union includes: each]).
+ 	self assert: (another allSatisfy: [:each | union includes: each])!

Item was added:
+ ----- Method: LinkedListTest>>element (in category 'requirements') -----
+ element
+ 	^ link ifNil: [link := ValueLink value: 42. "so that we can recognize this link"]!

Item was added:
+ ----- Method: LinkedListTest>>elementInForElementAccessing (in category 'requirements') -----
+ elementInForElementAccessing
+ " return an element inculded in 'accessCollection '"
+ 	^ elementIn !

Item was added:
+ ----- Method: LinkedListTest>>elementInForIndexAccessing (in category 'requirements') -----
+ elementInForIndexAccessing
+ " return an element included in 'accessCollection' "
+ 	^ elementIn !

Item was added:
+ ----- Method: LinkedListTest>>elementNotIn (in category 'requirements') -----
+ elementNotIn
+ 	^ Link new!

Item was added:
+ ----- Method: LinkedListTest>>elementNotInForElementAccessing (in category 'requirements') -----
+ elementNotInForElementAccessing
+ " return an element not included in 'accessCollection' "
+ 	^ elementNotIn !

Item was added:
+ ----- Method: LinkedListTest>>elementNotInForIndexAccessing (in category 'requirements') -----
+ elementNotInForIndexAccessing
+ " return an element not included in 'accessCollection' "
+ 	^ elementNotIn !

Item was added:
+ ----- Method: LinkedListTest>>elementNotInForOccurrences (in category 'requirements') -----
+ elementNotInForOccurrences
+ " return an element notIncluded in #collectionWithoutEqualElements"
+ 	^ elementNotIn !

Item was added:
+ ----- Method: LinkedListTest>>elementToAdd (in category 'requirements') -----
+ elementToAdd
+ " return an element of type 'nonEmpy' elements'type'"
+ 	^ ValueLink value: 77!

Item was added:
+ ----- Method: LinkedListTest>>empty (in category 'accessing') -----
+ empty
+ 	^ list!

Item was added:
+ ----- Method: LinkedListTest>>firstIndexesOf:in: (in category 'tests - copying with replacement') -----
+ firstIndexesOf: aSubCollection in: collection
+ " return an OrderedCollection with the first indexes of the occurrences of subCollection in  collection "
+ 	| tmp result currentIndex |
+ 	tmp:= collection.
+ 	result:= OrderedCollection new.
+ 	currentIndex := 1.
+ 	
+ 	[tmp isEmpty ]whileFalse:
+ 		[
+ 		(tmp beginsWith: aSubCollection)
+ 			ifTrue: [ 	
+ 				result add: currentIndex.
+ 				1 to: aSubCollection size do: 
+ 					[:i | 
+ 					tmp := tmp copyWithoutFirst.
+ 					currentIndex := currentIndex + 1]
+ 				]
+ 			ifFalse: [
+ 				tmp := tmp copyWithoutFirst.
+ 				currentIndex := currentIndex +1.
+ 				]
+ 		 ].
+ 	
+ 	^ result.
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>howMany:in: (in category 'tests - fixture') -----
+ howMany: aSubCollection in: collection
+ " return an integer representing how many time 'subCollection'  appears in 'collection'  "
+ 	| tmp nTime |
+ 	tmp := collection.
+ 	nTime:= 0.
+ 	
+ 	[tmp isEmpty ]whileFalse:
+ 		[
+ 		(tmp beginsWith: aSubCollection)
+ 			ifTrue: [ 	
+ 				nTime := nTime + 1.
+ 				1 to: aSubCollection size do: [:i | tmp := tmp copyWithoutFirst.]
+ 				]
+ 			ifFalse: [tmp := tmp copyWithoutFirst.]
+ 		 ].
+ 	
+ 	^ nTime.
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>indexInForCollectionWithoutDuplicates (in category 'requirements') -----
+ indexInForCollectionWithoutDuplicates
+ " return an index between 'collectionWithoutEqualsElements'  bounds"
+ 	^ 2!

Item was added:
+ ----- Method: LinkedListTest>>indexInNonEmpty (in category 'requirements') -----
+ indexInNonEmpty
+ " return an index between bounds of 'nonEmpty' "
+ 
+ 	^ self nonEmpty size!

Item was added:
+ ----- Method: LinkedListTest>>moreThan3Elements (in category 'requirements') -----
+ moreThan3Elements
+ 	" return a collection including atLeast 3 elements"
+ 	^ collectionWithoutEqualElements !

Item was added:
+ ----- Method: LinkedListTest>>moreThan4Elements (in category 'requirements') -----
+ moreThan4Elements
+ 
+ " return a collection including at leat 4 elements"
+ 	^ collectionWithoutEqualElements !

Item was added:
+ ----- Method: LinkedListTest>>nonEmpty (in category 'requirements') -----
+ nonEmpty
+ 	^ nonEmpty ifNil: [nonEmpty := LinkedList with: 5 with: 4 with: 3 with: 2 with: 1 with: self element]!

Item was added:
+ ----- Method: LinkedListTest>>nonEmpty1Element (in category 'requirements') -----
+ nonEmpty1Element
+ " return a collection of size 1 including one element"
+ 	^ nonEmpty1Element !

Item was added:
+ ----- Method: LinkedListTest>>nonEmptyMoreThan1Element (in category 'requirements') -----
+ nonEmptyMoreThan1Element
+ " return a collection that don't includes equl elements'" 
+ 	^collectionWithoutNil !

Item was added:
+ ----- Method: LinkedListTest>>nonEmptyWithoutEqualElements (in category 'requirements') -----
+ nonEmptyWithoutEqualElements
+ " return a collection without equal elements "
+ 	^ collectionWithoutEqualElements !

Item was added:
+ ----- Method: LinkedListTest>>numberOfSimilarElementsInIntersection (in category 'tests - set arithmetic') -----
+ numberOfSimilarElementsInIntersection
+ 	^ self collection occurrencesOf: self anotherElementOrAssociationIn!

Item was added:
+ ----- Method: LinkedListTest>>oldSubCollection (in category 'requirements') -----
+ oldSubCollection
+ " return a subCollection included in collectionWith1TimeSubcollection .
+ ex :   subCollection := #( 2 3 4) and collectionWith1TimeSubcollection := #(1 2 3 4 5)"
+ 	^ self nonEmpty !

Item was added:
+ ----- Method: LinkedListTest>>otherCollection (in category 'requirements') -----
+ otherCollection
+ 	^ otherList ifNil: [otherList := LinkedList with: Link new with: Link new]!

Item was added:
+ ----- Method: LinkedListTest>>replacementCollection (in category 'requirements') -----
+ replacementCollection
+ " return a collection that will be used to replace 'oldSubcollection' in ' collectionWith1TimeSubcollection'  " 
+ 	^ collectionWithoutNil !

Item was added:
+ ----- Method: LinkedListTest>>result (in category 'requirements') -----
+ result
+ 	"Returns a collection of the classes of elements in #collection"
+ 	 ^ collectResult!

Item was changed:
  ----- Method: LinkedListTest>>setUp (in category 'running') -----
  setUp
+ 	
  	super setUp.
  	list := LinkedList new.
+ 	link1 := 133.
+ 	link2 := 'test'.
+ 	link3 := $h.
+ 	link4 := Set new.
+ 	elementNotIn := Link new.
+ 	collectionWithoutNil := LinkedList new add: link1; add: link2 ; add: link3; yourself.
+ 	elementIn := 'thisElementIsIncluded'.
+ 	collectionWithoutEqualElements := LinkedList new add: elementIn ; add: 'pewpew' ; add: 'normal links'; add: 'are no fun!!' ;add: $x ;yourself.
+ 	collection5Elements := collectionWithoutEqualElements .
+ 	
+ 	"sameAtendAndBegining := LinkedList new add: Link new; add: Link new ; add: Link new; yourself."
+ 	link := ValueLink value: 42.
+ 	nonEmpty1Element :=  LinkedList new add: Link new; yourself.
+ 	 "so that we can recognize this link"
+ 	"nonEmpty := LinkedList with: link with: Link new."
+ 	"otherList := LinkedList with: Link new with: Link new."
+ !
- 	link1 := Link new.
- 	link2 := Link new.
- 	link3 := Link new.
- 	link4 := Link new!

Item was added:
+ ----- Method: LinkedListTest>>speciesClass (in category 'requirements') -----
+ speciesClass
+ 	
+ 	^LinkedList!

Item was added:
+ ----- Method: LinkedListTest>>subCollectionNotIn (in category 'requirements') -----
+ subCollectionNotIn
+ " return a collection for which at least one element is not included in 'accessCollection' "
+ 	^ collectionWithoutNil !

Item was changed:
  ----- Method: LinkedListTest>>tearDown (in category 'running') -----
  tearDown
  	list := nil.
  	link1 := nil.
  	link2 := nil.
  	link3 := nil.
  	link4 := nil.
+ 	
+ 	link := nil.
+ 	nonEmpty := nil.
+ 	otherList := nil.
+ 	
  	^ super tearDown!

Item was added:
+ ----- Method: LinkedListTest>>test0CopyTest (in category 'tests - fixture') -----
+ test0CopyTest
+ 	self empty.
+ 	self assert: self empty size = 0.
+ 	self nonEmpty.
+ 	self assert: (self nonEmpty size = 0) not.
+ 	self collectionWithElementsToRemove.
+ 	self assert: (self collectionWithElementsToRemove size = 0) not.
+ 	self collectionWithElementsToRemove do: [ :each | self assert: (self nonEmpty includes: each) ].
+ 	self elementToAdd.
+ 	self deny: (self nonEmpty includes: self elementToAdd).
+ 	self collectionNotIncluded.
+ 	self collectionNotIncluded do: [ :each | self deny: (self nonEmpty includes: each) ]!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureAsStringCommaAndDelimiterTest (in category 'tests - fixture') -----
+ test0FixtureAsStringCommaAndDelimiterTest
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty.
+ 	self empty.
+ 	self assert: self empty isEmpty.
+ 	self nonEmpty1Element.
+ 	self assert: self nonEmpty1Element size = 1!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureBeginsEndsWithTest (in category 'tests - fixture') -----
+ test0FixtureBeginsEndsWithTest
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty.
+ 	self assert: self nonEmpty size > 1.
+ 	self empty.
+ 	self assert: self empty isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureCopyPartOfSequenceableTest (in category 'tests - fixture') -----
+ test0FixtureCopyPartOfSequenceableTest
+ 	self collectionWithoutEqualElements.
+ 	self collectionWithoutEqualElements
+ 		do: [ :each | self assert: (self collectionWithoutEqualElements occurrencesOf: each) = 1 ].
+ 	self indexInForCollectionWithoutDuplicates.
+ 	self
+ 		assert:
+ 			(self indexInForCollectionWithoutDuplicates > 0 & self indexInForCollectionWithoutDuplicates)
+ 				< self collectionWithoutEqualElements size.
+ 	self empty.
+ 	self assert: self empty isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureCopySameContentsTest (in category 'tests - fixture') -----
+ test0FixtureCopySameContentsTest
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty.
+ 	self empty.
+ 	self assert: self empty isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureCopyWithOrWithoutSpecificElementsTest (in category 'tests - fixture') -----
+ test0FixtureCopyWithOrWithoutSpecificElementsTest
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty.
+ 	self indexInNonEmpty.
+ 	self assert: self indexInNonEmpty > 0.
+ 	self assert: self indexInNonEmpty <= self nonEmpty size!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureCopyWithReplacementTest (in category 'tests - fixture') -----
+ test0FixtureCopyWithReplacementTest
+ 	self replacementCollection.
+ 	self oldSubCollection.
+ 	self collectionWith1TimeSubcollection.
+ 	self assert: (self howMany: self oldSubCollection in: self collectionWith1TimeSubcollection) = 1!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureEmptyTest (in category 'tests - fixture') -----
+ test0FixtureEmptyTest
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty.
+ 	self empty.
+ 	self assert: self empty isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureIncludeTest (in category 'tests - fixture') -----
+ test0FixtureIncludeTest
+ 	| anElementIn |
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty.
+ 	self elementNotIn.
+ 	anElementIn := true.
+ 	self nonEmpty detect: [ :each | each = self elementNotIn ] ifNone: [ anElementIn := false ].
+ 	self assert: anElementIn = false.
+ 	self anotherElementNotIn.
+ 	anElementIn := true.
+ 	self nonEmpty detect: [ :each | each = self anotherElementNotIn ] ifNone: [ anElementIn := false ].
+ 	self assert: anElementIn = false.
+ 	self empty.
+ 	self assert: self empty isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureIncludeWithIdentityTest (in category 'tests - fixture') -----
+ test0FixtureIncludeWithIdentityTest
+ 	| anElement |
+ 	self collectionWithCopyNonIdentical.
+ 	anElement := self collectionWithCopyNonIdentical anyOne.
+ 	self deny: anElement == anElement copy!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureIndexAccessTest (in category 'tests - fixture') -----
+ test0FixtureIndexAccessTest
+ 	| res |
+ 	self collectionMoreThan1NoDuplicates.
+ 	self assert: self collectionMoreThan1NoDuplicates size = 5.
+ 	res := true.
+ 	self collectionMoreThan1NoDuplicates
+ 		detect: [ :each | (self collectionMoreThan1NoDuplicates occurrencesOf: each) > 1 ]
+ 		ifNone: [ res := false ].
+ 	self assert: res = false.
+ 	self elementInForIndexAccessing.
+ 	self assert: (self collectionMoreThan1NoDuplicates includes: self elementInForIndexAccessing).
+ 	self elementNotInForIndexAccessing.
+ 	self deny: (self collectionMoreThan1NoDuplicates includes: self elementNotInForIndexAccessing)!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureIterateSequencedReadableTest (in category 'tests - fixture') -----
+ test0FixtureIterateSequencedReadableTest
+ 
+ 	| res |
+ 	
+ 	self nonEmptyMoreThan1Element.
+ 	self assert: self nonEmptyMoreThan1Element  size > 1.
+ 	
+ 	
+ 	self empty.
+ 	self assert: self empty isEmpty .
+ 	
+ 	res := true.
+ 	self nonEmptyMoreThan1Element    
+ 	detect: [ :each | (self nonEmptyMoreThan1Element    occurrencesOf: each) > 1 ]
+ 	ifNone: [ res := false ].
+ 	self assert: res = false.!

Item was added:
+ ----- 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 added:
+ ----- Method: LinkedListTest>>test0FixtureOccurrencesTest (in category 'tests - fixture') -----
+ test0FixtureOccurrencesTest
+ 	| tmp |
+ 	self empty.
+ 	self assert: self empty isEmpty.
+ 	self collectionWithoutEqualElements.
+ 	self deny: self collectionWithoutEqualElements isEmpty.
+ 	tmp := OrderedCollection new.
+ 	self collectionWithoutEqualElements
+ 		do: [ :each | 
+ 			self deny: (tmp includes: each).
+ 			tmp add: each ].
+ 	self elementNotInForOccurrences.
+ 	self deny: (self collectionWithoutEqualElements includes: self elementNotInForOccurrences)!

Item was added:
+ ----- Method: LinkedListTest>>test0FixturePrintTest (in category 'tests - fixture') -----
+ test0FixturePrintTest
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureRequirementsOfTAddTest (in category 'tests - fixture') -----
+ test0FixtureRequirementsOfTAddTest
+ 	self collectionWithElement.
+ 	self otherCollection.
+ 	self element.
+ 	self assert: (self collectionWithElement includes: self element).
+ 	self deny: (self otherCollection includes: self element)!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureSequencedElementAccessTest (in category 'tests - fixture') -----
+ test0FixtureSequencedElementAccessTest
+ 	self moreThan4Elements.
+ 	self assert: self moreThan4Elements size >= 4.
+ 	self subCollectionNotIn.
+ 	self subCollectionNotIn detect: [ :each | (self moreThan4Elements includes: each) not ] ifNone: [ self assert: false ].
+ 	self elementNotInForElementAccessing.
+ 	self deny: (self moreThan4Elements includes: self elementNotInForElementAccessing).
+ 	self elementInForElementAccessing.
+ 	self assert: (self moreThan4Elements includes: self elementInForElementAccessing)!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureSetAritmeticTest (in category 'tests - fixture') -----
+ test0FixtureSetAritmeticTest
+ 	self collection.
+ 	self deny: self collection isEmpty.
+ 	self nonEmpty.
+ 	self deny: self nonEmpty isEmpty.
+ 	self anotherElementOrAssociationNotIn.
+ 	self collection isDictionary
+ 		ifTrue: [ self deny: (self collection associations includes: self anotherElementOrAssociationNotIn key) ]
+ 		ifFalse: [ self deny: (self collection includes: self anotherElementOrAssociationNotIn) ].
+ 	self collectionClass!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureSubcollectionAccessTest (in category 'tests - fixture') -----
+ test0FixtureSubcollectionAccessTest
+ 	self moreThan3Elements.
+ 	self assert: self moreThan3Elements size > 2!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureTConvertTest (in category 'tests - fixture') -----
+ test0FixtureTConvertTest
+ 	"a collection of number without equal elements:"
+ 
+ 	| res |
+ 	self collectionWithoutEqualElements.
+ 	res := true.
+ 	self collectionWithoutEqualElements
+ 		detect: [ :each | (self collectionWithoutEqualElements occurrencesOf: each) > 1 ]
+ 		ifNone: [ res := false ].
+ 	self assert: res = false!

Item was added:
+ ----- Method: LinkedListTest>>test0FixtureTRemoveTest (in category 'tests - fixture') -----
+ test0FixtureTRemoveTest
+ 	| duplicate |
+ 	self empty.
+ 	self nonEmptyWithoutEqualElements.
+ 	self deny: self nonEmptyWithoutEqualElements isEmpty.
+ 	duplicate := true.
+ 	self nonEmptyWithoutEqualElements
+ 		detect: [ :each | (self nonEmptyWithoutEqualElements occurrencesOf: each) > 1 ]
+ 		ifNone: [ duplicate := false ].
+ 	self assert: duplicate = false.
+ 	self elementNotIn.
+ 	self assert: self empty isEmpty.
+ 	self deny: self nonEmptyWithoutEqualElements isEmpty.
+ 	self deny: (self nonEmptyWithoutEqualElements includes: self elementNotIn)!

Item was added:
+ ----- Method: LinkedListTest>>test0TStructuralEqualityTest (in category 'tests - fixture') -----
+ test0TStructuralEqualityTest
+ 	self empty.
+ 	self nonEmpty.
+ 	self assert: self empty isEmpty.
+ 	self deny: self nonEmpty isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testAfter (in category 'tests - element accessing') -----
+ testAfter
+ 	"self debug: #testAfter"
+ 	self assert: (self moreThan4Elements after: (self moreThan4Elements at: 1)) = (self moreThan4Elements at: 2).
+ 	self 
+ 		should: 
+ 			[ self moreThan4Elements after: (self moreThan4Elements at: self moreThan4Elements size) ]
+ 		raise: Error.
+ 	self 
+ 		should: [ self moreThan4Elements after: self elementNotInForElementAccessing ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testAfterIfAbsent (in category 'tests - element accessing') -----
+ testAfterIfAbsent
+ 	"self debug: #testAfterIfAbsent"
+ 	self assert: (self moreThan4Elements 
+ 			after: (self moreThan4Elements at: 1)
+ 			ifAbsent: [ 33 ]) = (self moreThan4Elements at: 2).
+ 	self assert: (self moreThan4Elements 
+ 			after: (self moreThan4Elements at: self moreThan4Elements size)
+ 			ifAbsent: [ 33 ]) = 33.
+ 	self assert: (self moreThan4Elements 
+ 			after: self elementNotInForElementAccessing
+ 			ifAbsent: [ 33 ]) = 33!

Item was added:
+ ----- Method: LinkedListTest>>testAllButFirst (in category 'tests - subcollections access') -----
+ testAllButFirst
+ 	"self debug: #testAllButFirst"
+ 	| abf col |
+ 	col := self moreThan3Elements.
+ 	abf := col allButFirst.
+ 	self deny: abf first = col first.
+ 	self assert: abf size + 1 = col size!

Item was added:
+ ----- Method: LinkedListTest>>testAllButFirstDo (in category 'tests - iterate on sequenced reable collections') -----
+ testAllButFirstDo
+ 	
+ 	| result |
+ 	result:= OrderedCollection  new.
+ 	
+ 	self nonEmptyMoreThan1Element  allButFirstDo: [:each | result add: each].
+ 	
+ 	1 to: (result size) do:
+ 		[:i|
+ 		self assert: (self nonEmptyMoreThan1Element  at:(i +1))=(result at:i)].
+ 	
+ 	self assert: result size=(self nonEmptyMoreThan1Element  size-1).!

Item was added:
+ ----- Method: LinkedListTest>>testAllButFirstNElements (in category 'tests - subcollections access') -----
+ testAllButFirstNElements
+ 	"self debug: #testAllButFirst"
+ 	| abf col |
+ 	col := self moreThan3Elements.
+ 	abf := col allButFirst: 2.
+ 	1 
+ 		to: abf size
+ 		do: [ :i | self assert: (abf at: i) = (col at: i + 2) ].
+ 	self assert: abf size + 2 = col size!

Item was added:
+ ----- Method: LinkedListTest>>testAllButLast (in category 'tests - subcollections access') -----
+ testAllButLast
+ 	"self debug: #testAllButLast"
+ 	| abf col |
+ 	col := self moreThan3Elements.
+ 	abf := col allButLast.
+ 	self deny: abf last = col last.
+ 	self assert: abf size + 1 = col size!

Item was added:
+ ----- Method: LinkedListTest>>testAllButLastDo (in category 'tests - iterate on sequenced reable collections') -----
+ testAllButLastDo
+ 	
+ 	| result |
+ 	result:= OrderedCollection  new.
+ 	
+ 	self nonEmptyMoreThan1Element  allButLastDo: [:each | result add: each].
+ 	
+ 	1 to: (result size) do:
+ 		[:i|
+ 		self assert: (self nonEmptyMoreThan1Element  at:(i ))=(result at:i)].
+ 	
+ 	self assert: result size=(self nonEmptyMoreThan1Element  size-1).!

Item was added:
+ ----- Method: LinkedListTest>>testAllButLastNElements (in category 'tests - subcollections access') -----
+ testAllButLastNElements
+ 	"self debug: #testAllButFirst"
+ 	| abf col |
+ 	col := self moreThan3Elements.
+ 	abf := col allButLast: 2.
+ 	1 
+ 		to: abf size
+ 		do: [ :i | self assert: (abf at: i) = (col at: i) ].
+ 	self assert: abf size + 2 = col size!

Item was added:
+ ----- Method: LinkedListTest>>testAllSatisfy (in category 'tests - iterating') -----
+ testAllSatisfy
+ 
+ 	| element |
+ 	" when all element  satisfy the condition, should return true : "
+ 	self assert: ( self collectionWithoutNilElements  allSatisfy: [:each | (each notNil) ] ).
+ 	
+ 	" when all element don't satisfy the condition, should return false : "
+ 	self deny: ( self collectionWithoutNilElements  allSatisfy: [:each | (each notNil) not ] ).
+ 	
+ 	" when only one element doesn't satisfy the condition' should return false'"
+ 	element := self collectionWithoutNilElements anyOne.
+ 	self deny: ( self collectionWithoutNilElements  allSatisfy: [:each | (each = element) not] ).!

Item was added:
+ ----- Method: LinkedListTest>>testAllSatisfyEmpty (in category 'tests - iterating') -----
+ testAllSatisfyEmpty
+ 
+ 	self assert: ( self empty allSatisfy: [:each | false]).
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testAnySastify (in category 'tests - iterating') -----
+ testAnySastify
+ 
+ 	| element |
+ 	" when all elements satisty the condition, should return true :"
+ 	self assert: ( self collectionWithoutNilElements anySatisfy: [:each | each notNil ]).
+ 	
+ 	" when only one element satisfy the condition, should return true :"
+ 	element := self collectionWithoutNilElements anyOne.
+ 	self assert: ( self collectionWithoutNilElements  anySatisfy: [:each | (each = element)  ]   ).
+ 	
+ 	" when all elements don't satisty the condition, should return false :"
+ 	self deny: ( self collectionWithoutNilElements anySatisfy: [:each | (each notNil) not ]).
+ !

Item was added:
+ ----- Method: LinkedListTest>>testAsArray (in category 'tests - converting') -----
+ testAsArray
+ 	"self debug: #testAsArray3"
+ 	self 
+ 		assertSameContents: self collectionWithoutEqualElements
+ 		whenConvertedTo: Array!

Item was added:
+ ----- Method: LinkedListTest>>testAsBag (in category 'tests - converting') -----
+ testAsBag
+ 
+ 	self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Bag!

Item was added:
+ ----- Method: LinkedListTest>>testAsCommaStringEmpty (in category 'tests - comma and delimiter') -----
+ testAsCommaStringEmpty
+ 
+ 	self assert: self empty asCommaString = ''.
+ 	self assert: self empty asCommaStringAnd = ''.
+ 	
+ !

Item was added:
+ ----- Method: LinkedListTest>>testAsCommaStringMore (in category 'tests - comma and delimiter') -----
+ testAsCommaStringMore
+ 
+ 	"self assert: self oneTwoThreeItemCol asCommaString = '1, 2, 3'.
+ 	self assert: self oneTwoThreeItemCol asCommaStringAnd = '1, 2 and 3'
+ "
+ 
+ 	| result resultAnd index allElementsAsString |
+ 	result:= self nonEmpty asCommaString .
+ 	resultAnd:= self nonEmpty asCommaStringAnd .
+  
+ 	index := 1.
+ 	(result findBetweenSubStrs: ',' )do:
+ 		[:each |
+ 		index = 1
+ 			ifTrue: [self assert: each= ((self nonEmpty at:index)asString)]
+ 			ifFalse: [self assert: each= (' ',(self nonEmpty at:index) asString)].
+ 		index:=index+1
+ 		].
+ 	
+ 	"verifying esultAnd :"
+ 	allElementsAsString:=(resultAnd findBetweenSubStrs: ',' ).
+ 	1 to: allElementsAsString size do:
+ 		[:i | 
+ 		i<(allElementsAsString size )
+ 			ifTrue: [
+ 			i = 1
+ 				ifTrue:[self assert: (allElementsAsString at:i)=((self nonEmpty at:i) asString)]
+ 				ifFalse:[self assert: (allElementsAsString at:i)=(' ',(self nonEmpty at:i) asString)]
+ 				].
+ 		i=(allElementsAsString size)
+ 			ifTrue:[ 
+ 			i = 1
+ 				ifTrue:[self assert: (allElementsAsString at:i)=( (self nonEmpty at:i ) asString ,' and ', (self nonEmpty at: ( i + 1) ) asString )]
+ 				ifFalse:[self assert: (allElementsAsString at:i)=( ' ' , (self nonEmpty at:i ) asString ,' and ', (self nonEmpty at: ( i + 1) ) asString )]
+ 				].
+ 		
+ 		
+ 			].!

Item was added:
+ ----- Method: LinkedListTest>>testAsCommaStringOne (in category 'tests - comma and delimiter') -----
+ testAsCommaStringOne
+ 	
+ 	"self assert: self oneItemCol asCommaString = '1'.
+ 	self assert: self oneItemCol asCommaStringAnd = '1'."
+ 
+ 	self assert: self nonEmpty1Element  asCommaString = (self nonEmpty1Element first asString).
+ 	self assert: self nonEmpty1Element  asCommaStringAnd = (self nonEmpty1Element first asString).
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testAsIdentitySet (in category 'tests - converting') -----
+ testAsIdentitySet
+ 	"test with a collection without equal elements :"
+ 	self 
+ 		assertSameContents: self collectionWithoutEqualElements
+ 		whenConvertedTo: IdentitySet.
+ !

Item was added:
+ ----- Method: LinkedListTest>>testAsOrderedCollection (in category 'tests - converting') -----
+ testAsOrderedCollection
+ 	
+ 	self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: OrderedCollection!

Item was added:
+ ----- Method: LinkedListTest>>testAsSet (in category 'tests - converting') -----
+ testAsSet
+ 	| |
+ 	"test with a collection without equal elements :"
+ 	self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Set.
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testAsStringOnDelimiterEmpty (in category 'tests - comma and delimiter') -----
+ testAsStringOnDelimiterEmpty
+ 
+ 	| delim emptyStream |
+ 	delim := ', '.
+ 	emptyStream := ReadWriteStream on: ''.
+ 	self empty asStringOn: emptyStream delimiter: delim.
+ 	self assert: emptyStream contents = ''.
+ !

Item was added:
+ ----- Method: LinkedListTest>>testAsStringOnDelimiterLastEmpty (in category 'tests - comma and delimiter') -----
+ testAsStringOnDelimiterLastEmpty
+ 
+ 	| delim emptyStream |
+ 	delim := ', '.
+ 	emptyStream := ReadWriteStream on: ''.
+ 	self empty asStringOn: emptyStream delimiter: delim last:'and'.
+ 	self assert: emptyStream contents = ''.
+ !

Item was added:
+ ----- Method: LinkedListTest>>testAsStringOnDelimiterLastMore (in category 'tests - comma and delimiter') -----
+ testAsStringOnDelimiterLastMore
+ 
+ 	| delim multiItemStream result last allElementsAsString |
+ 	
+ 	delim := ', '.
+ 	last := 'and'.
+ 	result:=''.
+ 	multiItemStream := ReadWriteStream on:result.
+ 	self nonEmpty  asStringOn: multiItemStream delimiter: ', ' last: last.
+ 	
+ 	allElementsAsString:=(result findBetweenSubStrs: ', ' ).
+ 	1 to: allElementsAsString size do:
+ 		[:i | 
+ 		i<(allElementsAsString size-1 )
+ 			ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString)].
+ 		i=(allElementsAsString size-1)
+ 			ifTrue:[ self deny: (allElementsAsString at:i)=(last)asString].
+ 		i=(allElementsAsString size)
+ 			ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)].
+ 			].
+ 	
+ !

Item was added:
+ ----- Method: LinkedListTest>>testAsStringOnDelimiterLastOne (in category 'tests - comma and delimiter') -----
+ testAsStringOnDelimiterLastOne
+ 
+ 	| delim oneItemStream result |
+ 	
+ 	delim := ', '.
+ 	result:=''.
+ 	oneItemStream := ReadWriteStream on: result.
+ 	self nonEmpty1Element  asStringOn: oneItemStream delimiter: delim last: 'and'.
+ 	oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)].
+ 	
+ 
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testAsStringOnDelimiterMore (in category 'tests - comma and delimiter') -----
+ testAsStringOnDelimiterMore
+ 
+ 	| delim multiItemStream result index |
+ 	"delim := ', '.
+ 	multiItemStream := '' readWrite.
+ 	self oneTwoThreeItemCol asStringOn: multiItemStream delimiter: ', '.
+ 	self assert: multiItemStream contents = '1, 2, 3'."
+ 	
+ 	delim := ', '.
+ 	result:=''.
+ 	multiItemStream := ReadWriteStream on:result.
+ 	self nonEmpty  asStringOn: multiItemStream delimiter: ', '.
+ 	
+ 	index:=1.
+ 	(result findBetweenSubStrs: ', ' )do:
+ 		[:each |
+ 		self assert: each= ((self nonEmpty at:index)asString).
+ 		index:=index+1
+ 		].!

Item was added:
+ ----- Method: LinkedListTest>>testAsStringOnDelimiterOne (in category 'tests - comma and delimiter') -----
+ testAsStringOnDelimiterOne
+ 
+ 	| delim oneItemStream result |
+ 	"delim := ', '.
+ 	oneItemStream := '' readWrite.
+ 	self oneItemCol asStringOn: oneItemStream delimiter: delim.
+ 	self assert: oneItemStream contents = '1'."
+ 	
+ 	delim := ', '.
+ 	result:=''.
+ 	oneItemStream := ReadWriteStream on: result.
+ 	self nonEmpty1Element  asStringOn: oneItemStream delimiter: delim.
+ 	oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)].
+ 	
+ 
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testAt (in category 'tests - element accessing') -----
+ testAt
+ 	"self debug: #testAt"
+ 	"
+ 	self assert: (self accessCollection at: 1) = 1.
+ 	self assert: (self accessCollection at: 2) = 2.
+ 	"
+ 	| index |
+ 	index := self moreThan4Elements indexOf: self elementInForElementAccessing.
+ 	self assert: (self moreThan4Elements at: index) = self elementInForElementAccessing!

Item was added:
+ ----- Method: LinkedListTest>>testAtAll (in category 'tests - element accessing') -----
+ testAtAll
+ 	"self debug: #testAtAll"
+ 	"	self flag: #theCollectionshouldbe102030intheFixture.
+ 	
+ 	self assert: (self accessCollection atAll: #(2 1)) first = self accessCollection second.
+ 	self assert: (self accessCollection atAll: #(2)) first = self accessCollection second."
+ 	| result |
+ 	result := self moreThan4Elements atAll: #(2 1 2 ).
+ 	self assert: (result at: 1) = (self moreThan4Elements at: 2).
+ 	self assert: (result at: 2) = (self moreThan4Elements at: 1).
+ 	self assert: (result at: 3) = (self moreThan4Elements at: 2).
+ 	self assert: (self moreThan4Elements atAll: #()) = self moreThan4Elements species new!

Item was added:
+ ----- Method: LinkedListTest>>testAtIfAbsent (in category 'tests - element accessing') -----
+ testAtIfAbsent
+ 	"self debug: #testAt"
+ 	| absent |
+ 	absent := false.
+ 	self moreThan4Elements 
+ 		at: self moreThan4Elements size + 1
+ 		ifAbsent: [ absent := true ].
+ 	self assert: absent = true.
+ 	absent := false.
+ 	self moreThan4Elements 
+ 		at: self moreThan4Elements size
+ 		ifAbsent: [ absent := true ].
+ 	self assert: absent = false!

Item was added:
+ ----- Method: LinkedListTest>>testAtLast (in category 'tests - element accessing') -----
+ testAtLast
+ 	"self debug: #testAtLast"
+ 	| index |
+ 	self assert: (self moreThan4Elements atLast: 1) = self moreThan4Elements last.
+ 	"tmp:=1.
+ 	self do:
+ 		[:each | 
+ 		each =self elementInForIndexAccessing 
+ 			ifTrue:[index:=tmp].
+ 		tmp:=tmp+1]."
+ 	index := self moreThan4Elements indexOf: self elementInForElementAccessing.
+ 	self assert: (self moreThan4Elements atLast: index) = (self moreThan4Elements at: self moreThan4Elements size - index + 1)!

Item was added:
+ ----- Method: LinkedListTest>>testAtLastError (in category 'tests - element accessing') -----
+ testAtLastError
+ 	"self debug: #testAtLast"
+ 	self 
+ 		should: [ self moreThan4Elements atLast: self moreThan4Elements size + 1 ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testAtLastIfAbsent (in category 'tests - element accessing') -----
+ testAtLastIfAbsent
+ 	"self debug: #testAtLastIfAbsent"
+ 	self assert: (self moreThan4Elements 
+ 			atLast: 1
+ 			ifAbsent: [ nil ]) = self moreThan4Elements last.
+ 	self assert: (self moreThan4Elements 
+ 			atLast: self moreThan4Elements size + 1
+ 			ifAbsent: [ 222 ]) = 222!

Item was added:
+ ----- Method: LinkedListTest>>testAtOutOfBounds (in category 'tests - element accessing') -----
+ testAtOutOfBounds
+ 	"self debug: #testAtOutOfBounds"
+ 	self 
+ 		should: [ self moreThan4Elements at: self moreThan4Elements size + 1 ]
+ 		raise: Error.
+ 	self 
+ 		should: [ self moreThan4Elements at: -1 ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testAtPin (in category 'tests - element accessing') -----
+ testAtPin
+ 	"self debug: #testAtPin"
+ 	self assert: (self moreThan4Elements atPin: 2) = self moreThan4Elements second.
+ 	self assert: (self moreThan4Elements atPin: 99) = self moreThan4Elements last.
+ 	self assert: (self moreThan4Elements atPin: -99) = self moreThan4Elements first!

Item was added:
+ ----- Method: LinkedListTest>>testAtPut (in category 'tests - sequenceable') -----
+ testAtPut
+ 	| ll |
+ 	ll := LinkedList new.
+ 	ll add: 1.
+ 	ll at: 1 put: 2.
+ 	self assert: (ll at: 1) equals: 2!

Item was added:
+ ----- Method: LinkedListTest>>testAtPutOutsideBounds (in category 'tests - sequenceable') -----
+ testAtPutOutsideBounds
+ 	| ll |
+ 	ll := LinkedList new.
+ 	self should: [ ll at: 1 put: 1 ] raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testAtRandom (in category 'tests - element accessing') -----
+ testAtRandom
+ 	| result |
+ 	result := self nonEmpty atRandom .
+ 	self assert: (self nonEmpty includes: result).!

Item was added:
+ ----- Method: LinkedListTest>>testAtWrap (in category 'tests - element accessing') -----
+ testAtWrap
+ 	"self debug: #testAt"
+ 	"
+ 	self assert: (self accessCollection at: 1) = 1.
+ 	self assert: (self accessCollection at: 2) = 2.
+ 	"
+ 	| index |
+ 	index := self moreThan4Elements indexOf: self elementInForElementAccessing.
+ 	self assert: (self moreThan4Elements atWrap: index) = self elementInForElementAccessing.
+ 	self assert: (self moreThan4Elements atWrap: index + self moreThan4Elements size) = self elementInForElementAccessing.
+ 	self assert: (self moreThan4Elements atWrap: index - self moreThan4Elements size) = self elementInForElementAccessing.
+ 	self assert: (self moreThan4Elements atWrap: 1 + self moreThan4Elements size) = (self moreThan4Elements at: 1)!

Item was added:
+ ----- Method: LinkedListTest>>testBasicCollect (in category 'tests - iterating') -----
+ testBasicCollect
+ 
+ 	| res index |
+ 	index := 0.
+ 	res := self collectionWithoutNilElements collect: [ :each | 
+ 		index := index + 1.
+ 		each ].
+ 	
+ 	res do: [ :each | 
+ 		self assert: (self collectionWithoutNilElements occurrencesOf: each) = (res occurrencesOf: each)].
+ 	self assert: index equals: self collectionWithoutNilElements size.
+ 	 !

Item was added:
+ ----- Method: LinkedListTest>>testBasicCollectEmpty (in category 'tests - iterating') -----
+ testBasicCollectEmpty
+ 
+ 	| res |
+ 	res := self empty collect: [:each | each class].
+ 	self assert: res isEmpty
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testBefore (in category 'tests - element accessing') -----
+ testBefore
+ 	"self debug: #testBefore"
+ 	self assert: (self moreThan4Elements before: (self moreThan4Elements at: 2)) = (self moreThan4Elements at: 1).
+ 	self 
+ 		should: [ self moreThan4Elements before: (self moreThan4Elements at: 1) ]
+ 		raise: Error.
+ 	self 
+ 		should: [ self moreThan4Elements before: 66 ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testBeforeIfAbsent (in category 'tests - element accessing') -----
+ testBeforeIfAbsent
+ 	"self debug: #testBefore"
+ 	self assert: (self moreThan4Elements 
+ 			before: (self moreThan4Elements at: 1)
+ 			ifAbsent: [ 99 ]) = 99.
+ 	self assert: (self moreThan4Elements 
+ 			before: (self moreThan4Elements at: 2)
+ 			ifAbsent: [ 99 ]) = (self moreThan4Elements at: 1)!

Item was added:
+ ----- Method: LinkedListTest>>testCollectFromTo (in category 'tests - iterate on sequenced reable collections') -----
+ testCollectFromTo
+ 	
+ 	| result |
+ 	result:=self nonEmptyMoreThan1Element 
+ 		collect: [ :each | each ]
+ 		from: 1
+ 		to: (self nonEmptyMoreThan1Element size - 1).
+ 		
+ 	1 to: result size
+ 		do: [ :i | self assert: (self nonEmptyMoreThan1Element at: i) = (result at: i) ].
+ 	self assert: result size = (self nonEmptyMoreThan1Element size - 1)!

Item was added:
+ ----- Method: LinkedListTest>>testCollectOnEmpty (in category 'tests - iterating') -----
+ testCollectOnEmpty
+ 	self assert: (self empty collect: [:e | self fail]) isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testCollectThenDoOnEmpty (in category 'tests - iterating') -----
+ testCollectThenDoOnEmpty
+ 
+ 	self assert: (self empty collect: [:e | self fail] thenDo: [ self fail ]) isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testCollectThenSelectOnEmpty (in category 'tests - iterating') -----
+ testCollectThenSelectOnEmpty
+ 
+ 	self assert: (self empty collect: [:e | self fail] thenSelect: [:e | self fail ]) isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testCopyAfter (in category 'tests - copying part of sequenceable') -----
+ testCopyAfter
+ 	| result index collection |
+ 	collection := self collectionWithoutEqualElements .
+ 	index:= self indexInForCollectionWithoutDuplicates .
+ 	result := collection   copyAfter: (collection  at:index ).
+ 	
+ 	"verifying content: "
+ 	(1) to: result size do: 
+ 		[:i |
+ 		self assert: (collection   at:(i + index ))=(result at: (i))].
+ 
+ 	"verify size: "
+ 	self assert: result size = (collection   size - index).!

Item was added:
+ ----- Method: LinkedListTest>>testCopyAfterEmpty (in category 'tests - copying part of sequenceable') -----
+ testCopyAfterEmpty
+ 	| result |
+ 	result := self empty copyAfter: self collectionWithoutEqualElements first.
+ 	self assert: result isEmpty.
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testCopyAfterLast (in category 'tests - copying part of sequenceable') -----
+ testCopyAfterLast
+ 	| result index collection |
+ 	collection := self collectionWithoutEqualElements .
+ 	index:= self indexInForCollectionWithoutDuplicates .
+ 	result := collection   copyAfterLast: (collection  at:index ).
+ 	
+ 	"verifying content: "
+ 	(1) to: result size do: 
+ 		[:i |
+ 		self assert: (collection   at:(i + index ))=(result at: (i))].
+ 
+ 	"verify size: "
+ 	self assert: result size = (collection   size - index).!

Item was added:
+ ----- Method: LinkedListTest>>testCopyAfterLastEmpty (in category 'tests - copying part of sequenceable') -----
+ testCopyAfterLastEmpty
+ 	| result |
+ 	result := self empty copyAfterLast: self collectionWithoutEqualElements first.
+ 	self assert: result isEmpty.!

Item was added:
+ ----- Method: LinkedListTest>>testCopyEmptyWith (in category 'tests - copy') -----
+ testCopyEmptyWith
+ 	"self debug: #testCopyWith"
+ 	| res anElement |
+ 	anElement := self elementToAdd.
+ 	res := self empty copyWith: anElement.
+ 	self assert: res size = (self empty size + 1).
+ 	self assert: (res includes: (anElement value))!

Item was added:
+ ----- Method: LinkedListTest>>testCopyEmptyWithout (in category 'tests - copy') -----
+ testCopyEmptyWithout
+ 	"self debug: #testCopyEmptyWithout"
+ 	| res |
+ 	res := self empty copyWithout: self elementToAdd.
+ 	self assert: res size = self empty size.
+ 	self deny: (res includes: self elementToAdd)!

Item was added:
+ ----- Method: LinkedListTest>>testCopyEmptyWithoutAll (in category 'tests - copy') -----
+ testCopyEmptyWithoutAll
+ 	"self debug: #testCopyEmptyWithoutAll"
+ 	| res |
+ 	res := self empty copyWithoutAll: self collectionWithElementsToRemove.
+ 	self assert: res size = self empty size.
+ 	self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ]!

Item was added:
+ ----- Method: LinkedListTest>>testCopyEquals (in category 'tests - copy') -----
+ testCopyEquals
+ 	"self debug: #testCopySameClass"
+ 	"A copy should be equivalent to the things it's a copy of"
+ 	
+ 	| copy | 
+ 	copy := self nonEmpty copy.
+ 	self assert: copy  = self nonEmpty.!

Item was added:
+ ----- Method: LinkedListTest>>testCopyFromTo (in category 'tests - copying part of sequenceable') -----
+ testCopyFromTo
+ 	| result  index collection |
+ 	collection := self collectionWithoutEqualElements .
+ 	index :=self indexInForCollectionWithoutDuplicates .
+ 	result := collection   copyFrom: index  to: collection  size .
+ 	
+ 	"verify content of 'result' : "
+ 	1 to: result size do:
+ 		[:i | 
+ 		self assert: (result at:i)=(collection  at: (i + index - 1))].
+ 	
+ 	"verify size of 'result' : "
+ 	self assert: result size = (collection  size - index + 1).!

Item was added:
+ ----- Method: LinkedListTest>>testCopyNonEmptyWith (in category 'tests - copy') -----
+ testCopyNonEmptyWith
+ 	"self debug: #testCopyNonEmptyWith"
+ 	| res anElement |
+ 	anElement := self elementToAdd .
+ 	res := self nonEmpty copyWith: anElement.
+ 	"here we do not test the size since for a non empty set we would get a problem.
+ 	Then in addition copy is not about duplicate management. The element should 
+ 	be in at the end."
+ 	self assert: (res includes: (anElement value)).
+ 	self nonEmpty do: [ :each | res includes: each ]!

Item was added:
+ ----- Method: LinkedListTest>>testCopyNonEmptyWithout (in category 'tests - copy') -----
+ testCopyNonEmptyWithout
+ 	"self debug: #testCopyNonEmptyWithout"
+ 	
+ 	| res anElementOfTheCollection |
+ 	anElementOfTheCollection :=  self nonEmpty anyOne.
+ 	res := (self nonEmpty copyWithout: anElementOfTheCollection).
+ 	"here we do not test the size since for a non empty set we would get a problem.
+ 	Then in addition copy is not about duplicate management. The element should 
+ 	be in at the end."
+ 	self deny: (res includes: anElementOfTheCollection).
+ 	self nonEmpty do:
+ 		[:each | (each = anElementOfTheCollection) 
+ 					ifFalse: [self assert: (res includes: each)]].
+ 	
+ !

Item was added:
+ ----- Method: LinkedListTest>>testCopyNonEmptyWithoutAll (in category 'tests - copy') -----
+ testCopyNonEmptyWithoutAll
+ 	"self debug: #testCopyNonEmptyWithoutAll"
+ 	| res |
+ 	res := self nonEmpty copyWithoutAll: self collectionWithElementsToRemove.
+ 	"here we do not test the size since for a non empty set we would get a problem.
+ 	Then in addition copy is not about duplicate management. The element should 
+ 	be in at the end."
+ 	self collectionWithElementsToRemove do: [ :each | self deny: (res includes: (each)) ].
+ 	self nonEmpty do: 
+ 		[ :each | 
+ 		(self collectionWithElementsToRemove includes: each) ifFalse: [ self assert: (res includes: each) ] ]!

Item was added:
+ ----- Method: LinkedListTest>>testCopyNonEmptyWithoutAllNotIncluded (in category 'tests - copy') -----
+ testCopyNonEmptyWithoutAllNotIncluded
+ 	"self debug: #testCopyNonEmptyWithoutAllNotIncluded"
+ 	| res |
+ 	res := self nonEmpty copyWithoutAll: self collectionNotIncluded.
+ 	"here we do not test the size since for a non empty set we would get a problem.
+ 	Then in addition copy is not about duplicate management. The element should 
+ 	be in at the end."
+ 	self nonEmpty do: [ :each | self assert: (res includes: each) ]!

Item was added:
+ ----- Method: LinkedListTest>>testCopyNonEmptyWithoutNotIncluded (in category 'tests - copy') -----
+ testCopyNonEmptyWithoutNotIncluded
+ 	"self debug: #testCopyNonEmptyWithoutNotIncluded"
+ 	| res |
+ 	res := self nonEmpty copyWithout: self elementToAdd.
+ 	"here we do not test the size since for a non empty set we would get a problem.
+ 	Then in addition copy is not about duplicate management. The element should 
+ 	be in at the end."
+ 	self nonEmpty do: [ :each | self assert: (res includes: each) ]!

Item was added:
+ ----- Method: LinkedListTest>>testCopyNotSame (in category 'tests - copy') -----
+ testCopyNotSame
+ 	"self debug: #testCopySameClass"
+ 	"A copy of a collection should always be of the same class as the instance it copies"
+ 	
+ 	| copy | 
+ 	copy := self nonEmpty copy.
+ 	self deny: copy  == self nonEmpty.!

Item was added:
+ ----- Method: LinkedListTest>>testCopyReplaceAllWith1Occurence (in category 'tests - copying with replacement') -----
+ testCopyReplaceAllWith1Occurence
+ 	| result  firstIndexesOfOccurrence index endPartIndexResult endPartIndexCollection |
+ 	
+ 	result := self collectionWith1TimeSubcollection  copyReplaceAll: self oldSubCollection with: self replacementCollection .
+ 	
+ 	"detecting indexes of olSubCollection"
+ 	firstIndexesOfOccurrence  := self firstIndexesOf: self oldSubCollection in: self collectionWith1TimeSubcollection .
+ 	index:= firstIndexesOfOccurrence at: 1.
+ 	
+ 	"verify content of 'result' : "
+ 	"first part of 'result'' : '"
+ 
+ 	1 to: (index -1) do: 
+ 		[
+ 		:i |  
+ 		self assert: (self collectionWith1TimeSubcollection  at:i)=(result at: i)
+ 		].
+ 
+ 	" middle part containing replacementCollection : "
+ 	
+ 	index to: (index + self replacementCollection size-1) do: 
+ 		[
+ 		:i |
+ 		self assert: ( result at: i )=(self replacementCollection at: ( i - index + 1 ))
+ 		].
+ 	
+ 	" end part :"
+ 	
+ 	endPartIndexResult :=  index + self replacementCollection  size .
+ 	endPartIndexCollection :=   index + self oldSubCollection size  .
+ 	
+ 	1 to: (result size - endPartIndexResult - 1 ) do:
+ 		[ 
+ 		:i |
+ 		self assert: (result at: ( endPartIndexResult + i - 1 ) ) = (self collectionWith1TimeSubcollection  at: ( endPartIndexCollection + i - 1 ) ).
+ 		].
+ 	
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testCopyReplaceFromToWith (in category 'tests - copying with replacement') -----
+ testCopyReplaceFromToWith
+ 	| result  indexOfSubcollection lastIndexOfOldSubcollection lastIndexOfReplacementCollection |
+ 	
+ 	indexOfSubcollection := (self firstIndexesOf: self oldSubCollection  in:  self collectionWith1TimeSubcollection) at: 1. 
+ 	lastIndexOfOldSubcollection := indexOfSubcollection + self oldSubCollection size -1.
+ 	lastIndexOfReplacementCollection := indexOfSubcollection + self replacementCollection  size -1.
+ 	
+ 	result := self collectionWith1TimeSubcollection  copyReplaceFrom: indexOfSubcollection  to: lastIndexOfOldSubcollection   with: self replacementCollection .
+ 	
+ 	"verify content of 'result' : "
+ 	"first part of 'result'  "
+ 	
+ 	1 to: (indexOfSubcollection  - 1) do: 
+ 		[ 
+ 		:i | 
+ 		self assert: (self collectionWith1TimeSubcollection  at:i) = (result at: i)
+ 		].
+ 	
+ 	" middle part containing replacementCollection : "
+ 	
+ 	(indexOfSubcollection ) to: ( lastIndexOfReplacementCollection  ) do: 
+ 		[
+ 		:i |
+ 		self assert: (result at: i)=(self replacementCollection at: (i - indexOfSubcollection +1))
+ 		].
+ 	
+ 	" end part :"
+ 	1 to: (result size - lastIndexOfReplacementCollection   ) do:
+ 		[ 
+ 		:i |
+ 		self assert: (result at: ( lastIndexOfReplacementCollection  + i  ) ) = (self collectionWith1TimeSubcollection  at: ( lastIndexOfOldSubcollection  + i  ) ).
+ 		].
+ 	
+ 	
+ 	
+ 
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testCopyReplaceFromToWithInsertion (in category 'tests - copying with replacement') -----
+ testCopyReplaceFromToWithInsertion
+ 	| result  indexOfSubcollection |
+ 	
+ 	indexOfSubcollection := (self firstIndexesOf: self oldSubCollection  in:  self collectionWith1TimeSubcollection) at: 1. 
+ 	
+ 	result := self collectionWith1TimeSubcollection  copyReplaceFrom: indexOfSubcollection  to: ( indexOfSubcollection - 1 ) with: self replacementCollection .
+ 	
+ 	"verify content of 'result' : "
+ 	"first part of 'result'' : '"
+ 	
+ 	1 to: (indexOfSubcollection -1) do: 
+ 		[
+ 		:i | 
+ 		self assert: (self collectionWith1TimeSubcollection  at:i)=(result at: i)
+ 		].
+ 	
+ 	" middle part containing replacementCollection : "
+ 	indexOfSubcollection  to: (indexOfSubcollection  + self replacementCollection size-1) do: 
+ 		[
+ 		:i |
+ 		self assert: ( result at: i )=(self replacementCollection at: ( i - indexOfSubcollection +1 ))
+ 		].
+ 	
+ 	" end part :"
+ 	(indexOfSubcollection  + self replacementCollection size) to: (result size) do:
+ 		[:i|
+ 		self assert: (result at: i)=(self collectionWith1TimeSubcollection  at: (i-self replacementCollection size))].
+ 	
+ 	" verify size: "	
+ 	self assert: result size=(self collectionWith1TimeSubcollection  size + self replacementCollection size).
+ 	
+ 
+ 	
+ 
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testCopySameClass (in category 'tests - copy') -----
+ testCopySameClass
+ 	"self debug: #testCopySameClass"
+ 	"A copy of a collection should always be of the same class as the instance it copies"
+ 	
+ 	| copy | 
+ 	copy := self empty copy.
+ 	self assert: copy class == self empty class.!

Item was added:
+ ----- Method: LinkedListTest>>testCopyUpTo (in category 'tests - copying part of sequenceable') -----
+ testCopyUpTo
+ 	| result index collection |
+ 	collection := self collectionWithoutEqualElements .
+ 	index:= self indexInForCollectionWithoutDuplicates .
+ 	result := collection   copyUpTo: (collection  at:index).
+ 	
+ 	"verify content of 'result' :"
+ 	1 to: result size do: [:i| self assert: (collection   at:i)=(result at:i)].
+ 	
+ 	"verify size of 'result' :"
+ 	self assert: result size = (index-1).
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testCopyUpToEmpty (in category 'tests - copying part of sequenceable') -----
+ testCopyUpToEmpty
+ 	| result |
+ 	result := self empty copyUpTo: self collectionWithoutEqualElements first.
+ 	self assert: result isEmpty.
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testCopyUpToLast (in category 'tests - copying part of sequenceable') -----
+ testCopyUpToLast
+ 	| result index collection |
+ 	collection := self collectionWithoutEqualElements .
+ 	index:= self indexInForCollectionWithoutDuplicates .
+ 	result := collection   copyUpToLast: (collection  at:index).
+ 	
+ 	"verify content of 'result' :"
+ 	1 to: result size do: [:i| self assert: (collection   at:i)=(result at:i)].
+ 	
+ 	"verify size of 'result' :"
+ 	self assert: result size = (index-1).!

Item was added:
+ ----- Method: LinkedListTest>>testCopyUpToLastEmpty (in category 'tests - copying part of sequenceable') -----
+ testCopyUpToLastEmpty
+ 	| result |
+ 	result := self empty copyUpToLast: self collectionWithoutEqualElements first.
+ 	self assert: result isEmpty.!

Item was added:
+ ----- Method: LinkedListTest>>testCopyWithFirst (in category 'tests - copying with or without') -----
+ testCopyWithFirst
+ 
+ 	| index element result |
+ 	index:= self indexInNonEmpty .
+ 	element:= self nonEmpty at: index.
+ 	
+ 	result := self nonEmpty copyWithFirst: element.	
+ 	
+ 	self assert: result size = (self nonEmpty size + 1).
+ 	self assert: result first = element .
+ 	
+ 	2 to: result size do:
+ 	[ :i |
+ 	self assert: (result at: i) = ( self nonEmpty at: ( i - 1 ))].!

Item was added:
+ ----- Method: LinkedListTest>>testCopyWithSequenceable (in category 'tests - copying with or without') -----
+ testCopyWithSequenceable
+ 
+ 	| result index element |
+ 	index := self indexInNonEmpty .
+ 	element := self nonEmpty at: index.
+ 	result := self nonEmpty copyWith: (element ).
+ 	
+ 	self assert: result size = (self nonEmpty size + 1).
+ 	self assert: result last = element .
+ 	
+ 	1 to: (result size - 1) do:
+ 	[ :i |
+ 	self assert: (result at: i) = ( self nonEmpty at: ( i  ))].!

Item was added:
+ ----- Method: LinkedListTest>>testCopyWithoutFirst (in category 'tests - copying with or without') -----
+ testCopyWithoutFirst
+ 
+ 	| result |
+ 	result := self nonEmpty copyWithoutFirst.
+ 	
+ 	self assert: result size = (self nonEmpty size - 1).
+ 	
+ 	1 to: result size do:
+ 		[:i |
+ 		self assert: (result at: i)= (self nonEmpty at: (i + 1))].!

Item was added:
+ ----- Method: LinkedListTest>>testCopyWithoutIndex (in category 'tests - copying with or without') -----
+ testCopyWithoutIndex
+ 	| result index |
+ 	index := self indexInNonEmpty .
+ 	result := self nonEmpty copyWithoutIndex: index .
+ 	
+ 	"verify content of 'result:'"
+ 	1 to: result size do:
+ 		[:i | 
+ 		i<( index ) ifTrue: [self assert: ((result at:i )= (self nonEmpty at:i))].
+ 		i>=( index ) ifTrue: [self assert: (result at:i )= (self nonEmpty at:(i+1))]].
+ 	
+ 	"verify size of result : "
+ 	self assert: result size=(self nonEmpty size -1).!

Item was added:
+ ----- Method: LinkedListTest>>testCreateAs (in category 'tests - creating') -----
+ testCreateAs
+ 	"Test that a LinkedList can be created by sending message #as: to another collection.
+ 	Implementation note: this method is generic for sequenceable collection and should be traitified."
+ 	| anotherCollection aLinkedList |
+ 	anotherCollection := 1 to: 10.
+ 	aLinkedList := anotherCollection as: LinkedList.
+ 	self assert: (aLinkedList isMemberOf: LinkedList).
+ 	self assert: aLinkedList size equals: anotherCollection size.
+ 	aLinkedList with: anotherCollection do: [:nextElementOfLinkedList :nextElementOfAnotherCollection |
+ 		self assert: nextElementOfLinkedList equals: nextElementOfAnotherCollection]!

Item was added:
+ ----- Method: LinkedListTest>>testDetect (in category 'tests - iterating') -----
+ testDetect
+ 
+ 	| res element |
+ 	element := self collectionWithoutNilElements anyOne .
+ 	 
+ 	res := self collectionWithoutNilElements  detect: [:each | each = element].
+ 	self assert: (res  = element).
+ 
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testDetectIfNone (in category 'tests - iterating') -----
+ testDetectIfNone
+ 
+ 	| res element |
+ 	res := self collectionWithoutNilElements  detect: [:each | each notNil not] ifNone: [100].
+ 	self assert: res  = 100.
+ 	
+ 	element := self collectionWithoutNilElements anyOne.
+ 	res := self collectionWithoutNilElements  detect: [:each | each = element] ifNone: [100].
+ 	self assert: res  = element.
+ 
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testDetectSequenced (in category 'tests - iterate on sequenced reable collections') -----
+ testDetectSequenced
+ " testing that detect keep the first element returning true for sequenceable collections "
+ 
+ 	| element result |
+ 	element := self nonEmptyMoreThan1Element   at:1.
+ 	result:=self nonEmptyMoreThan1Element  detect: [:each | each notNil ].
+ 	self assert: result = element. !

Item was added:
+ ----- Method: LinkedListTest>>testDifference (in category 'tests - set arithmetic') -----
+ testDifference
+ 	"Answer the set theoretic difference of two collections."
+ 	"self debug: #testDifference"
+ 	
+ 	| difference |
+ 	self assert: (self collectionWithoutEqualElements difference: self collectionWithoutEqualElements) isEmpty.
+ 	self assert: (self empty difference: self collectionWithoutEqualElements) isEmpty.
+ 	difference := (self collectionWithoutEqualElements difference: self empty).
+ 	self assert: difference size = self collectionWithoutEqualElements	 size.
+ 	self collectionWithoutEqualElements do: [ :each |
+ 		self assert: (difference includes: each)].
+ !

Item was added:
+ ----- Method: LinkedListTest>>testDifferenceWithNonNullIntersection (in category 'tests - set arithmetic') -----
+ testDifferenceWithNonNullIntersection
+ 	"Answer the set theoretic difference of two collections."
+ 	"self debug: #testDifferenceWithNonNullIntersection"
+ 	"	#(1 2 3) difference: #(2 4) 
+ 	->  #(1 3)"
+ 	| res overlapping |
+ 	overlapping := self collectionClass 
+ 		with: self anotherElementOrAssociationNotIn
+ 		with: self anotherElementOrAssociationIn.
+ 	res := self collection difference: overlapping.
+ 	self deny: (res includes: self anotherElementOrAssociationIn).
+ 	overlapping do: [ :each | self deny: (res includes: each) ]!

Item was added:
+ ----- Method: LinkedListTest>>testDifferenceWithSeparateCollection (in category 'tests - set arithmetic') -----
+ testDifferenceWithSeparateCollection
+ 	"Answer the set theoretic difference of two collections."
+ 	"self debug: #testDifferenceWithSeparateCollection"
+ 	| res separateCol |
+ 	
+ 	separateCol := self collectionClass with: self anotherElementOrAssociationNotIn.
+ 	res := self collectionWithoutEqualElements difference: separateCol.
+ 	
+ 	self deny: (res includes: self anotherElementOrAssociationNotIn).
+ 	self assert: res size equals: self collectionWithoutEqualElements size.
+ 	
+ 	self collectionWithoutEqualElements do: [ :each|
+ 		self assert: (res includes: each)].
+ 	
+ 	res := separateCol difference: self collection.
+ 	self deny: (res includes: self collection anyOne).
+ 	self assert: res equals: separateCol!

Item was added:
+ ----- Method: LinkedListTest>>testDo (in category 'tests - iterate on sequenced reable collections') -----
+ testDo!

Item was added:
+ ----- Method: LinkedListTest>>testDo2 (in category 'tests - iterating') -----
+ testDo2
+ 	"dc: Bad test, it assumes that a new instance of #speciesClass allows addition with #add:. This is not the case of Interval for which species is Array."
+ 	"res := self speciesClass new.  
+ 	self collection do: [:each | res add: each class].
+ 	self assert: res = self result. "
+ 	| collection cptElementsViewed cptElementsIn |
+ 	collection := self collectionWithoutNilElements.
+ 	cptElementsViewed := 0.
+ 	cptElementsIn := OrderedCollection new.
+ 	collection do: 
+ 		[ :each | 
+ 		cptElementsViewed := cptElementsViewed + 1.
+ 		" #do doesn't iterate with the same objects than those in the collection for FloatArray( I don' t know why ) . That's why I use #includes: and not #identityIncludes:  '"
+ 		(collection includes: each) ifTrue: [
+ 			" the collection used doesn't include equal elements. Therefore each element viewed should not have been viewed before "
+ 			( cptElementsIn includes: each ) ifFalse: [ cptElementsIn add: each ] .
+ 			]. 
+ 		].
+ 	self assert: cptElementsViewed = collection size.
+ 	self assert: cptElementsIn size  = collection size.
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testDoSeparatedBy (in category 'tests - iterating') -----
+ testDoSeparatedBy
+ 	| string expectedString beforeFirst |
+ 	
+ 	string := ''.
+ 	self collectionWithoutNilElements  
+ 		do: [ :each | string := string , each asString ]
+ 		separatedBy: [ string := string , '|' ].
+ 		
+ 	expectedString := ''.
+ 	beforeFirst := true.
+ 	self collectionWithoutNilElements  do: 
+ 		[ :each | 
+ 		beforeFirst = true 
+ 			ifTrue: [ beforeFirst := false ]
+ 			ifFalse: [ expectedString := expectedString , '|' ].
+ 		expectedString := expectedString , each asString ].
+ 	self assert: expectedString = string!

Item was added:
+ ----- Method: LinkedListTest>>testDoWithout (in category 'tests - iterating') -----
+ testDoWithout
+ 	"self debug: #testDoWithout"
+ 	
+ 	| res element collection |
+ 	collection := self collectionWithoutNilElements .	
+ 	res := OrderedCollection new.  
+ 	element := self collectionWithoutNilElements anyOne .
+ 	collection  do: [:each | res add: each] without: element  .
+ 	" verifying result :"
+ 	self assert: res size = (collection  size - (collection  occurrencesOf: element)).
+ 	res do: [:each | self assert: (collection occurrencesOf: each) = ( res occurrencesOf: each ) ].
+ 	!

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

Item was added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- Method: LinkedListTest>>testFindFirst (in category 'tests - iterate on sequenced reable collections') -----
+ testFindFirst
+ 
+ 	| element result |
+ 	element := self nonEmptyMoreThan1Element   at:1.
+ 	 result:=self nonEmptyMoreThan1Element  findFirst: [:each | each =element].
+ 	
+ 	self assert: result=1. !

Item was added:
+ ----- Method: LinkedListTest>>testFindFirstNotIn (in category 'tests - iterate on sequenced reable collections') -----
+ testFindFirstNotIn
+ 
+ 	| result |
+ 	
+ 	 result:=self empty findFirst: [:each | true].
+ 	
+ 	self assert: result=0. !

Item was added:
+ ----- Method: LinkedListTest>>testFindLast (in category 'tests - iterate on sequenced reable collections') -----
+ testFindLast
+ 
+ 	| element result |
+ 	element := self nonEmptyMoreThan1Element  at:self nonEmptyMoreThan1Element  size.
+ 	 result:=self nonEmptyMoreThan1Element  findLast: [:each | each =element].
+ 	
+ 	self assert: result=self nonEmptyMoreThan1Element  size. !

Item was added:
+ ----- Method: LinkedListTest>>testFindLastNotIn (in category 'tests - iterate on sequenced reable collections') -----
+ testFindLastNotIn
+ 
+ 	| result |
+ 	
+ 	 result:=self empty findFirst: [:each | true].
+ 	
+ 	self assert: result=0. !

Item was added:
+ ----- Method: LinkedListTest>>testFirstNElements (in category 'tests - subcollections access') -----
+ testFirstNElements
+ 	"self debug: #testFirstNElements"
+ 	| result |
+ 	result := self moreThan3Elements first: self moreThan3Elements size - 1.
+ 	1 
+ 		to: result size
+ 		do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i) ].
+ 	self assert: result size = (self moreThan3Elements size - 1).
+ 	self 
+ 		should: [ self moreThan3Elements first: self moreThan3Elements size + 1 ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testFirstSecondThird (in category 'tests - element accessing') -----
+ testFirstSecondThird
+ 	"self debug: #testFirstSecondThird"
+ 	self assert: self moreThan4Elements first = (self moreThan4Elements at: 1).
+ 	self assert: self moreThan4Elements second = (self moreThan4Elements at: 2).
+ 	self assert: self moreThan4Elements third = (self moreThan4Elements at: 3).
+ 	self assert: self moreThan4Elements fourth = (self moreThan4Elements at: 4)!

Item was added:
+ ----- Method: LinkedListTest>>testForceToPaddingStartWith (in category 'tests - copying with or without') -----
+ testForceToPaddingStartWith
+ 
+ 	| result element |
+ 	element := self nonEmpty at: self indexInNonEmpty .
+ 	result := self nonEmpty forceTo: (self nonEmpty size+2) paddingStartWith: ( element ).
+ 	
+ 	"verify content of 'result' : "
+ 	1 to: 2   do:
+ 		[:i | self assert: ( element ) = ( result at:(i) ) ].
+ 	
+ 	3 to: result size do:
+ 		[:i | self assert: ( result at:i ) = ( self nonEmpty at:(i-2) ) ].
+ 
+ 	"verify size of 'result' :"
+ 	self assert: result size = (self nonEmpty size + 2).!

Item was added:
+ ----- Method: LinkedListTest>>testForceToPaddingWith (in category 'tests - copying with or without') -----
+ testForceToPaddingWith
+ 
+ 	| result element |
+ 	element := self nonEmpty at: self indexInNonEmpty .
+ 	result := self nonEmpty forceTo: (self nonEmpty size+2) paddingWith: ( element ).
+ 	
+ 	"verify content of 'result' : "
+ 	1 to: self nonEmpty  size do:
+ 		[:i | self assert: ( self nonEmpty at: i ) = ( result at:(i) ). ].
+ 	
+ 	(result size - 1) to: result size do:
+ 		[:i | self assert: ( result at:i ) = ( element ) ].
+ 
+ 	"verify size of 'result' :"
+ 	self assert: result size = (self nonEmpty size + 2).!

Item was added:
+ ----- Method: LinkedListTest>>testFromToDo (in category 'tests - iterate on sequenced reable collections') -----
+ testFromToDo
+ 	
+ 	| result |
+ 	result:= OrderedCollection  new.
+ 	
+ 	self nonEmptyMoreThan1Element  from: 1 to: (self nonEmptyMoreThan1Element  size -1) do: [:each | result add: each].
+ 	
+ 	1 to: (self nonEmptyMoreThan1Element  size -1) do:
+ 		[:i|
+ 		self assert: (self nonEmptyMoreThan1Element  at:i )=(result at:i)].
+ 	self assert: result size=(self nonEmptyMoreThan1Element  size-1).!

Item was added:
+ ----- Method: LinkedListTest>>testIdentityIncludes (in category 'tests - includes') -----
+ testIdentityIncludes
+ 	" test the comportement in presence of elements 'includes' but not 'identityIncludes' "
+ 
+ 	" can not be used by collections that can't include elements for wich copy doesn't return another instance "
+ 
+ 	| collection element |
+ 	self collectionWithCopyNonIdentical.
+ 	collection := self collectionWithCopyNonIdentical.
+ 	element := collection anyOne copy.	"self assert: (collection includes: element)."
+ 	self deny: (collection identityIncludes: element)!

Item was added:
+ ----- Method: LinkedListTest>>testIdentityIncludesNonSpecificComportement (in category 'tests - includes') -----
+ testIdentityIncludesNonSpecificComportement
+ 	" test the same comportement than 'includes: '  "
+ 	| collection |	
+ 	collection := self nonEmpty  .
+ 	
+ 	self deny: (collection identityIncludes: self elementNotIn ).
+ 	self assert:(collection identityIncludes: collection anyOne)
+ !

Item was added:
+ ----- Method: LinkedListTest>>testIdentityIndexOf (in category 'tests - index access') -----
+ testIdentityIndexOf
+ 	"self debug: #testIdentityIndexOf"
+ 	| collection element |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	element := collection first.
+ 	self assert: (collection identityIndexOf: element) = (collection indexOf: element)!

Item was added:
+ ----- Method: LinkedListTest>>testIdentityIndexOfIAbsent (in category 'tests - index access') -----
+ testIdentityIndexOfIAbsent
+ 	| collection element |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	element := collection first.
+ 	self assert: (collection 
+ 			identityIndexOf: element
+ 			ifAbsent: [ 0 ]) = 1.
+ 	self assert: (collection 
+ 			identityIndexOf: self elementNotInForIndexAccessing
+ 			ifAbsent: [ 55 ]) = 55!

Item was added:
+ ----- Method: LinkedListTest>>testIfEmpty (in category 'tests - empty') -----
+ testIfEmpty
+ 
+ 	self nonEmpty ifEmpty: [ self assert: false] .
+ 	self empty ifEmpty: [ self assert: true] .
+ 	
+ 
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testIfEmptyifNotEmpty (in category 'tests - empty') -----
+ testIfEmptyifNotEmpty
+ 
+ 	self assert: (self empty ifEmpty: [true] ifNotEmpty: [false]).
+ 	self assert: (self nonEmpty ifEmpty: [false] ifNotEmpty: [true]).
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testIfNotEmpty (in category 'tests - empty') -----
+ testIfNotEmpty
+ 
+ 	self empty ifNotEmpty: [self assert: false].
+ 	self nonEmpty ifNotEmpty: [self assert: true].
+ 	self assert: (self nonEmpty ifNotEmpty: [:s | s ]) = self nonEmpty
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testIfNotEmptyifEmpty (in category 'tests - empty') -----
+ testIfNotEmptyifEmpty
+ 
+ 	self assert: (self empty ifNotEmpty: [false] ifEmpty: [true]).
+ 	self assert: (self nonEmpty ifNotEmpty: [true] ifEmpty: [false]).
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testIncludesAllNoneThere (in category 'tests - includes') -----
+ testIncludesAllNoneThere
+ 	"self debug: #testIncludesAllOfNoneThere'"
+ 	self deny: (self empty includesAllOf: self nonEmpty ).
+ 	self deny: (self nonEmpty includesAllOf: { self elementNotIn. self anotherElementNotIn })!

Item was added:
+ ----- Method: LinkedListTest>>testIncludesAnyAllThere (in category 'tests - includes') -----
+ testIncludesAnyAllThere
+ 	"self debug: #testIncludesAnyOfAllThere'"
+ 	self deny: (self nonEmpty includesAnyOf: self empty).
+ 	self assert: (self nonEmpty includesAnyOf: { self nonEmpty anyOne }).
+ 	self assert: (self nonEmpty includesAnyOf: self nonEmpty).!

Item was added:
+ ----- Method: LinkedListTest>>testIncludesAnyNoneThere (in category 'tests - includes') -----
+ testIncludesAnyNoneThere
+ 	"self debug: #testIncludesAnyOfNoneThere'"
+ 	
+ 	self deny: (self nonEmpty includesAnyOf: self empty).
+ 	self deny: (self nonEmpty includesAnyOf: { self elementNotIn. self anotherElementNotIn })!

Item was added:
+ ----- Method: LinkedListTest>>testIncludesElementIsNotThere (in category 'tests - includes') -----
+ testIncludesElementIsNotThere
+ 	"self debug: #testIncludesElementIsNotThere"
+ 	
+ 	self deny: (self nonEmpty includes: self elementNotIn).
+ 	self assert: (self nonEmpty includes: self nonEmpty anyOne).
+ 	self deny: (self empty includes: self elementNotIn)!

Item was added:
+ ----- Method: LinkedListTest>>testIncludesElementIsThere (in category 'tests - includes') -----
+ testIncludesElementIsThere
+ 	"self debug: #testIncludesElementIsThere"
+ 	
+ 	self assert: (self nonEmpty includes: self nonEmpty anyOne).!

Item was added:
+ ----- Method: LinkedListTest>>testIndexOf (in category 'tests - index access') -----
+ testIndexOf
+ 	"self debug: #testIndexOf"
+ 	| tmp index collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	tmp := collection size.
+ 	collection reverseDo: 
+ 		[ :each | 
+ 		each = self elementInForIndexAccessing ifTrue: [ index := tmp ].
+ 		tmp := tmp - 1 ].
+ 	self assert: (collection indexOf: self elementInForIndexAccessing) = index!

Item was added:
+ ----- Method: LinkedListTest>>testIndexOfIfAbsent (in category 'tests - index access') -----
+ testIndexOfIfAbsent
+ 	"self debug: #testIndexOfIfAbsent"
+ 	| collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	self assert: (collection 
+ 			indexOf: collection first
+ 			ifAbsent: [ 33 ]) = 1.
+ 	self assert: (collection 
+ 			indexOf: self elementNotInForIndexAccessing
+ 			ifAbsent: [ 33 ]) = 33!

Item was added:
+ ----- Method: LinkedListTest>>testIndexOfStartingAt (in category 'tests - index access') -----
+ testIndexOfStartingAt
+ 	"self debug: #testLastIndexOf"
+ 	| element collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	element := collection first.
+ 	self assert: (collection 
+ 			indexOf: element
+ 			startingAt: 2
+ 			ifAbsent: [ 99 ]) = 99.
+ 	self assert: (collection 
+ 			indexOf: element
+ 			startingAt: 1
+ 			ifAbsent: [ 99 ]) = 1.
+ 	self assert: (collection 
+ 			indexOf: self elementNotInForIndexAccessing
+ 			startingAt: 1
+ 			ifAbsent: [ 99 ]) = 99!

Item was added:
+ ----- Method: LinkedListTest>>testIndexOfStartingAtIfAbsent (in category 'tests - index access') -----
+ testIndexOfStartingAtIfAbsent
+ 	"self debug: #testLastIndexOf"
+ 	| element collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	element := collection first.
+ 	self assert: (collection 
+ 			indexOf: element
+ 			startingAt: 2
+ 			ifAbsent: [ 99 ]) = 99.
+ 	self assert: (collection 
+ 			indexOf: element
+ 			startingAt: 1
+ 			ifAbsent: [ 99 ]) = 1.
+ 	self assert: (collection 
+ 			indexOf: self elementNotInForIndexAccessing
+ 			startingAt: 1
+ 			ifAbsent: [ 99 ]) = 99!

Item was added:
+ ----- Method: LinkedListTest>>testIndexOfSubCollectionStartingAt (in category 'tests - index access') -----
+ testIndexOfSubCollectionStartingAt
+ 	"self debug: #testIndexOfIfAbsent"
+ 	| subcollection index collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	subcollection := self collectionMoreThan1NoDuplicates.
+ 	index := collection 
+ 		indexOfSubCollection: subcollection
+ 		startingAt: 1.
+ 	self assert: index = 1.
+ 	index := collection 
+ 		indexOfSubCollection: subcollection
+ 		startingAt: 2.
+ 	self assert: index = 0!

Item was added:
+ ----- Method: LinkedListTest>>testIndexOfSubCollectionStartingAtIfAbsent (in category 'tests - index access') -----
+ testIndexOfSubCollectionStartingAtIfAbsent
+ 	"self debug: #testIndexOfIfAbsent"
+ 	| index absent subcollection collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	subcollection := self collectionMoreThan1NoDuplicates.
+ 	absent := false.
+ 	index := collection 
+ 		indexOfSubCollection: subcollection
+ 		startingAt: 1
+ 		ifAbsent: [ absent := true ].
+ 	self assert: absent = false.
+ 	absent := false.
+ 	index := collection 
+ 		indexOfSubCollection: subcollection
+ 		startingAt: 2
+ 		ifAbsent: [ absent := true ].
+ 	self assert: absent = true!

Item was added:
+ ----- Method: LinkedListTest>>testInjectInto (in category 'tests - iterating') -----
+ testInjectInto
+ 	|result|
+ 	result:= self collectionWithoutNilElements 
+ 		inject: 0
+ 		into: [:inj :ele | ele notNil ifTrue: [ inj + 1 ]].
+ 	
+ 	self assert: self collectionWithoutNilElements size = result .!

Item was added:
+ ----- Method: LinkedListTest>>testIntersectionBasic (in category 'tests - set arithmetic') -----
+ testIntersectionBasic
+ 	"self debug: #testIntersectionBasic"
+ 	| inter |
+ 	inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn).
+ 	self deny: inter isEmpty.
+ 	self assert: (inter includes: self anotherElementOrAssociationIn value)!

Item was added:
+ ----- Method: LinkedListTest>>testIntersectionEmpty (in category 'tests - set arithmetic') -----
+ testIntersectionEmpty
+ 	"self debug: #testIntersectionEmpty"
+ 	
+ 	| inter |
+ 	inter := self empty intersection: self empty.
+ 	self assert: inter isEmpty. 
+ 	inter := self empty intersection: self collection .
+ 	self assert: inter =  self empty.
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testIntersectionItself (in category 'tests - set arithmetic') -----
+ testIntersectionItself
+ 	"self debug: #testIntersectionItself"
+ 	
+ 	| result |
+ 	result :=  (self collectionWithoutEqualElements intersection: self collectionWithoutEqualElements).
+ 	self assert: result size  = self collectionWithoutEqualElements size.
+ 	self collectionWithoutEqualElements do: [ :each|
+ 		self assert: (result includes: each) ].
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testIntersectionTwoSimilarElementsInIntersection (in category 'tests - set arithmetic') -----
+ testIntersectionTwoSimilarElementsInIntersection
+ 	"self debug: #testIntersectionBasic"
+ 	| inter |
+ 	inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn).
+ 	self assert: (self collection occurrencesOf: self anotherElementOrAssociationIn) = self numberOfSimilarElementsInIntersection.
+ 	self assert: (inter includes: self anotherElementOrAssociationIn value)!

Item was added:
+ ----- Method: LinkedListTest>>testIsEmpty (in category 'tests - empty') -----
+ testIsEmpty
+ 
+ 	self assert: (self empty isEmpty).
+ 	self deny: (self nonEmpty isEmpty).!

Item was added:
+ ----- Method: LinkedListTest>>testIsEmptyOrNil (in category 'tests - empty') -----
+ testIsEmptyOrNil
+ 
+ 	self assert: (self empty isEmptyOrNil).
+ 	self deny: (self nonEmpty isEmptyOrNil).!

Item was added:
+ ----- Method: LinkedListTest>>testKeysAndValuesDo (in category 'tests - iterate on sequenced reable collections') -----
+ testKeysAndValuesDo
+ 	"| result |
+ 	result:= OrderedCollection new.
+ 	
+ 	self nonEmptyMoreThan1Element  keysAndValuesDo: 
+ 		[:i :value|
+ 		result add: (value+i)].
+ 	
+ 	1 to: result size do:
+ 		[:i|
+ 		self assert: (result at:i)=((self nonEmptyMoreThan1Element at:i)+i)]"
+ 	|  indexes elements |
+ 	indexes:= OrderedCollection new.
+ 	elements := OrderedCollection new.
+ 	
+ 	self nonEmptyMoreThan1Element  keysAndValuesDo: 
+ 		[:i :value|
+ 		indexes  add: (i).
+ 		elements add: value].
+ 	
+ 	(1 to: self nonEmptyMoreThan1Element size )do:
+ 		[ :i |
+ 		self assert: (indexes at: i) = i.
+ 		self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i).	
+ 		].
+ 	
+ 	self assert: indexes size = elements size. 
+ 	self assert: indexes size = self nonEmptyMoreThan1Element size . 
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testKeysAndValuesDoEmpty (in category 'tests - iterate on sequenced reable collections') -----
+ testKeysAndValuesDoEmpty
+ 	| result |
+ 	result:= OrderedCollection new.
+ 	
+ 	self empty  keysAndValuesDo: 
+ 		[:i :value|
+ 		result add: (value+i)].
+ 	
+ 	self assert: result isEmpty .!

Item was added:
+ ----- Method: LinkedListTest>>testLast (in category 'tests - element accessing') -----
+ testLast
+ 	"self debug: #testLast"
+ 	self assert: self moreThan4Elements last = (self moreThan4Elements at: self moreThan4Elements size)!

Item was added:
+ ----- Method: LinkedListTest>>testLastIndexOf (in category 'tests - index access') -----
+ testLastIndexOf
+ 	"self debug: #testLastIndexOf"
+ 	| element collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	element := collection first.
+ 	self assert: (collection lastIndexOf: element) = 1.
+ 	self assert: (collection lastIndexOf: self elementNotInForIndexAccessing) = 0!

Item was added:
+ ----- Method: LinkedListTest>>testLastIndexOfIfAbsent (in category 'tests - index access') -----
+ testLastIndexOfIfAbsent
+ 	"self debug: #testIndexOfIfAbsent"
+ 	| element collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	element := collection first.
+ 	self assert: (collection 
+ 			lastIndexOf: element
+ 			ifAbsent: [ 99 ]) = 1.
+ 	self assert: (collection 
+ 			lastIndexOf: self elementNotInForIndexAccessing
+ 			ifAbsent: [ 99 ]) = 99!

Item was added:
+ ----- Method: LinkedListTest>>testLastIndexOfStartingAt (in category 'tests - index access') -----
+ testLastIndexOfStartingAt
+ 	"self debug: #testLastIndexOf"
+ 	| element collection |
+ 	collection := self collectionMoreThan1NoDuplicates.
+ 	element := collection last.
+ 	self assert: (collection 
+ 			lastIndexOf: element
+ 			startingAt: collection size
+ 			ifAbsent: [ 99 ]) = collection size.
+ 	self assert: (collection 
+ 			lastIndexOf: element
+ 			startingAt: collection size - 1
+ 			ifAbsent: [ 99 ]) = 99.
+ 	self assert: (collection 
+ 			lastIndexOf: self elementNotInForIndexAccessing
+ 			startingAt: collection size
+ 			ifAbsent: [ 99 ]) = 99!

Item was added:
+ ----- Method: LinkedListTest>>testLastNElements (in category 'tests - subcollections access') -----
+ testLastNElements
+ 	"self debug: #testLastNElements"
+ 	| result |
+ 	result := self moreThan3Elements last: self moreThan3Elements size - 1.
+ 	1 
+ 		to: result size
+ 		do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i + 1) ].
+ 	self assert: result size = (self moreThan3Elements size - 1).
+ 	self 
+ 		should: [ self moreThan3Elements last: self moreThan3Elements size + 1 ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testMiddle (in category 'tests - element accessing') -----
+ testMiddle
+ 	"self debug: #testMiddle"
+ 	self assert: self moreThan4Elements middle = (self moreThan4Elements at: self moreThan4Elements size // 2 + 1)!

Item was added:
+ ----- Method: LinkedListTest>>testNoneSatisfy (in category 'tests - iterating') -----
+ testNoneSatisfy
+ 
+ 	| element |
+ 	self assert: ( self collectionWithoutNilElements  noneSatisfy: [:each | each notNil not ] ).
+ 	element := self collectionWithoutNilElements anyOne.
+ 	self deny: ( self collectionWithoutNilElements  noneSatisfy: [:each | (each = element)not ] ).!

Item was added:
+ ----- Method: LinkedListTest>>testNoneSatisfyEmpty (in category 'tests - iterating') -----
+ testNoneSatisfyEmpty
+ 
+ 	self assert: ( self empty noneSatisfy: [:each | false]).
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testNotEmpty (in category 'tests - empty') -----
+ testNotEmpty
+ 
+ 	self assert: (self nonEmpty  notEmpty).
+ 	self deny: (self empty notEmpty).!

Item was added:
+ ----- Method: LinkedListTest>>testOccurrencesOf (in category 'tests - occurrencesOf') -----
+ testOccurrencesOf
+ 	| collection |
+ 	collection := self collectionWithoutEqualElements .
+ 	
+ 	collection do: [ :each | self assert: (collection occurrencesOf: each) = 1 ].!

Item was added:
+ ----- Method: LinkedListTest>>testOccurrencesOfEmpty (in category 'tests - occurrencesOf') -----
+ testOccurrencesOfEmpty
+ 	| result |
+ 	result := self empty occurrencesOf: (self collectionWithoutEqualElements anyOne).
+ 	self assert: result = 0!

Item was added:
+ ----- Method: LinkedListTest>>testOccurrencesOfNotIn (in category 'tests - occurrencesOf') -----
+ testOccurrencesOfNotIn
+ 	| result |
+ 	result := self collectionWithoutEqualElements occurrencesOf: self elementNotInForOccurrences.
+ 	self assert: result = 0!

Item was added:
+ ----- Method: LinkedListTest>>testPairsCollect (in category 'tests - iterate on sequenced reable collections') -----
+ testPairsCollect
+ 	
+ 	| index result |
+ 	index:=0.
+ 	
+ 	result:=self nonEmptyMoreThan1Element  pairsCollect: 
+ 		[:each1 :each2 | 
+ 		self assert: ( self nonEmptyMoreThan1Element indexOf: each2 ) = (index := index + 2).
+ 		(self nonEmptyMoreThan1Element indexOf: each2) = ((self nonEmptyMoreThan1Element indexOf: each1) + 1).
+ 		].
+ 	
+ 	result do: 
+ 		[:each | self assert: each = true].
+ 	
+ !

Item was added:
+ ----- Method: LinkedListTest>>testPairsDo (in category 'tests - iterate on sequenced reable collections') -----
+ testPairsDo
+ 	| index |
+ 	index:=1.
+ 	
+ 	self nonEmptyMoreThan1Element  pairsDo: 
+ 		[:each1 :each2 | 
+ 		self assert:(self nonEmptyMoreThan1Element at:index)=each1.
+ 		self assert:(self nonEmptyMoreThan1Element at:(index+1))=each2.
+ 		index:=index+2].
+ 	
+ 	self nonEmptyMoreThan1Element size odd
+ 		ifTrue:[self assert: index=self nonEmptyMoreThan1Element size]
+ 		ifFalse:[self assert: index=(self nonEmptyMoreThan1Element size+1)].!

Item was added:
+ ----- Method: LinkedListTest>>testPrintElementsOn (in category 'tests - printing') -----
+ testPrintElementsOn
+ 
+ 	| aStream result allElementsAsString tmp |
+ 	result:=''.
+ 	aStream:= ReadWriteStream on: result.
+ 	tmp:= OrderedCollection new.
+ 	self nonEmpty do: [:each | tmp add: each asString].
+ 	
+ 	self nonEmpty printElementsOn: aStream .
+ 	allElementsAsString:=(result findBetweenSubStrs: ' ' ).
+ 	1 to: allElementsAsString size do:
+ 		[:i | 
+ 		self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString  occurrencesOf:(allElementsAsString at:i)).
+ 			].!

Item was added:
+ ----- Method: LinkedListTest>>testPrintNameOn (in category 'tests - printing') -----
+ testPrintNameOn
+ 
+ 	| aStream result |
+ 	result:=''.
+ 	aStream:= ReadWriteStream on: result.
+ 	self nonEmpty printNameOn: aStream.
+ 	self nonEmpty class name first isVowel
+ 		ifTrue:[ self assert: aStream contents =('an ',self nonEmpty class name ) ]
+ 		ifFalse:[self assert: aStream contents =('a ',self nonEmpty class name)].!

Item was added:
+ ----- Method: LinkedListTest>>testPrintOn (in category 'tests - printing') -----
+ testPrintOn
+ 	| aStream result allElementsAsString tmp |
+ 	result:=''.
+ 	aStream:= ReadWriteStream on: result.
+ 	tmp:= OrderedCollection new.
+ 	self nonEmpty do: [:each | tmp add: each asString].
+ 	
+ 	self nonEmpty printOn: aStream .
+ 	allElementsAsString:=(result findBetweenSubStrs: ' ' ).
+ 	1 to: allElementsAsString size do:
+ 		[:i | 
+ 		i=1
+ 			ifTrue:[
+ 			self accessCollection class name first isVowel 
+ 				ifTrue:[self assert: (allElementsAsString at:i)='an' ]
+ 				ifFalse:[self assert: (allElementsAsString at:i)='a'].].
+ 		i=2
+ 			ifTrue:[self assert: (allElementsAsString at:i)=self accessCollection class name].
+ 		i>2
+ 			ifTrue:[self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString  occurrencesOf:(allElementsAsString at:i)).].	
+ 			].!

Item was added:
+ ----- Method: LinkedListTest>>testPrintOnDelimiter (in category 'tests - printing') -----
+ testPrintOnDelimiter
+ 	| aStream result allElementsAsString tmp |
+ 	result:=''.
+ 	aStream:= ReadWriteStream on: result.
+ 	tmp:= OrderedCollection new.
+ 	self nonEmpty do: [:each | tmp add: each asString].
+ 	
+ 	
+ 	
+ 	self nonEmpty printOn: aStream delimiter: ', ' .
+ 	
+ 	allElementsAsString:=(result findBetweenSubStrs: ', ' ).
+ 	1 to: allElementsAsString size do:
+ 		[:i | 
+ 		self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString  occurrencesOf:(allElementsAsString at:i))
+ 			].!

Item was added:
+ ----- Method: LinkedListTest>>testPrintOnDelimiterLast (in category 'tests - printing') -----
+ testPrintOnDelimiterLast
+ 
+ 	| aStream result allElementsAsString tmp |
+ 	result:=''.
+ 	aStream:= ReadWriteStream on: result.
+ 	tmp:= OrderedCollection new.
+ 	self nonEmpty do: [:each | tmp add: each asString].
+ 	
+ 	self nonEmpty printOn: aStream delimiter: ', ' last: 'and'.
+ 	
+ 	allElementsAsString:=(result findBetweenSubStrs: ', ' ).
+ 	1 to: allElementsAsString size do:
+ 		[:i | 
+ 		i<(allElementsAsString size-1 )
+ 			ifTrue: [self assert: (tmp occurrencesOf: (allElementsAsString at:i))=(allElementsAsString  occurrencesOf: (allElementsAsString at:i))].
+ 		i=(allElementsAsString size-1)
+ 			ifTrue:[ self deny: (allElementsAsString at:i)=('and')asString].
+ 		i=(allElementsAsString size)
+ 			ifTrue: [self assert: (tmp occurrencesOf: (allElementsAsString at:i))=(allElementsAsString  occurrencesOf: (allElementsAsString at:i))].
+ 			].!

Item was added:
+ ----- Method: LinkedListTest>>testReject (in category 'tests - iterating') -----
+ testReject
+ 
+ 	| res element |
+ 	res := self collectionWithoutNilElements reject: [:each | each notNil not].
+ 	self assert: res size = self collectionWithoutNilElements size.
+ 	
+ 	element := self collectionWithoutNilElements anyOne.
+ 	res := self collectionWithoutNilElements  reject: [:each | each = element].
+ 	self assert: res size = (self collectionWithoutNilElements size - 1).
+ 	
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testRejectAllThenCollect (in category 'tests - iterating') -----
+ testRejectAllThenCollect
+ 	| result |
+ 	
+ 	result := (self collectionWithoutNilElements 
+ 		reject: [ :each | each notNil ] )
+ 		collect: [ :each| self fail ].
+ 	
+ 	self assert: result isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testRejectEmpty (in category 'tests - iterating') -----
+ testRejectEmpty
+ 
+ 	| res |
+ 	res := self empty reject: [:each | each odd].
+ 	self assert: res size = self empty size
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testRejectNoReject (in category 'tests - iterating') -----
+ testRejectNoReject
+ 
+ 	| res |
+ 	res := self collectionWithoutNilElements  reject: [:each | each notNil not].
+ 	self assert: res size = self collectionWithoutNilElements size.
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testRejectThenCollect (in category 'tests - iterating') -----
+ testRejectThenCollect
+ 
+ 	| result index selectIndex pivot |
+ 	
+ 	index := 0.
+ 	selectIndex := 0.
+ 	pivot := self collectionWithoutNilElements anyOne.
+ 	
+ 	result := (self collectionWithoutNilElements 
+ 		reject: [ :each | 
+ 			selectIndex := selectIndex + 1.
+ 			"reject the first element"
+ 			selectIndex = 1 ])
+ 		collect: [ :each | 
+ 			self assert: each notNil.
+ 			index := index + 1.
+ 			pivot ].
+ 			
+ 	self assert: result ~= self collectionWithoutNilElements.
+ 	self assert: selectIndex equals: self collectionWithoutNilElements size.
+ 	self assert: index equals: self collectionWithoutNilElements size - 1.
+ 	
+ 	self assert: (self collectionWithoutNilElements occurrencesOf: pivot) equals: 1.
+ 	"should be > 1 for standard collection and = 1 for those that do not allow exact duplicates"
+ 	self assert: (result occurrencesOf: pivot) >= 1.
+ 	 !

Item was added:
+ ----- Method: LinkedListTest>>testRejectThenCollectEmpty (in category 'tests - iterating') -----
+ testRejectThenCollectEmpty
+ 
+ 	self assert: ((self empty reject: [:e | self fail ]) collect: [ :each| self fail ]) isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testRejectThenDoOnEmpty (in category 'tests - iterating') -----
+ testRejectThenDoOnEmpty
+ 
+ 	self assert: (self empty reject: [:e | self fail ] thenDo: [ self fail ]) isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testRemoveAllError (in category 'tests - remove') -----
+ testRemoveAllError
+ 	"self debug: #testRemoveElementThatExists"
+ 	| el aSubCollection |
+ 	el := self elementNotIn.
+ 	aSubCollection := self nonEmptyWithoutEqualElements copyWith: el.
+ 	self 
+ 		should: [ | res | res := self nonEmptyWithoutEqualElements removeAll: aSubCollection ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testRemoveAllFoundIn (in category 'tests - remove') -----
+ testRemoveAllFoundIn
+ 	"self debug: #testRemoveElementThatExists"
+ 	| el aSubCollection res |
+ 	el := self nonEmptyWithoutEqualElements anyOne.
+ 	aSubCollection := (self nonEmptyWithoutEqualElements copyWithout: el) copyWith: self elementNotIn.
+ 	res := self nonEmptyWithoutEqualElements removeAllFoundIn: aSubCollection.
+ 	self assert: self nonEmptyWithoutEqualElements size = 1.
+ 	self nonEmptyWithoutEqualElements do: [ :each | self assert: each = el ]!

Item was added:
+ ----- Method: LinkedListTest>>testRemoveAllSuchThat (in category 'tests - remove') -----
+ testRemoveAllSuchThat
+ 	"self debug: #testRemoveElementThatExists"
+ 	| el aSubCollection |
+ 	el := self nonEmptyWithoutEqualElements anyOne.
+ 	aSubCollection := self nonEmptyWithoutEqualElements copyWithout: el.
+ 	self nonEmptyWithoutEqualElements removeAllSuchThat: [ :each | aSubCollection includes: each ].
+ 	self assert: self nonEmptyWithoutEqualElements size = 1.
+ 	self nonEmptyWithoutEqualElements do: [ :each | self assert: each = el ]!

Item was added:
+ ----- Method: LinkedListTest>>testRemoveElementFromEmpty (in category 'tests - remove') -----
+ testRemoveElementFromEmpty
+ 	"self debug: #testRemoveElementFromEmpty"
+ 	self 
+ 		should: [ self empty remove: self nonEmptyWithoutEqualElements anyOne ]
+ 		raise: Error!

Item was added:
+ ----- Method: LinkedListTest>>testRemoveElementReallyRemovesElement (in category 'tests - remove') -----
+ testRemoveElementReallyRemovesElement
+ 	"self debug: #testRemoveElementReallyRemovesElement"
+ 	| size |
+ 	size := self nonEmptyWithoutEqualElements size.
+ 	self nonEmptyWithoutEqualElements remove: self nonEmptyWithoutEqualElements anyOne.
+ 	self assert: size - 1 = self nonEmptyWithoutEqualElements size!

Item was added:
+ ----- Method: LinkedListTest>>testRemoveElementThatExists (in category 'tests - remove') -----
+ testRemoveElementThatExists
+ 	"self debug: #testRemoveElementThatExists"
+ 
+ 	| el res |
+ 	el := self nonEmptyWithoutEqualElements anyOne.
+ 	res := self nonEmptyWithoutEqualElements remove: el.
+ 	self assert: res == el!

Item was added:
+ ----- Method: LinkedListTest>>testRemoveIfAbsent (in category 'tests - remove') -----
+ testRemoveIfAbsent
+ 	"self debug: #testRemoveElementThatExists"
+ 
+ 	| el res |
+ 	el := self elementNotIn.
+ 	res := self nonEmptyWithoutEqualElements remove: el ifAbsent: [ 33 ].
+ 	self assert: res = 33!

Item was added:
+ ----- Method: LinkedListTest>>testReverse (in category 'tests - copying same contents') -----
+ testReverse
+ 
+ 	| result |
+ 	result := self nonEmpty reversed.	
+ 	"verify content of 'result: '"
+ 	1 to: result size do:
+ 		[:i | self assert: ((result at: i) 
+ 			= (self nonEmpty at: (self nonEmpty size - i + 1)))].
+ 	"verify size of 'result' :"
+ 	self assert: result size=self nonEmpty size.!

Item was added:
+ ----- Method: LinkedListTest>>testReverseDo (in category 'tests - iterate on sequenced reable collections') -----
+ testReverseDo
+ 	| result |
+ 	result:= OrderedCollection new.
+ 	self nonEmpty reverseDo: [: each | result add: each].
+ 	
+ 	1 to: result size do:
+ 		[:i|
+ 		self assert: (result at: i)=(self nonEmpty at:(self nonEmpty size-i+1))].!

Item was added:
+ ----- Method: LinkedListTest>>testReverseDoEmpty (in category 'tests - iterate on sequenced reable collections') -----
+ testReverseDoEmpty
+ 	| result |
+ 	result:= OrderedCollection new.
+ 	self empty reverseDo: [: each | result add: each].
+ 	
+ 	self assert: result isEmpty .!

Item was added:
+ ----- Method: LinkedListTest>>testReverseWithDo (in category 'tests - iterate on sequenced reable collections') -----
+ testReverseWithDo
+ 	
+ 	| firstCollection secondCollection index |
+ 
+ 	firstCollection := self nonEmptyMoreThan1Element.
+ 	secondCollection := firstCollection copy.
+ 	index := firstCollection size.
+ 	
+ 	firstCollection  reverseWith: secondCollection do:
+ 		[:a :b |
+ 	
+ 		self assert: (firstCollection at: index) equals:  a. 
+ 		self assert: (secondCollection at: index) equals:  b.
+ 			( index := index - 1).]
+ 	
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testReversed (in category 'tests - copying same contents') -----
+ testReversed
+ 	| result |
+ 	result := self nonEmpty reversed .
+ 	
+ 	"verify content of 'result: '"
+ 	1 to:  result size do:
+ 		[:i | self assert: ((result at:i)=(self nonEmpty at:(self nonEmpty size-i+1)))].
+ 	"verify size of 'result' :"
+ 	self assert: result size=self nonEmpty size.!

Item was added:
+ ----- Method: LinkedListTest>>testSelect (in category 'tests - iterating') -----
+ testSelect
+ 
+ 	| result element |
+ 	result := self collectionWithoutNilElements select: [ :each | each notNil].
+ 	self assert: result size equals: self collectionWithoutNilElements size.
+ 	
+ 	element := self collectionWithoutNilElements anyOne.
+ 	result := self collectionWithoutNilElements select: [ :each | (each = element) not].
+ 	self assert: result size equals: (self collectionWithoutNilElements size - 1).
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testSelectNoneThenCollect (in category 'tests - iterating') -----
+ testSelectNoneThenCollect
+ 	| result |
+ 	
+ 	result := self collectionWithoutNilElements 
+ 		select: [ :each | each isNil ] 
+ 		thenCollect: [ :each| self fail ].
+ 	
+ 	self assert: result isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testSelectOnEmpty (in category 'tests - iterating') -----
+ testSelectOnEmpty
+ 
+ 	self assert: (self empty select: [:e | self fail]) isEmpty
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testSelectThenCollect (in category 'tests - iterating') -----
+ testSelectThenCollect
+ 
+ 	| result index selectIndex pivot |
+ 	
+ 	index := 0.
+ 	selectIndex := 0.
+ 	pivot := self collectionWithoutNilElements anyOne.
+ 	
+ 	result := self collectionWithoutNilElements 
+ 		select: [ :each | 
+ 			selectIndex := selectIndex + 1.
+ 			"reject the first element"
+ 			selectIndex > 1 ]
+ 		thenCollect: [ :each | 
+ 			self assert: each notNil.
+ 			index := index + 1.
+ 			pivot ].
+ 			
+ 	self assert: result ~= self collectionWithoutNilElements.
+ 	self assert: selectIndex equals: self collectionWithoutNilElements size.
+ 	self assert: index equals: self collectionWithoutNilElements size - 1.
+ 	
+ 	self assert: (self collectionWithoutNilElements occurrencesOf: pivot) equals: 1.
+ 	"should be > 1 for standard collection and = 1 for those that do not allow exact duplicates"
+ 	self assert: (result occurrencesOf: pivot) >= 1.
+ 	 !

Item was added:
+ ----- Method: LinkedListTest>>testSelectThenCollectOnEmpty (in category 'tests - iterating') -----
+ testSelectThenCollectOnEmpty
+ 
+ 	self assert: (self empty select: [:e | self fail ] thenCollect: [ self fail ]) isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testSelectThenDoOnEmpty (in category 'tests - iterating') -----
+ testSelectThenDoOnEmpty
+ 
+ 	self assert: (self empty select: [:e | self fail ] thenDo: [ self fail ]) isEmpty!

Item was added:
+ ----- Method: LinkedListTest>>testShallowCopy (in category 'tests - copying same contents') -----
+ testShallowCopy
+ 	| result |
+ 	result := self nonEmpty shallowCopy .
+ 	
+ 	"verify content of 'result: '"
+ 	1 to: self nonEmpty size do:
+ 		[:i | self assert: ((result at:i)=(self nonEmpty at:i))].
+ 	"verify size of 'result' :"
+ 	self assert: result size=self nonEmpty size.!

Item was added:
+ ----- Method: LinkedListTest>>testShallowCopyEmpty (in category 'tests - copying same contents') -----
+ testShallowCopyEmpty
+ 	| result |
+ 	result := self empty shallowCopy .
+ 	self assert: result isEmpty .!

Item was added:
+ ----- Method: LinkedListTest>>testShuffled (in category 'tests - copying same contents') -----
+ testShuffled
+ 	| result |
+ 	result := self nonEmpty shuffled .
+ 	
+ 	"verify content of 'result: '"
+ 	result do: [:each | self assert: (self nonEmpty occurrencesOf: each)=(result occurrencesOf: each)].
+ 	"verify size of 'result' :"
+ 	self assert: result size=self nonEmpty size.!

Item was added:
+ ----- Method: LinkedListTest>>testStoreOn (in category 'tests - printing') -----
+ testStoreOn
+ " for the moment work only for collection that include simple elements such that Integer"
+ 
+ "| string str result cuttedResult index elementsAsStringExpected elementsAsStringObtained tmp |
+ string := ''.
+ str := ReadWriteStream  on: string.
+ elementsAsStringExpected := OrderedCollection new.
+ elementsAsStringObtained := OrderedCollection new.
+ self nonEmpty do: [ :each | elementsAsStringExpected  add: each asString].
+ 
+ self nonEmpty storeOn: str.
+ result := str contents .
+ cuttedResult := ( result findBetweenSubStrs: ';' ).
+ 
+ index := 1.
+ 
+ cuttedResult do:
+ 	[ :each |
+ 	index = 1 
+ 		ifTrue: [ self assert: (each beginsWith: ( tmp := '((' , self nonEmpty class asString , ' new) add: '           )).
+ 				tmp := each copyFrom: ( tmp size + 1) to: ( each size ).
+ 				elementsAsStringObtained add: tmp.
+ 				index := index + 1. ]
+ 		ifFalse:  [ 
+ 		 index < cuttedResult size
+ 			ifTrue:[self assert: (each beginsWith: ( tmp:=  ' add: '   )).
+ 				tmp := each copyFrom: ( tmp size + 1) to: ( each size ).
+ 				elementsAsStringObtained add: tmp.
+ 					index := index + 1.]
+ 			ifFalse: [self assert: ( each = ' yourself)' ) ].
+ 			]
+ 	
+ 	].
+ 
+ 
+ 	elementsAsStringExpected do: [ :each | self assert: (elementsAsStringExpected occurrencesOf: each ) = ( elementsAsStringObtained occurrencesOf: each) ]"
+ 
+ !

Item was added:
+ ----- Method: LinkedListTest>>testSumNumbers (in category 'tests - iterating') -----
+ testSumNumbers
+ 	|result|
+ 	result:= self collectionWithoutNilElements 
+ 		detectSum: [ :ele | ele notNil ifTrue: [ 1 ] ifFalse: [ 0 ]].
+ 	
+ 	self assert: self collectionWithoutNilElements size = result!

Item was added:
+ ----- Method: LinkedListTest>>testSwapAdjacent (in category 'tests - swap') -----
+ testSwapAdjacent
+ 	|aList|
+ 	aList := LinkedList with: 5 with: 4 with: 3 with: 2 with: 1.
+ 	
+ 	aList swap: 3 with: 4.
+ 	self assert: (aList at: 3) equals: 2.
+ 	self assert: (aList at: 4) equals: 3.!

Item was added:
+ ----- Method: LinkedListTest>>testSwapAdjacentEnd (in category 'tests - swap') -----
+ testSwapAdjacentEnd
+ 	|aList|
+ 	aList := LinkedList with: 5 with: 4 with: 3 with: 2 with: 1.
+ 	
+ 	aList swap: 4 with: 5.
+ 	self assert: (aList at: 4) equals: 1.
+ 	self assert: (aList at: 5) equals: 2.
+ 	self assert: aList last equals: 2.!

Item was added:
+ ----- Method: LinkedListTest>>testSwapAdjacentStart (in category 'tests - swap') -----
+ testSwapAdjacentStart
+ 	|aList|
+ 	aList := LinkedList with: 5 with: 4 with: 3 with: 2 with: 1.
+ 	
+ 	aList swap: 1 with: 2.
+ 	self assert: (aList at: 1) equals: 4.
+ 	self assert: (aList at: 2) equals: 5.
+ 	self assert: aList first equals: 4.!

Item was added:
+ ----- Method: LinkedListTest>>testSwapBasic (in category 'tests - swap') -----
+ testSwapBasic
+ 	|aList|
+ 	aList := LinkedList with: 5 with: 4 with: 3 with: 2 with: 1.
+ 	
+ 	aList swap: 2 with: 4.
+ 	self assert: (aList at: 2) equals: 2.
+ 	self assert: (aList at: 4) equals: 4.
+ !

Item was added:
+ ----- Method: LinkedListTest>>testSwapStartAndEnd (in category 'tests - swap') -----
+ testSwapStartAndEnd
+ 	|aList|
+ 	aList := LinkedList with: 5 with: 4 with: 3 with: 2 with: 1.
+ 	
+ 	aList swap: 1 with: 5.
+ 	self assert: (aList at: 1) equals: 1.
+ 	self assert: (aList at: 5) equals: 5.
+ 	self assert: aList first equals: 1.
+ 	self assert: aList last equals: 5.!

Item was added:
+ ----- Method: LinkedListTest>>testTAdd (in category 'tests - adding') -----
+ testTAdd
+ 
+ 	| added |
+ 	added := self otherCollection add: self element.
+ 	self assert: added = self element. "equality or identity ?"
+ 	self assert: (self otherCollection includes: self element).
+ 
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testTAddAll (in category 'tests - adding') -----
+ testTAddAll
+ 	| added collection toBeAdded |
+ 	collection := self collectionWithElement .
+ 	toBeAdded := self otherCollection .
+ 	added := collection addAll: toBeAdded .
+ 	self assert: added == toBeAdded .	"test for identiy because #addAll: has not reason to copy its parameter."
+ 	self assert: (collection includesAllOf: toBeAdded )!

Item was added:
+ ----- Method: LinkedListTest>>testTAddIfNotPresentWithElementAlreadyIn (in category 'tests - adding') -----
+ testTAddIfNotPresentWithElementAlreadyIn
+ 
+ 	| added oldSize collection anElement |
+ 	collection := self collectionWithElement .
+ 	oldSize := collection size.
+ 	anElement := self element .
+ 	self assert: (collection  includes: anElement ).
+ 	
+ 	added := collection  addIfNotPresent: anElement .
+ 	
+ 	self assert: added == anElement .	"test for identiy because #add: has not reason to copy its parameter."
+ 	self assert: collection  size = oldSize!

Item was added:
+ ----- Method: LinkedListTest>>testTAddIfNotPresentWithNewElement (in category 'tests - adding') -----
+ testTAddIfNotPresentWithNewElement
+ 
+ 	| added oldSize collection elem |
+ 	collection := self otherCollection .
+ 	oldSize := collection  size.
+ 	elem := self element .
+ 	self deny: (collection  includes: elem ).
+ 	
+ 	added := collection  addIfNotPresent: elem .
+ 	self assert: added == elem . "test for identiy because #add: has not reason to copy its parameter."
+ 	self assert: (collection  size = (oldSize + 1)).
+ 
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testTWrite (in category 'tests - adding') -----
+ testTWrite
+ 	| added collection elem |
+ 	collection := self otherCollection  .
+ 	elem := self element .
+ 	added := collection  write: elem .
+ 	
+ 	self assert: added == elem .	"test for identiy because #add: has not reason to copy its parameter."
+ 	self assert: (collection  includes: elem )	.
+ 	self assert: (collection  includes: elem ).
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testUnion (in category 'tests - set arithmetic') -----
+ testUnion
+ 	"self debug: #testUnionOfEmpties"
+ 	
+ 	| union |
+ 	union := self empty union: self nonEmpty.
+ 	self containsAll: union of: self empty andOf: self nonEmpty.
+ 	union := self nonEmpty union: self empty.
+ 	self containsAll: union of: self empty andOf: self nonEmpty.
+ 	union := self collection union: self nonEmpty.
+ 	self containsAll: union of: self collection andOf: self nonEmpty.!

Item was added:
+ ----- Method: LinkedListTest>>testUnionOfEmpties (in category 'tests - set arithmetic') -----
+ testUnionOfEmpties
+ 	"self debug: #testUnionOfEmpties"
+ 	
+ 	self assert:  (self empty union: self empty) isEmpty.
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testWithCollect (in category 'tests - iterate on sequenced reable collections') -----
+ testWithCollect
+ 	
+ 	| result firstCollection secondCollection index  |
+ 
+ 	firstCollection := self nonEmptyMoreThan1Element.
+ 	secondCollection := firstCollection copy.
+ 	index := 0.
+ 	
+ 	result := firstCollection  with: secondCollection collect:
+ 		[:a :b |
+ 		( index := index + 1).
+ 		self assert: (firstCollection at: index) equals:  a. 
+ 		self assert: (secondCollection at: index) equals:  b.
+ 		b].
+ 	
+ 	1 to: result size do:[: i | self assert: (result at:i)= (secondCollection  at: i)].
+ 	self assert: result size = secondCollection  size.!

Item was added:
+ ----- Method: LinkedListTest>>testWithCollectError (in category 'tests - iterate on sequenced reable collections') -----
+ testWithCollectError
+ 	self should: [self nonEmptyMoreThan1Element with: self empty collect:[:a :b | ]] raise: Error.!

Item was added:
+ ----- Method: LinkedListTest>>testWithDo (in category 'tests - iterate on sequenced reable collections') -----
+ testWithDo
+ 	
+ 	| firstCollection secondCollection index |
+ 
+ 	firstCollection := self nonEmptyMoreThan1Element.
+ 	secondCollection := firstCollection copy.
+ 	index := 0.
+ 	
+ 	firstCollection  with: secondCollection do:
+ 		[:a :b |
+ 		( index := index + 1).
+ 		self assert: (firstCollection at: index) equals:  a. 
+ 		self assert: (secondCollection at: index) equals:  b.]
+ 	
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testWithDoError (in category 'tests - iterate on sequenced reable collections') -----
+ testWithDoError
+ 	
+ 	self should: [self nonEmptyMoreThan1Element with: self empty do:[:a :b | ]] raise: Error.!

Item was added:
+ ----- Method: LinkedListTest>>testWithIndexCollect (in category 'tests - iterate on sequenced reable collections') -----
+ testWithIndexCollect
+ 	
+ 	| result index collection |
+ 	index := 0.
+ 	collection := self nonEmptyMoreThan1Element .
+ 	result := collection  withIndexCollect: [:each :i | 
+ 		self assert: i = (index := index + 1).	
+ 		self assert: i = (collection  indexOf: each) .
+ 		each] . 
+ 	
+ 	1 to: result size do:[: i | self assert: (result at:i)= (collection at: i)].
+ 	self assert: result size = collection size.!

Item was added:
+ ----- Method: LinkedListTest>>testWithIndexDo (in category 'tests - iterate on sequenced reable collections') -----
+ testWithIndexDo
+ 	
+ 	"| result |
+ 	result:=Array new: self nonEmptyMoreThan1Element size.
+ 	self nonEmptyMoreThan1Element  withIndexDo: [:each :i | result at:i put:(each+i)].
+ 	
+ 	1 to: result size do:[: i | self assert: (result at:i)= ((self nonEmptyMoreThan1Element at: i) + i)]"
+ 	|  indexes elements |
+ 	indexes:= OrderedCollection new.
+ 	elements := OrderedCollection new.
+ 	
+ 	self nonEmptyMoreThan1Element  withIndexDo: 
+ 		[:value :i  |
+ 		indexes  add: (i).
+ 		elements add: value].
+ 	
+ 	(1 to: self nonEmptyMoreThan1Element size )do:
+ 		[ :i |
+ 		self assert: (indexes at: i) = i.
+ 		self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i).	
+ 		].
+ 	
+ 	self assert: indexes size = elements size. 
+ 	self assert: indexes size = self nonEmptyMoreThan1Element size . 
+ 	!

Item was added:
+ ----- Method: LinkedListTest>>testsBeginsWith (in category 'tests - begins ends with') -----
+ testsBeginsWith
+ 	
+ 	self assert: (self nonEmpty beginsWith:(self nonEmpty copyUpTo: self nonEmpty last)).
+ 	self assert: (self nonEmpty beginsWith:(self nonEmpty )).
+ 	self deny: (self nonEmpty beginsWith:(self nonEmpty copyWith:self nonEmpty first)).!

Item was added:
+ ----- Method: LinkedListTest>>testsBeginsWithEmpty (in category 'tests - begins ends with') -----
+ testsBeginsWithEmpty
+ 	
+ 	self deny: (self nonEmpty beginsWith:(self empty)).
+ 	self deny: (self empty beginsWith:(self nonEmpty )).
+ !

Item was added:
+ ----- Method: LinkedListTest>>testsEndsWith (in category 'tests - begins ends with') -----
+ testsEndsWith
+ 	
+ 	self assert: (self nonEmpty endsWith: self nonEmpty copyWithoutFirst).
+ 	self assert: (self nonEmpty endsWith: self nonEmpty).
+ 	self deny: (self nonEmpty endsWith: (self nonEmpty copyWith: self nonEmpty first)).!

Item was added:
+ ----- Method: LinkedListTest>>testsEndsWithEmpty (in category 'tests - begins ends with') -----
+ testsEndsWithEmpty
+ 	
+ 	self deny: (self nonEmpty endsWith: self empty).
+ 	self deny: (self empty endsWith: self nonEmpty).
+ 	!



More information about the Packages mailing list