96
S.Ducasse 1 QuickTime™ TIFF (Uncompr are needed t Stéphane Ducasse [email protected] http://www.listic.univ-savoie.f r/~ducasse/ Elements of Design

Stoop 414-smalltalk elementsofdesign

Embed Size (px)

DESCRIPTION

 

Citation preview

Page 1: Stoop 414-smalltalk elementsofdesign

S.Ducasse 1

QuickTime™ and aTIFF (Uncompressed) decompressorare needed to see this picture.

Stéphane [email protected]://www.listic.univ-savoie.fr/~ducasse/

Elements of Design

Page 2: Stoop 414-smalltalk elementsofdesign

S.Ducasse 2

License: CC-Attribution-ShareAlike 2.0http://creativecommons.org/licenses/by-sa/2.0/

Page 3: Stoop 414-smalltalk elementsofdesign

S.Ducasse 3

Elements of Design • Instance initialization • Enforcing the instance

creation • Instance / Class methods• Instance variables / Class

instance variables• Class initialization• Law of Demeter• Factoring Constants• Abstract Classes• Template Methods• Delegation• Bad Coding Style

Page 4: Stoop 414-smalltalk elementsofdesign

S.Ducasse 4

Instance initialization • Automatic initialize• Lazy initialize• Proposing the right interface• Providing default value

Page 5: Stoop 414-smalltalk elementsofdesign

S.Ducasse 5

Provider Responsibility• This is the responsibility of the class to

provide well-formed object

• The client should not make assumptions or been responsible to send specific sequence of messages to get a working object

Page 6: Stoop 414-smalltalk elementsofdesign

S.Ducasse 6

Instance Initialization•How to ensure that an instance is well

initialized?• Automatic initialize• Lazy initialize• Proposing the right interface• Providing default value

Page 7: Stoop 414-smalltalk elementsofdesign

S.Ducasse 7

A First Implementation of Packet

Object subclass: #PacketinstanceVariableNames: ‘contents addressee

originator ‘

Packet>>printOn: aStreamsuper printOn: aStream.aStream nextPutAll: ‘ addressed to: ‘; nextPutAll: self

addressee.aStream nextPutAll: ‘ with contents: ’; nextPutAll: self

contents

Packet>>addressee^addressee

Packet>>addressee: aSymboladdressee := aSymbol

Page 8: Stoop 414-smalltalk elementsofdesign

S.Ducasse 8

Packet class Definition

Packet class is automatically defined Packet class

instanceVariableNames: ''

Example of instance creationPacket new

addressee: #mac ; contents: ‘hello mac’

Page 9: Stoop 414-smalltalk elementsofdesign

S.Ducasse 9

Fragile Instance CreationIf we do not specify a contents, it breaks!

|p|p := Packet new addressee: #mac.p printOn: aStream -> error

Problems of this approach:responsibility of the instance creation relies on the clients A client can create packet without contents, without address instance variable not initialized -> error (for example, printOn:) -> system fragile

Page 10: Stoop 414-smalltalk elementsofdesign

S.Ducasse 10

Fragile Instance Creation Solutions

•Automatic initialization of instance variables

• Proposing a solid interface for the creation• Lazy initialization

Page 11: Stoop 414-smalltalk elementsofdesign

S.Ducasse 11

Assuring Instance Variable Initialization•How to initialize a newly created instance ?•Define the method initialize

Packet>>initialize

super initialize. contents := ‘’. addressee := #noAd

Page 12: Stoop 414-smalltalk elementsofdesign

S.Ducasse 12

(VW) Assuring Instance Variable Initialization•Problem: By default new class method

returns instance with uninitialized instance variables.

•Moreover in VisualWorks, initialize method is not automatically called by creation methods new/new:.

•How to initialize a newly created instance ?

Page 13: Stoop 414-smalltalk elementsofdesign

S.Ducasse 13

The New/Initialize CoupleDefine an instance method that initializes the instance variables and override new to invoke it.(1&2) Packet class>>new “Class Method”

^ super new initialize

(3) Packet>>initialize “Instance Method” super initialize.(4) contents := ‘default message’

Packet new (1-2) => aPacket initialize (3-4) => returning aPacket but initialized!Reminder: You cannot access instance variables from a class method like new

Page 14: Stoop 414-smalltalk elementsofdesign

S.Ducasse 14

The New/Initialize CoupleObject>>initialize

“do nothing. Called by new my subclasses override me if necessary”

^ self

Page 15: Stoop 414-smalltalk elementsofdesign

S.Ducasse 15

One single method application

Page 16: Stoop 414-smalltalk elementsofdesign

S.Ducasse 16

Strengthen Instance Creation Interface•Problem: A client can still create aPacket

without address. •Solution: Force the client to use the class

interface creation.

• Providing an interface for creation and avoiding the use of new: Packet send: ‘Hello mac’ to: #Mac

•First try: Packet class>>send: aString to: anAddress

^ self new contents: aString ; addressee: anAddress

Page 17: Stoop 414-smalltalk elementsofdesign

S.Ducasse 17

Examples of Instance Initialization

step 1. SortedCollection sortBlock: [:a :b| a name < b name]

SortedCollection class>>sortBlock: aBlock "Answer a new instance of SortedCollection such that its elements are sorted according to the criterion specified in aBlock."

^self new sortBlock: aBlock

step 2. self new => aSortedCollection step 3. aSortedCollection sortBlock: aBlock step 4. returning the instance aSortedCollection

Page 18: Stoop 414-smalltalk elementsofdesign

S.Ducasse 18

Another Examplestep 1. OrderedCollection with: 1

Collection class>>with: anObject "Answer a new instance of a Collection containing anObject."

| newCollection | newCollection := self new.

newCollection add: anObject. ^newCollection

Page 19: Stoop 414-smalltalk elementsofdesign

S.Ducasse 19

Lazy InitializationWhen some instance variables are:

- not used all the time- consuming space, difficult to initialize because depending on other- need a lot of computation

Use lazy initialization based on accessors

Accessor access should be used consistently!

Page 20: Stoop 414-smalltalk elementsofdesign

S.Ducasse 20

Lazy Initialization ExampleA lazy initialization scheme with default value

Packet>>contents contents isNil ifTrue: [contents := ‘no contents’]

^ contentsaPacket contents or self contents

A lazy initialization scheme with computed valueDummy>>ratioBetweenThermonuclearAndSolar

ratio isNil ifTrue: [ratio := self heavyComputation]

^ ratio

Page 21: Stoop 414-smalltalk elementsofdesign

S.Ducasse 21

Providing a Default ValueOrderedCollection variableSubclass: #SortedCollection

instanceVariableNames: 'sortBlock 'classVariableNames: 'DefaultSortBlock '

SortedCollection class>>initializeDefaultSortBlock := [:x :y | x <= y]

SortedCollection>>initialize"Set the initial value of the receiver's sorting

algorithm to a default.”sortBlock := DefaultSortBlock

Page 22: Stoop 414-smalltalk elementsofdesign

S.Ducasse 22

Providing a Default ValueSortedCollection class>>new: anInteger

"Answer a new instance of SortedCollection. The default sorting is a <= comparison on elements. "

^ (super new: anInteger) initialize

SortedCollection class>>sortBlock: aBlock "Answer a new instance of SortedCollection such

that its elements are sorted according to the criterion specified in aBlock. "

^ self new sortBlock: aBlock

Page 23: Stoop 414-smalltalk elementsofdesign

S.Ducasse 23

Invoking per Default the Creation Interface

OrderedCollection class>>new"Answer a new empty instance of

OrderedCollection."

^self new: 5

Page 24: Stoop 414-smalltalk elementsofdesign

S.Ducasse 24

Forbidding new?Problem: We can still use new to create fragile instances

Solution: new should raise an error!

Packet class>>new self error: 'Packet should only be

created using send:to:'

Page 25: Stoop 414-smalltalk elementsofdesign

S.Ducasse 25

Forbidding new Implications

But we still have to be able to create instance!

Packet class>>send: aString to: anAddres ^ self new contents: aString ; addressee: anAddress=> raises an error

Packet class>>send: aString to: anAddress^ super new contents: aString ; addressee:

anAddress

=> BAD STYLE: link between class and superclass dangerous in case of evolution

Page 26: Stoop 414-smalltalk elementsofdesign

S.Ducasse 26

Forbidding new Solution: use basicNew and basicNew:

Packet class>>send: aString to: anAddress

^ self basicNew contents: aString ; addressee: anAddress

Conclusion: Never override basic* methods else you will not be able to invoke them later

Page 27: Stoop 414-smalltalk elementsofdesign

S.Ducasse 27

How to Reuse Superclass Initialization?

A class>>new^ super new doThat; andThat; end

B class>>forceClientInterface^ self basicNew ???

Solution: Define the initialization behavior on the instance sideA>>doThatAndThatEnd

^ self doThat; andThat; end A class>>new

^ super new doThatAndThatEndB class>>forceClientInterface

^ self basicNew doThatAndThatEnd

Page 28: Stoop 414-smalltalk elementsofdesign

S.Ducasse 28

Different Self/SuperDo not invoke a super with a different method selector. It’s bad style because it links a class and a superclass. This is dangerous in case the software evolves.

Page 29: Stoop 414-smalltalk elementsofdesign

S.Ducasse 29

ExamplePacket class>>new self error: 'Packet should be created using send:to:'

Packet class>>send: aString to: anAddress^ super new contents: aString ; addressee:

anAddress

Use basicNew and basicNew:

Packet class>>send: aString to: anAddress ^ self basicNew contents: aString ; addressee: anAddress

Page 30: Stoop 414-smalltalk elementsofdesign

S.Ducasse 30

Super is static!With the super foo:

A new bar-> 10B new bar-> 10C new bar -> 10

Without the super foo:A new bar-> 10B new bar-> 100C new bar -> 50

super shortcuts dynamic calls

Page 31: Stoop 414-smalltalk elementsofdesign

S.Ducasse 31

Basic Design Mistakes

Page 32: Stoop 414-smalltalk elementsofdesign

S.Ducasse 32

A Class should haveClass Person {

String getName(); void setName(String name);int getAge(); void setAge(int age);Car getCar(); void setCar(Car car);

}What do we see ?

A class should have one main responsibility and some behavior not just holding stateMinimal access to its data!

Page 33: Stoop 414-smalltalk elementsofdesign

S.Ducasse 33

Confusing Class City extends Place { … }Class Jerusalem extends City implements Capital { … }Class TelAviv extends City { … }

What is wrong here?

Confusing inheritance and instantiationToo much inheritance?

Page 34: Stoop 414-smalltalk elementsofdesign

S.Ducasse 34

Do not expose implementation

Page 35: Stoop 414-smalltalk elementsofdesign

S.Ducasse 35

Do not overuse conversionsnodes asSet removes all the duplicated nodes (if node knows how to compare). But a systematic use of asSet to protect yourself from duplicate is not good

nodes asSet asOrderedCollectionreturns an ordered collection after removing duplicates

Look for the real source of duplication if you do not want it!

Page 36: Stoop 414-smalltalk elementsofdesign

S.Ducasse 36

Hiding missing informationDictionary>>at: aKey This raises an error if the key is not found

Dictionary>>at: aKey ifAbsent: aBlockAllows one to specify action aBlock to be done when the key does not exist.

Do not overuse it:nodes at: nodeId ifAbsent:[ ]

This is bad because at least we should know that the nodeId was missing

Page 37: Stoop 414-smalltalk elementsofdesign

S.Ducasse 37

isNilAvoid to return special results as nil

messages := self fetchMessages.messages isNil  ifFalse: [ messages dispatchFrom: self ]

What if we would simply return an empty collection infetchMessages instead of nil?

Less conditional and ugly tests!!

Page 38: Stoop 414-smalltalk elementsofdesign

S.Ducasse 38

Say once and only once•No Magic Number Duplicated•Extract method•Remove duplicated code

Page 39: Stoop 414-smalltalk elementsofdesign

S.Ducasse 39

Factorize Magic NumbersIdeally you should be able to change your constants without having any impact on the code!

For thatdefine a constant only once via accessorprovide testing method (hasNextNode)default value using the constant accessor

Page 40: Stoop 414-smalltalk elementsofdesign

S.Ducasse 40

Factoring Out ConstantsWe want to encapsulate the way “no next node” is coded. Instead of writing:

Node>>nextNode^ nextNode

NodeClient>>transmitTo: aNodeaNode nextNode = ‘no next node’

...

Page 41: Stoop 414-smalltalk elementsofdesign

S.Ducasse 41

Factoring Out ConstantsWrite:

NodeClient>>transmitTo: aNodeaNode hasNextNode

....Node>>hasNextNode

^ (self nextNode = self class noNextNode) not

Node class>>noNextNode^ ‘no next node’

Page 42: Stoop 414-smalltalk elementsofdesign

S.Ducasse 42

Default value between class and instance

If we want to encapsulate the way “no next node” is coded and shared this knowledge between class and instances. Instead of writing: aNode nextNode isNil not Write: Node>>hasNextNode

^ self nextNode = self noNextNodeNode>>noNextNode

^self class noNextNodeNode class>>noNextNode

^ #noNode

Page 43: Stoop 414-smalltalk elementsofdesign

S.Ducasse 43

Initializing without Duplicating

Node>>initializeaccessType := ‘local’...

Node>>isLocal^ accessType = ‘local’

It’s better to writeNode>>initialize

accessType := self localAccessType

Node>>isLocal^ accessType = self localAccessType

Node>>localAccessType^ ‘local’

Page 44: Stoop 414-smalltalk elementsofdesign

S.Ducasse 44

Say something only onceIdeally you could be able to change the constant without having any problems.You may have to have mapping tables from model constants to UI constants or database constants.

Page 45: Stoop 414-smalltalk elementsofdesign

S.Ducasse 45

Constants Needed at Creation Time

Node class>>localNodeNamed: aString|inst|inst := self new.inst name: aString.inst type: inst localAccessType

If you want to have the following creation interfaceNode class>>name: aString accessType:

aType^self new name: aString ; accessType: aType

Node class>>name: aString^self name: aString accessType: self

localAccessType

Page 46: Stoop 414-smalltalk elementsofdesign

S.Ducasse 46

Constants Needed at Creation Time

You need:Node class>>localAccessType

^ ‘local’

=> Factor the constant between class and instance level

Node>>localAccessType^ self class localAccessType

=> You could also use a ClassVariable that is shared between a class and its instances.

Page 47: Stoop 414-smalltalk elementsofdesign

S.Ducasse 47

Elements of Design • Class initialization

Page 48: Stoop 414-smalltalk elementsofdesign

S.Ducasse 48

Class Methods - Class Instance Variables•Classes (Packet class) represents class (Packet).•Class instance variables are instance variables

of class • They should represent the state of class:

number of created instances, number of messages sent, superclasses, subclasses....

•Class methods represent class behavior: instance creation, class initialization, counting the number of instances....

• If you weaken the second point: class state and behavior can be used to define common properties shared by all the instances

Page 49: Stoop 414-smalltalk elementsofdesign

S.Ducasse 49

Class Initialization•How do we know that all the class behavior

has been loaded?•At the end !

•Automatically called by the system at load time or explicitly by the programmer.

•Used to initialize a classVariable, a pool dictionary or class instance variables.

• ‘Classname initialize’ at the end of the saved files in Squeak

• In postLoadAction: in VW

Page 50: Stoop 414-smalltalk elementsofdesign

S.Ducasse 50

Example of class initialization

Magnitude subclass: #Date instanceVariableNames: 'day year' classVariableNames:

'DaysInMonth FirstDayOfMonth MonthNames SecondsInDay WeekDayNames’

Page 51: Stoop 414-smalltalk elementsofdesign

S.Ducasse 51

Date class>>initializeDate class>>initialize "Initialize class variables representing the names of the months and days and the number of seconds, days in each month, and first day of each month. " MonthNames := #(January February March April May June July August September October November December ). SecondsInDay := 24 * 60 * 60. DaysInMonth := #(31 28 31 30 31 30 31 31 30 31 30 31 ). FirstDayOfMonth := #(1 32 60 91 121 152 182 213 244 274 305 335 ). WeekDayNames := #(Monday Tuesday Wednesday Thursday Friday Saturday Sunday )

Page 52: Stoop 414-smalltalk elementsofdesign

S.Ducasse 52

Sharing or not

•How can I share state and prepare • for instance specific state?

Page 53: Stoop 414-smalltalk elementsofdesign

S.Ducasse 53

Case Study: Scanner

Scanner new scanTokens: 'identifier keyword: 8r31

''string'' embedded.period key:word: . '

>#(#identifier #keyword: 25 'string' 'embedded.period' #key:word: #'.')

Page 54: Stoop 414-smalltalk elementsofdesign

S.Ducasse 54

A Case Study: The Scanner class

Class Definition

Object subclass: #ScannerinstanceVariableNames: 'source mark

prevEnd hereChar token tokenType saveComments currentComment buffer typeTable '

classVariableNames: 'TypeTable 'poolDictionaries: ''category: 'System-Compiler-Public Access'

Page 55: Stoop 414-smalltalk elementsofdesign

S.Ducasse 55

Scanner enigmaWhy having an instance variable and a classVariable denoting the same object (the scanner table)?

TypeTable is used to initialize once the tabletypeTable is used by every instance and each instance can customize the table (copying).

Page 56: Stoop 414-smalltalk elementsofdesign

S.Ducasse 56

Clever Sharing

Page 57: Stoop 414-smalltalk elementsofdesign

S.Ducasse 57

A Case Study: Scanner (II)Scanner class>>initialize

"Scanner initialize"| newTable |newTable := ScannerTable new: 255 withAll: #xDefault. "default"newTable atAllSeparatorsPut: #xDelimiter.newTable atAllDigitsPut: #xDigit.newTable atAllLettersPut: #xLetter.'!%&*+,-/<=>?@\~' do: [:bin | newTable at: bin asInteger put:

#xBinary]."Other multi-character tokens"newTable at: $" asInteger put: #xDoubleQuote...."Single-character tokens"newTable at: $( asInteger put: #leftParenthesis....newTable at: $^ asInteger put: #upArrow. "spacing circumflex,

formerly up arrow"newTable at: $| asInteger put: #verticalBar.TypeTable := newTable

Page 58: Stoop 414-smalltalk elementsofdesign

S.Ducasse 58

A Case Study: Scanner (III)Instances only access the type table via the instance variable that points to the table that has been initialized once.

Scanner class>> new^super new initScanner

Scanner>>initScannerbuffer := WriteStream on: (String new: 40).saveComments := true.typeTable := TypeTable

A subclass just has to specialize initScanner without copying the initialization of the table

MyScanner>>initScannersuper initScannertypeTable := typeTable copy.typeTable at: $) asInteger put: #xDefault.

