SortedDirectory subclass: #AddressCard instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' ! !AddressCard class methods ! new "comment" | answer | answer := super new. answer init. ^ answer.! ! !AddressCard methods ! contains: s "Returns true iff there is a string match of the argument and one of the values on the card." | index | index := associations size + 1. [(index := index - 1) > 0] whileTrue: [ ((((associations at: index) value) indexOfCollection: s) = 0) ifFalse: [^true]]. ^false! display: aStream "Nicely formatted output to aStream." aStream cr. aStream show: ( ((self lookup: 'Last') value), ', ', ((self lookup: 'First') value) ). aStream cr. aStream show: ( (self lookup: 'Address') value). aStream cr. aStream nextPutAll: ( ((self lookup: 'City') value), ', ', ((self lookup: 'State') value), ' ', ((self lookup: 'Zip') value)). aStream cr. aStream nextPutAll: ( (self lookup: 'Phone') value). aStream cr. associations do: [ :assoc | (self reserved: (assoc key)) ifTrue: [ ] ifFalse: [ aStream nextPutAll: ((assoc key) , ': ', (assoc value)). aStream cr. ] ]! init "Initialization and preset of reserved values." super init. self set: 'Last' value: 'undefined'. self set: 'First' value: 'undefined'. self set: 'Address' value: 'undefined'. self set: 'City' value: 'undefined'. self set: 'State' value: 'undefined'. self set: 'Zip' value: 'undefined'. self set: 'Phone' value: 'undefined'.! key: k contains: s "Returns true iff there is a string match of the argument with key k on card" | aKey | aKey := self lookup: k. (aKey = nil) ifFalse: [ ((aKey value) indexOfCollection: s) = 0 ifFalse: [^true] ]. ^false.! last: l first: f "Sets the last and first name" self set: 'Last' value: l. self set: 'First' value: f.! remove: k "Removes entry with key k if k is not a reserved entry." ( self reserved: k ) ifTrue: [ ] ifFalse: [ super remove: k ].! reserved: k "These are default keys. Method returns true iff k is not a default key." ^ k = 'Last' | ( (k = 'First') | (((( (k = 'Address') | (k = 'City')) | (k = 'State')) | (k = 'Zip')) | (k = 'Phone'))) .! 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: [ super remove: k. super set: k value: v.].! !