IntList / IntListElt CS 313 Smalltalk linked list example Also serves as an example for how you could organize your code for the text-based submission of homework 5 part 2. Class IntListElt ================ Object subclass:#IntListElt instanceVariableNames:'val next' classVariableNames:'' poolDictionaries:'' category:'DanielsClasses' Class methods ------------- none (the accessor methods val: and next: will be used to initialize the instance variables) Instance methods ---------------- val: anInt "set the value of the instance variable 'val'" val := anInt val "return the value of the instance variable 'val'" ^ val next: anIntListElt "set the value of the instance variable 'next'" next := anIntListElt next "return the value of the instance variable 'next'" ^ next lengthR "returns length of list (recursive version)" "called by IntList's instance method lengthR" (next == nil) ifTrue: [^ 1]. ^ 1 + (next lengthR) maxR "returns maximum value in list (recursive version)" "called by IntList's instance method maxR" (next == nil) ifTrue: [^ val]. ^ val max: (next maxR) do: aBlock "execute aBlock for all elements in list" aBlock value: val. (next ~~ nil) ifTrue: [ next do: aBlock ] Class IntList ============= Object subclass:#IntList instanceVariableNames:'head' classVariableNames:'' poolDictionaries:'' category:'DanielsClasses' Class methods ------------- none ("new" will initialize "head" to nil, which is just what we want) Instance methods ---------------- isEmpty "returns whether list is empty" ^ (head == nil) first "returns first integer in the list" "assert: list not empty" self isEmpty ifTrue: [self error: 'cannot get first of empty list']. ^ head val add: anInt "inserts anInt at the head of the list" | e | e := IntListElt new. e val: anInt. e next: head. head := e remove "removes first element in the list and returns its value" "assert: list not empty" | v | self isEmpty ifTrue: [self error: 'cannot remove from empty list']. v := head val. head := head next. ^ v length "returns length of list" | n e | n := 0. e := head. [e ~~ nil] whileTrue: [ n := n + 1. e := e next. ]. ^n lengthR "returns length of list (recursive version)" "most of the work is done by IntListElt's instance method lengthR" self isEmpty ifTrue: [^ 0]. ^ head lengthR max "returns maximum value in list" "assert: list not empty" | m e | self isEmpty ifTrue: [self error: 'cannot compute max of empty list']. m := head val. e := head next. [e ~~ nil] whileTrue: [ (e val > m) ifTrue: [ m := e val. ]. e := e next. ]. ^m maxR "returns maximum value in list (recursive version)" "all of the work is done by IntListElt's instance method maxR" "assert: list not empty" self isEmpty ifTrue: [self error: 'cannot compute max of empty list']. ^ head maxR do: aBlock "execute aBlock for all elements in list" self isEmpty ifFalse: [ head do: aBlock ] Testing and sample output ========================= Transcript clear; show: 'Testing IntList methods on list (0, 4, 2, 3)'; cr. t := IntList new. t add: 3. t add: 2. t add: 4. t add: 0. Transcript show: 'isEmpty -> '; show: t isEmpty; cr. Transcript show: 'max -> '; show: t max; cr. Transcript show: 'length -> '; show: t length; cr. Transcript show: 'remove -> '; show: t remove; cr. Transcript show: 'lengthR -> '; show: t lengthR; cr. Transcript show: 't do: [:x | Transcript show: x; cr]'; cr. t do: [:x | Transcript show: x; cr]. Transcript show: 'remove -> '; show: t remove; cr. Transcript show: 'max -> '; show: t max; cr. Transcript show: 'first -> '; show: t first; cr. Transcript show: 'maxR -> '; show: t maxR; cr. Transcript show: 'remove -> '; show: t remove; cr. Transcript show: 'isEmpty -> '; show: t isEmpty; cr. Transcript show: 'length -> '; show: t length; cr. Transcript show: 'remove -> '; show: t remove; cr. Transcript show: 'isEmpty -> '; show: t isEmpty; cr. output (produced using "doIt" on the code above): ------------------------------------------------- Testing IntList methods on list (0, 4, 2, 3) isEmpty -> false max -> 4 length -> 4 remove -> 0 lengthR -> 3 t do: [:x | Transcript show: x; cr] 4 2 3 remove -> 4 max -> 3 first -> 2 maxR -> 3 remove -> 2 isEmpty -> false length -> 1 remove -> 3 isEmpty -> true