Page 59: Stoop 414-smalltalk elementsofdesign

S.Ducasse 59

A Simple Case...• Introducing parametrization

Page 60: Stoop 414-smalltalk elementsofdesign

S.Ducasse 60

Parametrization Advantages

DialectStream>>initializeST80ColorTable"Initialize the colors that characterize the ST80 dialect"ST80ColorTable _ IdentityDictionary new.#((temporaryVariable blue italic) (methodArgument blue normal) … (setOrReturn black bold)) do:

[:aTriplet |ST80ColorTable at: aTriplet first put: aTriplet

allButFirst]

•Problems:•Color tables hardcoded in method•Changes Require compilation•Client responsible of initialize invocation•No run-time changes

Page 61: Stoop 414-smalltalk elementsofdesign

S.Ducasse 61

One StepDialectStream>>initializeST80ColorTable

ST80ColorTable := IdentityDictionary new.self defaultDescription do:

[:aTriplet | ST80ColorTable at: aTriplet first put: aTriplet allButFirst]

DialectStream>>defaultDescription ^ #((temporaryVariable blue italic) (methodArgument blue normal) … (setOrReturn black bold))

Still requires subclassing and recompilation

Page 62: Stoop 414-smalltalk elementsofdesign

S.Ducasse 62

Composition-based SolutionDialectStream>>initializeST80ColorTableWith: anArray

