[comp.lang.smalltalk] Inside Smalltalk example

benson@milton.u.washington.edu (Dan Benson) (03/19/91)

Here is some sample code from section 4.3 in chapter 5 of Inside Smalltalk
by Lalonde and Pugh.  It comes straight out of the book and I thought I'd
make it available so that others could save time typing.  I don't know if
it's already available somewhere else or if perhaps all of the book's code
is online (wouldn't that be nice?).

--------------------------------------- snip snip --------------  
Object subclass: #Pizza
	instanceVariableNames: 'size toppings window oldSize oldToppings '
	classVariableNames: 'OffForm OnForm '
	poolDictionaries: ''
	category: 'Inside Smalltalk 5.4.3'!


!Pizza methodsFor: 'query window support'!

acceptPizzaChoices
	oldSize := oldToppings := nil.
	window controller closeAndUnschedule.
	window := nil!

cancelPizzaChoices
	size := oldSize.
	toppings := oldToppings.
	window controller closeAndUnschedule.
	window := nil!

isSize: aSymbol
	^size == aSymbol!

makeSize: aSymbol
	size := aSymbol.
	self changed: #isSize:!

toppingAddOrRemove: aSymbol
	(self toppingContains: aSymbol)
		ifTrue: [toppings remove: aSymbol]
		ifFalse: [toppings add: aSymbol].
	self changed: #toppingContains:!

toppingContains: aSymbol
	^toppings includes: aSymbol! !

!Pizza methodsFor: 'querying'!

queryUser
	window isNil ifFalse: [Display flash: Display boundingBox. ^self].
	oldSize := size.
	oldToppings := toppings deepCopy. "in case of cancel"
	window := self queryWindow.
	window controller open!

queryWindow
	"Common information."
	| whiteColor noBorder noArguments topViewSize topView picture layout sizeSymbol selectorArguments xStart toppingSymbol acceptPicture cancelPicture pictureExtent |
	whiteColor := Form white.
	noBorder := 0.
	noArguments := #().

	topViewSize := 300 @ 200.
	topView := (StandardSystemView new)
		label: 'Pizza Choices';
		minimumSize: topViewSize;
		maximumSize: topViewSize;
		insideColor: whiteColor;
		borderWidth: 1;
		window: (0 @ 0 corner: topViewSize);
		yourself.

	"Row 1."
	picture := 'size:' asParagraph.
	layout := 20 @ 25 extent: picture extent.
	topView addSubView: ((DisplayTextView new) model: picture;
		controller: NoController new;
		insideColor: whiteColor;
		borderWidth: noBorder;
		window: layout viewport: layout;
		yourself).

	"Row 2."
	1 to: 3 do: 
		[:index | 
		sizeSymbol := #(#small #medium #large ) at: index.
		selectorArguments := Array with: sizeSymbol.
		xStart := index - 1 * 90 + 40.
		layout := xStart @ 50 extent: OffForm extent.
		topView addSubView: ((((SwitchView new) model: self;
		label: OffForm;
		selector: #isSize:;
		arguments: selectorArguments;
		insideColor: whiteColor;
		borderWidth: noBorder;
		window: OffForm boundingBox viewport: layout;
		highlightForm: OnForm;
		yourself) controller) selector: #makeSize:;
		arguments: selectorArguments;
		view).
		picture := sizeSymbol asParagraph.
		layout := xStart + 20 @ 50 extent: picture extent.
		topView addSubView: ((DisplayTextView new) model: picture;
		controller: NoController new;
		insideColor: whiteColor;
		borderWidth: noBorder;
		window: layout viewport: layout;
		yourself)].	"Row 3."
	picture := 'toppings:' asParagraph.
	layout := 20 @ 75 extent: picture extent.
	topView addSubView: ((DisplayTextView new) model: picture;
		controller: NoController new;
		insideColor: whiteColor;
		borderWidth: noBorder;
		window: layout viewport: layout;
		yourself).

	"Row 4."
	1 to: 3 do: 
		[:index | 
		toppingSymbol := #(#cheese #pepperoni #onion ) at: index.
		selectorArguments := Array with: toppingSymbol.
		xStart := index - 1 * 90 + 40.
		layout := xStart @ 100 extent: OffForm extent.
		topView addSubView: ((((SwitchView new) model: self;
		label: OffForm;
		selector: #toppingContains:;
		arguments: selectorArguments;
		insideColor: whiteColor;
		borderWidth: noBorder;
		window: OffForm boundingBox viewport: layout;
		highlightForm: OnForm;
		yourself) controller) selector: #toppingAddOrRemove:;
		arguments: selectorArguments;
		view).
		picture := toppingSymbol asParagraph.
		layout := xStart + 20 @ 100 extent: picture extent.
		topView addSubView: ((DisplayTextView new) model: picture;
		controller: NoController new;
		insideColor: whiteColor;
		borderWidth: noBorder;
		window: layout viewport: layout;
		yourself)].

"Eliminate destructive modification to switch labels caused by automatic centerLabel."
	OffForm offset: 0 @ 0.

	"Row 5."
	acceptPicture := 'accept' asParagraph.
	cancelPicture := 'cancel' asParagraph.
	pictureExtent := (acceptPicture extent max: cancelPicture extent) + (8 @ 8).
	layout := 80 @ 150 extent: pictureExtent.
	topView addSubView: ((((SwitchView new) model: self;
		label: acceptPicture;
		selector: #isNil;
		arguments: noArguments;
		insideColor: whiteColor;
		borderWidth: 1;
		window: layout viewport: layout;
		yourself) controller) selector: #acceptPizzaChoices;
		arguments: noArguments;
		view).

	layout := 175 @ 150 extent: pictureExtent.
	topView addSubView: ((((SwitchView new) model: self;
		label: cancelPicture;
		selector: #isNil;
		arguments: noArguments;
		insideColor: whiteColor;
		borderWidth: 1;
		window: layout viewport: layout;
		yourself) controller) selector: #cancelPizzaChoices;
		arguments: noArguments;
		view).

	"Done."
	^topView! !

!Pizza methodsFor: 'printing'!

printOn: aStream
	aStream nextPutAll: 'a '; nextPutAll: size; nextPutAll: ' pizza with: '.
	toppings asOrderedCollection asArray printOn: aStream! !

!Pizza methodsFor: 'initialize'!

initialize
	size := #medium.
	toppings := Set new! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Pizza class
	instanceVariableNames: ''!


!Pizza class methodsFor: 'instance creation'!

example1
	"Pizza example1"
	Pizza new inspect!

new
	^super new initialize! !

!Pizza class methodsFor: 'initialize'!

initialize
	"Pizza initialize"
	OffForm := Form
		extent: 15@15
		fromArray: #(0 1984 6192 12312 8200 16388 16388 16388 16388 16388 8200 12296 6192 1984 0)
		offset: 0@0.

	OnForm := Form
		extent: 15@15
		fromArray: #(0 0 0 0 0 896 1984 1984 1984 896 0 0 0 0 0)
		offset: 0@0! !

Pizza initialize!