Object subclass: #AddressBook instanceVariableNames: 'cards ' classVariableNames: '' poolDictionaries: '' ! !AddressBook class methods ! new | ab | ab := super new. ab init. ^ab.! ! !AddressBook methods ! add: aCard ( self exists: aCard ) ifFalse: [ cards add: aCard ]! cards ^cards! delete: aCard "Removes aCard from cards" cards remove: aCard ifAbsent: [ ]! display: aStream "Sends the answer of each cards display method to the stream" aStream nextPutAll: '-----------------------------------------------------------';cr. cards do: [ :c | c display: aStream ]. aStream nextPutAll: '-----------------------------------------------------------';cr.! exists: aCard "Answers true if aCard is bound to one of the cards in the receiver" cards findFirst: [ :c | c = aCard ] ifAbsent: [ ^false ]. ^true.! find: aBlock "answers an AddressBook with cards in self such that aBlock evaluates to true" | aBook | aBook := AddressBook new. cards do: [ :c | (aBlock value: c) ifTrue: [ aBook add: c ] ]. ^ aBook.! init "Causes cards to be sorted in alphabetical order by last name, using first name for tie-break." cards := SortedCollection new. cards sortBlock: [ :a :b | (((a lookup: 'Last') value) = ((b lookup: 'Last') value)) ifFalse: [ ((a lookup: 'Last') value) < ((b lookup: 'Last') value) ] ifTrue: [ ((a lookup: 'First') value) <= ((b lookup: 'First') value) ] ]! intersection: otherBook "Answers an AddressBook containing all cards that are in both self and otherBook To qualify as being in both, the cards must be the same objects in memory" | aBook | aBook := AddressBook new. cards do: [ :c | (otherBook exists: c) ifTrue: [ aBook add: c] ]. ^ aBook.! subtractFrom: otherBook "Answers an AddressBook containing all cards of otherBook that are not in self. Equality is defined as being the same object in memory" | aBook | aBook := AddressBook new. (otherBook cards) do: [ :c | (self exists: c) ifFalse: [ aBook add: c] ]. ^ aBook.! union: otherBook "Answers an AddressBook containing all of the cards in self and otherBook" | aBook | aBook := AddressBook new. (self cards) do: [ :c | aBook add: c ]. (otherBook cards) do: [ :c | aBook add: c ]. ^ aBook.! !