Object subclass: #SortedDirectory instanceVariableNames: 'associations ' classVariableNames: '' poolDictionaries: '' ! !SortedDirectory class methods ! new "comment" | answer | answer := super new. answer init. ^ answer.! ! !SortedDirectory methods ! associations ^associations! display: aStream "Basic diagnostic contents to the Stream." associations do: [ :association | aStream nextPutAll: (association key). aStream tab. aStream nextPutAll: (association value). aStream cr. ].! exists: k "Checks the existence of a certain key in the directory" associations findFirst: [ :association | (association key) = k ] ifAbsent: [ ^false ]. ^true.! init "Set up sorting criterion." associations := SortedCollection new. associations sortBlock: [:a :b | (a key) <= (b key)]! lookup: k "Answers association with key k." (self exists: k) ifFalse: [ ^ nil ] ifTrue: [ ^ associations at: (associations findFirst: [ :association | k = (association key) ]) ].! remove: k "removes association with key k" (self exists: k) ifTrue: [ associations removeIndex: (associations findFirst: [ :association | k = (association key) ] ) ] ifFalse: [ ]! set: k value: v "Sets key to value if key already exists, otherwise create a new key and set." (self exists: k) ifFalse: [ associations add: ( Association key: k value: v ) ] ifTrue: [ self remove: k. self set: k value: v. ].! !