ST80ColorTable := IdentityDictionary new. anArray do: [:aTriplet | ST80ColorTable at: aTriplet first

put: aTriplet allButFirst]. self initialize

•In a ClientDialectStream initializeST80ColorTableWith:

#(#(#temporaryVariable #blue #normal) … #(#prefixKeyword #veryDarkGray #bold) #(#setOrReturn #red #bold) )

Page 63: Stoop 414-smalltalk elementsofdesign

S.Ducasse 63

Methods are Units of Reuse•Dynamic binding and methods •= reuse in subclasses

Page 64: Stoop 414-smalltalk elementsofdesign

S.Ducasse 64

Methods are Unit of Reuse

Page 65: Stoop 414-smalltalk elementsofdesign

S.Ducasse 65

Example: Forced to Duplicate!Node>>computeRatioForDisplay

|averageRatio defaultNodeSize|averageRatio := 55.

defaultNodeSize := self mainWindowCoordinate /maximiseViewRatio.

self window add:(UINode new with:

(self bandWidth * averageRatio / defaultWindowSize)…

•We are forced to copy the complete method! SpecialNode>>computeRatioForDisplay

|averageRatio defaultNodeSize|averageRatio := 55.defaultNodeSize := self mainWindowCoordinate +

minimalRatio / maximiseViewRatio.self window add:

(UINode new with: (self bandWidth * averageRatio / defaultWindowSize)

Page 66: Stoop 414-smalltalk elementsofdesign

S.Ducasse 66

Self sends: Plan for ReuseNode>>computeRatioForDisplay

|averageRatio defaultNodeSize|averageRatio := 55.defaultNodeSize := self defaultNodeSize.self window add:

(UINode new with: (self bandWidth * averageRatio /

defaultWindowSize)...

Node>>defaultNodeSize^self mainWindowCoordinate / maxiViewRatio

SpecialNode>>defaultNodeSize^ self

mainWindowCoordinate+minimalRatio/maxiViewRatio

Page 67: Stoop 414-smalltalk elementsofdesign

S.Ducasse 67

Do not Hardcode ConstantsNode>>computeRatioForDisplay

|averageRatio defaultNodeSize|averageRatio := 55.defaultNodeSize := self mainWindowCoordinate / maximiseViewRatio.self window add:(UINode new with:

(self bandWidth * averageRatio / defaultWindowSize)....

•We are forced to copy the method! SpecialNode>>computeRatioForDisplay

|averageRatio defaultNodeSize|averageRatio := 55.defaultNodeSize := self mainWindowCoordinate / maximiseViewRatio.self window add:

(ExtendedUINode new with: (self bandWidth * averageRatio /

defaultWindowSize).

Page 68: Stoop 414-smalltalk elementsofdesign

S.Ducasse 68

Class FactoriesNode>>computeRatioForDisplay

|averageRatio |averageRatio := 55.self window add:

self UIClass new with: (self bandWidth * averageRatio / self

defaultWindowSize)...

Node>>UIClass^ UINode

SpecialNode>>UIClass^ ExtendedUINode

Page 69: Stoop 414-smalltalk elementsofdesign

S.Ducasse 69

Hook and Template

Page 70: Stoop 414-smalltalk elementsofdesign

S.Ducasse 70

Hook and Template Methods• Hooks: place for reuse• Template: context for reuse

Page 71: Stoop 414-smalltalk elementsofdesign

S.Ducasse 71

Hook and Template Methods

• Templates: Context reused by subclasses• Hook methods: holes that can be specialized• Hook methods do not have to be abstract, they

may define default behavior or no behavior at all.• This has an influence on the instantiability of the

superclass.

Page 72: Stoop 414-smalltalk elementsofdesign

S.Ducasse 72

Hook / Template Example: Printing

Object>>printString"Answer a String whose characters are a description of the receiver."

| aStream |aStream := WriteStream on: (String new: 16).self printOn: aStream.^aStream contents

Page 73: Stoop 414-smalltalk elementsofdesign

S.Ducasse 73

HookObject>>printOn: aStream

"Append to the argument aStream a sequence of characters that describes the receiver."

| title |title := self class name.aStream nextPutAll: ((title at: 1) isVowel ifTrue: ['an '] ifFalse: ['a ']).aStream print: self class

Page 74: Stoop 414-smalltalk elementsofdesign

S.Ducasse 74

Overriding the HookArray>>printOn: aStream

"Append to the argument, aStream, the elements of the Array

enclosed by parentheses."

| tooMany |tooMany := aStream position + self maxPrint.aStream nextPutAll: '#('.self do: [:element |

aStream position > tooMany ifTrue: [ aStream nextPutAll: '...(more)...)'.

^self ]. element printOn: aStream]

separatedBy: [aStream space].aStream nextPut: $)

Page 75: Stoop 414-smalltalk elementsofdesign

S.Ducasse 75

OverridingFalse>>printOn: aStream

"Print false."

aStream nextPutAll: 'false'

Page 76: Stoop 414-smalltalk elementsofdesign

S.Ducasse 76

Specialization of the Hook

The class Behavior that represents a class extends the default hook but still invokes the default one.

Behavior>>printOn: aStream "Append to the argument aStream a

statement of whichsuperclass the receiver descends from."

aStream nextPutAll: 'a descendent of '.superclass printOn: aStream

Page 77: Stoop 414-smalltalk elementsofdesign

S.Ducasse 77

Another Example: CopyingComplex (deepCopy, veryDeepCopy...)Recursive objectsGraph of connected objectsEach object wants a different copy of itselfNo up-front solution

Page 78: Stoop 414-smalltalk elementsofdesign

S.Ducasse 78

Hook Example: CopyingObject>>copy

" Answer another instance just like the receiver. Subclasses normally override the postCopy message, but some objects that should not be copied override copy. "

^self shallowCopy postCopy

Object>>shallowCopy"Answer a copy of the receiver which shares the receiver's instance variables."

<primitive: 532>

Page 79: Stoop 414-smalltalk elementsofdesign

S.Ducasse 79

postCopyObject>>postCopy

"Finish doing whatever is required, beyond a shallowCopy, to implement 'copy'. Answer the receiver. This message is only intended to be sent to the newly created instance. Subclasses may add functionality, but they should always do super postCopy first. "

^self

Page 80: Stoop 414-smalltalk elementsofdesign

S.Ducasse 80

Sounds Trivial?

Page 81: Stoop 414-smalltalk elementsofdesign

S.Ducasse 81

Hook Specialisation

Bag>>postCopy"Make sure to copy the contents fully."

| new |super postCopy.new := contents class new: contents

capacity.contents keysAndValuesDo: [:obj :count | new at: obj put: count].

contents := new.

Page 82: Stoop 414-smalltalk elementsofdesign

S.Ducasse 82

Guidelines for Creating Template Methods

Simple implementation. Implement all the code in one method.

Break into steps. Comment logical subparts

Make step methods. Extract subparts as methods

Call the step methods Make constant methods, i.e., methods doing nothing else than returning.Repeat steps 1-5 if necessary on the methods created

Page 83: Stoop 414-smalltalk elementsofdesign

S.Ducasse 83

Inheritance vs. Composition

Page 84: Stoop 414-smalltalk elementsofdesign

S.Ducasse 84

Delegation of Responsibilities

New requirement: A document can be printed on different printers for example lw100s or lw200s depending on which printer is first encountered.

Page 85: Stoop 414-smalltalk elementsofdesign

S.Ducasse 85

Ad-hoc SolutionLanPrinter>>accept: aPacket

(thePacket addressee = #*lw*)ifTrue: [ self print: thePacket]ifFalse: [ (thePacket isAddressedTo: self)

ifTrue: [self print: thePacket] ifFalse: [super accept:

thePacket]]Limits:

not generalbrittle because based on a conventionadding a new kind of address behavior requires editing the class Printer

Page 86: Stoop 414-smalltalk elementsofdesign

S.Ducasse 86

Create Object and Delegate

• An alternative solution: isAddressedTo: could be sent directly to the address

• With the current solution, the packet can still control the process if needed

accept: aPacket

send: aPacket

nodePrinter aPacketnode1

isAddressedTo: nodePrinter

accept: aPacket

print: aPacket

[true]

[false]

anAddress

Page 87: Stoop 414-smalltalk elementsofdesign

S.Ducasse 87

NodeAddressNodeAddress is responsible for identifying the packet receivers

Packet>>isAddressedTo: aNode^ self address isAddressedTo: aNode address “was

name”

Object subclass: #NodeAddressinstanceVariableNames: ‘id‘

NodeAddress>>isAddressedTo: aNodeAddress^ self id = aNodeAddress id

Refactoring Remark: name was not a good name anyway, and now it has become an address -> we should rename it.

Page 88: Stoop 414-smalltalk elementsofdesign

S.Ducasse 88

Matching AddressFor packets with matchable addresses

Packet send: ‘lulu’ to: (MatchingAddress with: #*lw*)

Address subclass: #MatchingAddressinstanceVariableNames: ‘’

MatchingAddress>>isAddressedTo: aNodeAddress

^ self id match: aNodeAddress id

Page 89: Stoop 414-smalltalk elementsofdesign

S.Ducasse 89

AddressesObject subclass: #Address

instanceVariableNames: ‘id‘

Address>>isAddressedTo: anAddress^self subclassResponsibility

Address subclass: #NodeAddressinstanceVariableNames: ‘‘

Address subclass: #MatchingAddressinstanceVariableNames: ‘‘

Page 90: Stoop 414-smalltalk elementsofdesign

S.Ducasse 90

Trade-OffDelegation Pros

No blob class: one class one responsibilityVariation possibilityPluggable behavior without inheritance extensionRuntime pluggability

Delegation ConsDifficult to follow responsibilities and message flowAdding new classes = adding complexities (more names)New object

Page 91: Stoop 414-smalltalk elementsofdesign

S.Ducasse 91

Inheritance vs. Composition

Inheritance is not a panaceaRequire class definitionRequire method definitionExtension should be prepared in advanceNo run-time changes

Ex: editor with spell-checkerS, colorizerS, mail-readerS….

No clear responsibilityCode bloatedCannot load a new colorizers

Page 92: Stoop 414-smalltalk elementsofdesign

S.Ducasse 92

Delegating to other Objects

myEditor setColorizer: FastColorizer new.myEditor setColorizer: AdvancedColorizer new.Strategy design pattern

Page 93: Stoop 414-smalltalk elementsofdesign

S.Ducasse 93

Composition AnalysisPros

Possibility to change at run-timeClear responsibilityNo blobClear interaction protocol

ConsNew classDelegationNew classes

Page 94: Stoop 414-smalltalk elementsofdesign

S.Ducasse 94

Designing Classes...

Page 95: Stoop 414-smalltalk elementsofdesign

S.Ducasse 95

Designing Classes for Reuse

Encapsulation principle: minimize data representation dependenciesComplete interfaceNo overuse of accessorsResponsibility of the instance creation Loose coupling between classesMethods are units of reuse (self send)Use polymorphism as much as possible to avoid type checkingBehavior up and state downUse correct names for classUse correct names for methods

Page 96: Stoop 414-smalltalk elementsofdesign

S.Ducasse 96

Nothing magicThink about it Find your own heuristicsTaste, try and be critic

Be the force with you...

Summary