[ENH] Splash screen and new user start-up experience -- version 1

Stephen T. Pope stp at create.ucsb.edu
Tue May 16 19:57:51 UTC 2000


Hello all,

I've been away from Squeak for a spell, but wanted to get this out to
you all for comment. The enclosed change sets do several things:

1) Make a splash screen that does something cute before dropping the
users into Squeak. Comments on, or improvements to, the animation are
welcome (see DisplayScreen splash). I have three main questions (aside
from aesthetic issues):

a) How can I get the start-up animation to hook in to the VM so the
user's screen simply fades, rather than flashing a small window, then
the default-sized window, then the fade. It'd be nice for Squeak to come
up full-screen by default and to "fade" in and out.

b) How can I get a form from a TTSampleStringMorph? What I'd like to do
is the following, which doesn't work:

	text := TTSampleStringMorph new font: TTFontDescription someInstance; 
		string: ' Squeak Version 2.8a '.
	form := (FormCanvas extent: text extent) contentsOfArea: text bounds.  

c) Any ideas on how to get this to scale well to small screens and slow machines?


2) I changed things to make flaps look at a preference as to whether to
auto-pop-up or only expand on mouse clicks (with the default to be less "flashy").


3) I added in the outline tool and a simple new user outline (taken from
the introductory text that came out of the Camp Smalltalk).
(contributions are welcome)


I've also put a pre-compiled image/changes with these minor changes in 
ftp://ftp.create.ucsb.edu/pub/Squeak/goodies/splash/

...enjoy!

-- 

stp
  Stephen Travis Pope
  http://www.create.ucsb.edu/~stp
-------------- next part --------------
'From Squeak2.8alpha of 13 January 2000 [latest update: #1974] on 16 May 2000 at 12:33:22 pm'!

!Utilities class methodsFor: 'flaps' stamp: 'stp 1/1/1904 01:11'!
menuFlap
	"Preferences enable: #clickToOpenFlaps"
	| aFlap aFlapTab aHolder verticalHolder aMenu |
	aFlap _ PasteUpMorph newSticky color: Color transparent;
			 extent: self currentWorld width @ 264;
			 borderWidth: 0;
			 padding: 0.
	aFlapTab _ FlapTab new referent: aFlap.
	aFlapTab color: Color brown lighter.
	aFlapTab
		assumeString: 'Menus'
		font: Preferences standardFlapFont
		orientation: #horizontal
		color: Color blue muchLighter.
	aFlapTab setToPopOutOnMouseOver: (Preferences valueOfFlag: #clickToOpenFlaps) not.
	aFlapTab edgeToAdhereTo: #top;
	 inboard: false.
	aFlapTab position: Display width - aFlapTab width // 2 @ 0.
	aFlap setProperty: #flap toValue: true.
	aFlap color: (Color blue muchLighter alpha: 0.6).
	aFlap extent: self currentWorld width @ 267.
	aHolder _ AlignmentMorph newRow beSticky beTransparent.
	#(openMenu helpMenu windowsMenu changesMenu debugMenu playfieldMenu scriptingMenu ) do: [:elem | (elem isKindOf: Array)
			ifTrue: 
				[verticalHolder _ AlignmentMorph newColumn beSticky beTransparent.
				verticalHolder hResizing: #shrinkWrap;
				 inset: 0;
				 centering: #center.
				elem do: 
					[:aMenuSymbol | 
					verticalHolder addMorphBack: ((aMenu _ self currentHand perform: aMenuSymbol) beSticky; stayUp: true).
					aMenu beSticky.
					aMenu borderWidth: 1.
					aMenu submorphs second delete].
				aHolder addMorphBack: verticalHolder]
			ifFalse: 
				[aHolder addMorphBack: ((aMenu _ self currentHand perform: elem) beSticky; stayUp: true).
				aMenu submorphs second delete.
				aMenu beSticky.
				aMenu borderWidth: 1]].
	aFlap addMorphBack: aHolder.
	^ aFlapTab! !

!Utilities class methodsFor: 'flaps' stamp: 'stp 1/1/1904 01:09'!
standardBottomFlap
	| aFlapTab aPage |
	aPage _ self newPartsFlapPage.
	aPage setProperty: #maximumThumbnailWidth toValue: 80.
	aFlapTab _ FlapTab new referent: aPage beSticky.
	aFlapTab color: Color red lighter.
	aFlapTab setToPopOutOnDragOver: true.
	aFlapTab setToPopOutOnMouseOver: (Preferences valueOfFlag: #clickToOpenFlaps) not.
	aFlapTab
		assumeString: 'Supplies'
		font: Preferences standardFlapFont
		orientation: #horizontal
		color: Color red lighter.
	aFlapTab edgeToAdhereTo: #bottom;
	 inboard: false.
	aPage extent: self currentWorld width @ 100.
	#(PaintInvokingMorph RectangleMorph EllipseMorph StarMorph CurveMorph PolygonMorph TextMorph ImageMorph BasicButton SimpleSliderMorph PasteUpMorph BookMorph TabbedPalette JoystickMorph ) do: [:sym | aPage addMorphBack: (Smalltalk at: sym) authoringPrototype].
	aPage addMorphBack: ScriptingSystem prototypicalHolder.
	aPage addMorphBack: RectangleMorph roundRectPrototype.
	aPage addMorphBack: TrashCanMorph new markAsPartsDonor.
	aPage addMorphBack: ScriptingSystem scriptControlButtons markAsPartsDonor.
	aPage addMorphBack: Morph new previousPageButton markAsPartsDonor.
	aPage addMorphBack: Morph new nextPageButton markAsPartsDonor.
	aPage addMorphBack: (ClockMorph authoringPrototype showSeconds: false) step.
	aPage replaceTallSubmorphsByThumbnails.
	aPage fixLayout.
	aFlapTab position: Display width - aFlapTab width // 2 @ (self currentWorld height - aFlapTab height).
	aPage setProperty: #flap toValue: true.
	aPage color: Color red muchLighter.
	"alpha: 0.2"
	aPage extent: self currentWorld width @ 100.
	^ aFlapTab! !

!Utilities class methodsFor: 'flaps' stamp: 'stp 1/1/1904 01:09'!
standardLeftFlap
	| aFlap aFlapTab aButton aClock buttonColor anOffset |
	aFlap _ PasteUpMorph newSticky borderWidth: 0.
	aFlapTab _ FlapTab new referent: aFlap.
	aFlapTab
		assumeString: 'Squeak'
		font: Preferences standardFlapFont
		orientation: #vertical
		color: Color brown lighter lighter.
	aFlapTab edgeToAdhereTo: #left;
	 inboard: false.
	aFlapTab setToPopOutOnDragOver: true.
	aFlapTab setToPopOutOnMouseOver: (Preferences valueOfFlag: #clickToOpenFlaps) not.
	aFlapTab position: 0 @ (Display height - aFlapTab height // 2).
	aFlap setProperty: #flap toValue: true.
	aFlap color: Color brown muchLighter lighter.
	"alpha: 0.3"
	aFlap extent: 200 @ self currentWorld height.
	self addProjectNavigationButtonsTo: aFlap.
	anOffset _ 16.
	buttonColor _ Color green muchLighter.
	aButton _ SimpleButtonMorph new target: Smalltalk.
	aButton color: buttonColor.
	aButton actionSelector: #saveSession.
	aButton setBalloonText: 'Make a complete snapshot of the current state of the image onto disk.'.
	aButton label: 'snapshot'.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	aButton _ aButton fullCopy target: Utilities.
	aButton actionSelector: #fileOutChanges.
	aButton label: 'file out changes'.
	aButton setBalloonText: 'File out the current change set to disk.'.
	aFlap addMorph: aButton.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	aButton _ aButton fullCopy target: Utilities.
	aButton actionSelector: #browseRecentSubmissions.
	aButton setBalloonText: 'Open a message-list browser showing the 20 most-recently-submitted methods.'.
	aButton label: 'recent submissions'.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	aClock _ ClockMorph newSticky.
	aClock color: Color red.
	aClock showSeconds: false.
	aClock font: (TextStyle default fontAt: 3).
	aClock step.
	aClock setBalloonText: 'The time of day.  If you prefer to see seconds, check out my menu.'.
	aFlap addCenteredAtBottom: aClock offset: anOffset.
	aButton _ aButton fullCopy target: Preferences.
	aButton actionSelector: #openPreferencesInspector.
	aButton setBalloonText: 'Open a window allowing me to view and change various Preferences.'.
	aButton label: 'preferences...'.
	aButton color: Color cyan muchLighter.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	aButton _ aButton fullCopy target: Utilities.
	aButton actionSelector: #updateFromServer.
	aButton label: 'load code updates'.
	aButton setBalloonText: 'Check the Squeak server for any new code updates, and load any that are found.'.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	self addSystemStatusLinesTo: aFlap.
	aButton _ SimpleButtonMorph new target: self.
	aButton actionSelector: #explainFlaps;
	 color: buttonColor.
	aButton label: 'About flaps...'.
	aButton setBalloonText: 'Click here to get a window of information about flaps.'.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	aButton _ aButton fullCopy target: Preferences;
			 actionSelector: #editAnnotations;
			 label: 'Annotations...'.
	aButton setBalloonText: 'Click here to get a little window that will allow you to specify which types of annotations, in which order, you wish to see in the annotation pane of method-list browsers.'.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	aButton _ TrashCanMorph newSticky.
	aFlap addCenteredAtBottom: aButton offset: anOffset.
	aButton startStepping.
	^ aFlapTab! !

!Utilities class methodsFor: 'flaps' stamp: 'stp 1/1/1904 01:11'!
standardRightFlap
	"Preferences enable: #clickToOpenFlaps"

	| aFlapTab aPage |
	aPage _ self newPartsFlapPage.
	aFlapTab _ FlapTab new referent: aPage beSticky.
	aFlapTab color: Color red lighter.
	aFlapTab
		assumeString: 'Tools'
		font: Preferences standardFlapFont
		orientation: #vertical
		color: Color orange lighter.
	aFlapTab edgeToAdhereTo: #right;
	 inboard: false.
	aFlapTab setToPopOutOnDragOver: true.
	aFlapTab setToPopOutOnMouseOver: (Preferences valueOfFlag: #clickToOpenFlaps) not.
	aPage extent: 90 @ self currentWorld height.
	self addSampleWindowsTo: aPage.
	aPage addMorphBack: ScriptingSystem newScriptingSpace.
	aPage addMorphBack: RecordingControlsMorph authoringPrototype.
	aPage replaceTallSubmorphsByThumbnails.
	aPage fixLayout.
	aFlapTab position: self currentWorld width - aFlapTab width @ (Display height - aFlapTab height // 2).
	aPage setProperty: #flap toValue: true.
	aPage color: (Color brown muchLighter alpha: 0.5).
	aPage extent: 90 @ self currentWorld height.
	^ aFlapTab! !

Preferences enable: #clickToOpenFlaps!
-------------- next part --------------
'From Squeak2.8alpha of 19 January 2000 [latest update: #2121] on 16 May 2000 at 12:30:49 pm'!
Model subclass: #Outline
	instanceVariableNames: 'organization fileName keySeparator entrySeparator '
	classVariableNames: 'Default '
	poolDictionaries: ''
	category: 'Tools-Outlines'!

!Outline commentStamp: '<historical>' prior: 0!
An outline is a simple interface to a text structure for browsing.
It can hold onto a keyed text list, parse it from/save it to files, and be used with an OutlineBrowser.

Instance variables:
	organization 		<OrderedCollection of Associations> the list of text key -> text entry
	fileName 			<String> the file I was read in from (when relevant)
	keySeparator		<String> the separator between a key and its entry
	entrySeparator 	<String> the separator an entry and the following key!
Outline class
	instanceVariableNames: ''!
Browser subclass: #OutlineBrowser
	instanceVariableNames: 'model currentCategory viewer world '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Outlines'!

!OutlineBrowser commentStamp: '<historical>' prior: 0!
An OutrlineBrowser holds onto an Outline and creates a simple two-paned view on the one-level hierarchy using pluggable view components (list and text views).
The Browser implements key-list menu items for adding new keys, removing or renaming existing ones, and inspecting or saving the outline.
Text menu items are implemented for execution and the like.

Instance variable:
	currentCategory		<Text> selected item in the list of the model's keys!
OutlineBrowser class
	instanceVariableNames: ''!

!Object methodsFor: 'testing'!
hasItems
	"Overridden to return true in Collection-like classes."
	^ false! !

!Object methodsFor: 'testing'!
isString
	"Overridden to return true in String."

	^ false! !

!Object methodsFor: 'testing'!
isSymbol
	"Overridden to return true in Symbol."

	^ false! !

!Object methodsFor: 'converting'!
asValue
	"Answer the receiver as a value."

	^Value on: self! !

!Object methodsFor: 'converting'!
value
	"Answer the value of the receiver."

	^self! !


!Collection methodsFor: 'testing'!
hasItems
	"Answer whether or not the receiver has items or components (true)."

	^true! !


!Outline methodsFor: 'initialize-release'!
initialize
	"Set up meaningful default values for the receiver."

	organization :=  OrderedCollection new.
	keySeparator :=  '
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'.
	entrySeparator := '
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'.! !

!Outline methodsFor: 'accessing'!
assAt: aKey
	"Answer the association out of the organization."

	^organization detect: [ :ass | ass key = aKey] ifNone: [nil]! !

!Outline methodsFor: 'accessing' stamp: 'stp 02/18/98 0-12:'!
at: aKey
	"Answer the value out of the organization."

	| item |
	item := organization detect: [ :ass | ass key = aKey] ifNone: [nil].
	^item isNil
		ifFalse: [item value]
		ifTrue: [nil]! !

!Outline methodsFor: 'accessing' stamp: 'stp 5/30/1998 05:35'!
at: aKey put: aVal
	"Plug the given value into the organization."

	| item |
	item := self at: aKey.
	item isNil
		ifTrue: [organization add: (aKey -> aVal)]
		ifFalse: [item contentsText: aVal]! !

!Outline methodsFor: 'accessing' stamp: 'stp 5/15/1998 23:48'!
categoryAtIndex: anInt
	"Answer an item from the organization."

	^organization at: anInt! !

!Outline methodsFor: 'accessing' stamp: 'stp 5/15/1998 23:49'!
indexOfKey: aKey
	"Answer the index of an item from the organization."

	| item |
	item := organization detect: [ :ass | ass key = aKey]
			ifNone: [nil].
	^item isNil
		ifFalse: [organization indexOf: item]
		ifTrue: [0]! !

!Outline methodsFor: 'accessing' stamp: 'stp 11/02/1998 22:29'!
name
	"Answer the receiver's file name"

	^fileName! !

!Outline methodsFor: 'accessing'!
name: aName
	"Set the receiver's file name"

	fileName :=  aName! !

!Outline methodsFor: 'accessing'!
organization
	"Answer the receiver's organization."

	^organization! !

!Outline methodsFor: 'accessing'!
organization: anOrg
	"Set the receiver's outline (being careful about nils)"

	anOrg isNil ifTrue: [^self].
	organization :=  anOrg! !

!Outline methodsFor: 'accessing'!
organizationList
	"Answer the keys of the outline."

	^organization collect: [ :ass | ass key]! !

!Outline methodsFor: 'accessing'!
removeKey: aKey
	"Remove the named item from the organization."

	| item |
	item := organization detect: [ :ass | ass key = aKey]
			ifNone: [nil].
	item isNil
		ifFalse: [organization remove: item]! !

!Outline methodsFor: 'parsing' stamp: 'stp 5/27/1998 11:12'!
parseFrom: aStream keySeparator: keyStr entrySeparator: entryStr
	"Read in the receiver's organization using the given separators (as strings)"

	| tmp key body |
	entrySeparator class == Character
		ifTrue: [entrySeparator :=  String with: entryStr]
		ifFalse: [entrySeparator :=  entryStr].
	keySeparator class == Character
		ifTrue: [keySeparator :=  String with: keyStr]
		ifFalse: [keySeparator :=  keyStr].
	[aStream atEnd]
		whileFalse: 
			[tmp :=  ReadStream on: (aStream upToAll: entrySeparator).
			key :=  Object readFromString: (tmp upToAll: keySeparator).
			body :=  Object readFromString: tmp upToEnd.
			body isString
				ifTrue: [body := Workspace new contents: body asText].
			organization add: (key -> body)]! !

!Outline methodsFor: 'fileIn/Out' stamp: 'stp 11/03/1998 17:04'!
printAll
	"Prompt the user for a name and write the whole outline on a fileStream in a format for printing."

	| aFS aName |
	aName :=  fileName.
	aName isNil ifTrue: [aName := ''].
	aName :=  FillInTheBlank 
			request: 'file name for saved outline: ' 
			initialAnswer: aName, '.txt'.
	aName = '' ifTrue: [^self].
	aFS :=  FileStream fileNamed: aName.
	Cursor write showWhile:
		[organization do:
			[ :ass |
			aFS nextPutAll: '--- ', ass key, ' ---'; cr; cr;
				nextPutAll: ass value contents string; cr; cr;
				nextPutAll: '--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--=--'; cr; cr]].
	aFS close.! !

!Outline methodsFor: 'fileIn/Out' stamp: 'stp 12/07/1999 05:19'!
saveAll
	"Prompt the user for a name and write the whole outline on a fileStream."

	| aFS aName |
	aName :=  fileName.
	aName isNil ifTrue: [aName := ''].
	aName :=  FillInTheBlank 
			request: 'file name for saved outline: ' 
			initialAnswer: aName.
	aName = '' ifTrue: [^self].
	(FileDirectory default fileExists: aName)
		ifTrue: [FileDirectory default deleteFileNamed: aName].
	fileName := aName.
	aFS :=  FileStream fileNamed: aName.
	aFS ifNil: [self error: 'Cannot open file ', aName, ' for writing'].
	Cursor write showWhile:
		[organization do:
			[ :ass |
			ass key storeOn: aFS.
			aFS nextPutAll: keySeparator.
			ass value storeOn: aFS.
			aFS nextPutAll: entrySeparator]].
	aFS close.!
]style[(7 694)f1bcblue;,f1! !

!Outline methodsFor: 'fileIn/Out'!
saveCategory: aKey
	"prompt the user for a name and write the current text on a fileStream"

	| aFS aName |
	aName :=  fileName.
	aName == nil ifTrue: [ aName :=  '' ].
	aName :=  FillInTheBlank 
			request: 'file name for saved outline: ' 
			initialAnswer: aName.
	aFS :=  FileStream fileNamed: aName.
	self storeCategory: aKey on: aFS.
	aFS close.! !

!Outline methodsFor: 'fileIn/Out'!
storeCategory: aCategory on: aStream
	"store the chosen category on a stream"

	aCategory storeOn: aStream.
	aStream nextPutAll: keySeparator.
	(self at: aCategory) storeOn: aStream.
	aStream nextPutAll: entrySeparator! !

!Outline methodsFor: 'html' stamp: 'stp 11/03/1998 17:13'!
htmlFooter
	"Answer the file footer for HTML output."

	^'<P>
<ADDRESS>', fileName, ' Outline -- stp at create.ucsb.edu -- Generated ',
(Time dateAndTimeNow printString), 
'</ADDRESS>
</BODY>
</HTML>
'! !

!Outline methodsFor: 'html' stamp: 'stp 11/03/1998 17:20'!
htmlForString: str
	"Do semi-smart line-wrapping or HTML representation of the given string."

	| cr |
	cr := String with: Character cr.
	^((((str  breakIntoLinesOf: 80)
			copyReplaceAll: '<' with: '&lt;') 
			copyReplaceAll: '>' with: '&gt;')
			copyReplaceAll: ' ' with: '&nbsp;')
			copyReplaceAll: cr with: (cr, '<BR>', cr)! !

!Outline methodsFor: 'html' stamp: 'stp 11/03/1998 17:12'!
htmlHeader
	"Answer the file header for HTML output."

	^'<HTML>
<HEAD>
<TITLE>', fileName, '</TITLE>
</HEAD>
<BODY>
<A NAME="TOP">
<H2>', fileName, '</H2>
<H3>Sections</H3>
<UL>
'! !

!Outline methodsFor: 'html' stamp: 'stp 11/03/1998 17:21'!
storeHTML
	"Store the receiver on the given stream."
	"Outline someInstance storeHTML"

	| name fs |
	name :=  FillInTheBlank 
			request: 'file name for saved outline: ' 
			initialAnswer: fileName, '.html'.
	name = '' ifTrue: [^self].
	fs :=  FileStream newFileNamed: name.
	Cursor write showWhile:
	[fs nextPutAll: self htmlHeader.
	organization do:
		[ :ass |
		fs nextPutAll: '<LI><A HREF=#', (ass key copyReplaceAll: ' ' with: '_'), '>', ass key, '</A>'; cr].
	fs nextPutAll: '</UL><HR>'; cr.
	organization do:
		[ :ass |
		fs nextPutAll: '<A NAME="', (ass key copyReplaceAll: ' ' with: '_'), '">'; cr.
		fs nextPutAll: '<H3>', ass key, '</H3>'; cr; cr;
			nextPutAll: (self htmlForString: ass value contents asString), '<P>';
			nextPutAll: '<A HREF=#TOP>Return To Top</A><P>'; cr; cr;
			nextPutAll:  '<HR>'; cr; cr].
	fs nextPutAll: self htmlFooter.
	fs close]! !


!Outline class methodsFor: 'instance creation'!
new
	"initialize me by default"

	^super new initialize! !

!Outline class methodsFor: 'loading'!
load: aFileName
	"read an outline in from the given file, using blank lines and double blank lines as key and entry separators"
	"Outline load: 'test.outline'."

	^self load: aFileName keySep: '
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'
		entrySep: '
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'! !

!Outline class methodsFor: 'loading'!
load: aFileName keySep: aKS entrySep: anES
	"Read an outline in from the given file, using the given key and entry separators"
	"Outline load: 'test.outline'."
	"Outline load: 'Squeak.outline"
	"Outline load: '/etc/passwd' keySep: ':' entrySep: (String with: Character cr)."

	| file org |
	file := FileStream oldFileNamed: aFileName.
	file ifNil: [^nil].
	org := self new.
	org name: aFileName.
	Cursor read showWhile:
		[org parseFrom: file
			keySeparator: aKS
			entrySeparator: anES].
	file close.
	^org! !

!Outline class methodsFor: 'class var accessing'!
default
	"Answer the default outline."
	"OutlineBrowser openOn: Outline default label: 'Squeak Outline' "

	^Default! !

!Outline class methodsFor: 'class var accessing'!
default: anOutline
	"Set the default outline."

	Default := anOutline! !


!PositionableStream methodsFor: 'accessing'!
upToAll: aCollection
	"Answer a subcollection from the current access position to the 
	occurrence (if any, not inclusive) of aCollection in the receiver. If 
	aCollection is not in the receiver, answer the entire rest of the receiver."
	"(ReadStream on: 'abcdefghijklmnop') upToAll: 'lmn' "
	"(ReadStream on: 'abcldefglmhijklmnop') upToAll: 'lmn' "
	"(ReadStream on: 'abcldefglmhijklmnop') upToAll: 'lqn' "

	| stream writer ch |
	stream := WriteStream on: String new.
		[stream nextPutAll: (self upTo: aCollection first).
		self atEnd
			ifTrue: [^stream contents].
		writer := WriteStream on: String new.
		writer nextPut: aCollection first.
		aCollection size - 1 timesRepeat:
			[ch := self next.
			ch isNil
				ifTrue: [stream nextPutAll: writer contents.
					^stream contents].
			writer nextPut: ch].
		writer contents = aCollection
			ifTrue: [^stream contents]
			ifFalse: [stream nextPutAll: writer contents].
		true] whileTrue! !


!ScreenController methodsFor: 'menu messages' stamp: 'stp 5/19/1998 22:31'!
openOutline
	"Create and schedule an outline browser."

	OutlineBrowser openSystemOutline! !

!ScreenController methodsFor: 'nested menus' stamp: 'stp 5/19/1998 22:31'!
openMenu
	"ScreenController new openMenu startUp"

	^SelectionMenu labelList:
		#(	'keep this menu up'

			'browser'
			'workspace'
			'file list'
			'file...'
			'open outline'
			'transcript'
			'selector finder'

			'simple change sorter'
			'dual change sorter'

			'project (mvc)'
			'project (morphic)'
			'project (construction)'
			)
		lines: #(1 8 10)
		selections: #(durableOpenMenu
openBrowser openWorkspace openFileList openFile openOutline openTranscript openSelectorBrowser
openSimpleChangeSorter openChangeManager
openProject  openMorphicProject  openConstructionProject )! !


!String methodsFor: 'testing'!
isString
	"Answer true."

	^true! !


!StringHolder methodsFor: 'accessing' stamp: 'stp 07/22/1998 20:19'!
contentsText: aText 
	"Set aText to be the contents of the receiver."

	contents _ aText! !


!OutlineBrowser methodsFor: 'accessing'!
currentCategory
	"Answer the selected category."

	^currentCategory! !

!OutlineBrowser methodsFor: 'accessing' stamp: 'stp 5/20/1998 00:09'!
currentCategory: aVal
	"Set the receiver's selected category."

	currentCategory = aVal
		ifTrue: [currentCategory := nil]
		ifFalse: [aVal isMorph
			ifTrue: [world ifNil:
					[self removeDependent: viewer].
				world := aVal.
				self addDependent: world].
			currentCategory := aVal].
	self changed: #currentCategory.
	self changed: #text! !

!OutlineBrowser methodsFor: 'accessing' stamp: 'stp 5/15/1998 23:45'!
currentCategoryIndex
	"Answer the selected category."

	currentCategory ifNil: [^0].
	^model indexOfKey: currentCategory! !

!OutlineBrowser methodsFor: 'accessing' stamp: 'stp 5/19/1998 15:13'!
currentCategoryIndex: aVal
	"Set the receiver's selected category."

	| cat |
	aVal = 0
		ifTrue: [currentCategory := nil]
		ifFalse: [cat := (model categoryAtIndex: aVal) key.
			self currentCategoryIndex = aVal
				ifFalse: [currentCategory := cat]
				ifTrue: [currentCategory := nil]].
	self changed: #currentCategory.
	self changed: #currentCategoryIndex.
	self changed: #text! !

!OutlineBrowser methodsFor: 'accessing'!
model: anOutline
	"Set the receiver's model."

	model := anOutline.
	anOutline addDependent: self! !

!OutlineBrowser methodsFor: 'accessing' stamp: 'stp 5/20/1998 00:00'!
viewer: aView

	viewer := aView! !

!OutlineBrowser methodsFor: 'organization list'!
organization: anOrg
	"stuff the model's outline"

	^model organization: anOrg! !

!OutlineBrowser methodsFor: 'organization list'!
organizationList
	"return the model's list"

	^model organizationList! !

!OutlineBrowser methodsFor: 'organization list' stamp: 'stp 02/15/98 0-23:'!
organizationMenu
	"Answer the menu for use in the list view"

	currentCategory == nil
		ifTrue: [^SelectionMenu
					labels: 'add category\save\print\inspect' withCRs
					lines: #(1 3)
					selectors: #(addCategory saveAll printAll inspect)].
	^SelectionMenu
		labels: 'add category\rename\remove\save\inspect' withCRs
		lines: #(3 4)
		selectors: #(addCategory renameCategory removeCategory saveCategory inspect)! !

!OutlineBrowser methodsFor: 'organization list' stamp: 'stp 10/16/1998 23:55'!
organizationMenu: aMenu
	"Answer the menu for use in the list view"

	currentCategory == nil
		ifTrue: [^aMenu
					labels: 'add category\save\print\html\inspect' withCRs
					lines: #(1 4)
					selections: #(addCategory saveAll printAll storeHTML inspect)].
	^aMenu
		labels: 'add category\rename\remove\save\inspect' withCRs
		lines: #(3 4)
		selections: #(addCategory renameCategory removeCategory saveCategory inspect)! !

!OutlineBrowser methodsFor: 'text' stamp: 'stp 5/30/1998 05:37'!
acceptText: aText
	"Accept the new text as the model's text for the current category"

	currentCategory == nil ifTrue: [^false].
	model at: currentCategory put: aText copy.
	self changed: #text.
	^true! !

!OutlineBrowser methodsFor: 'text' stamp: 'stp 02/18/98 0-12:'!
contents
	"Answer the current category's text."

	currentCategory isNil
		ifTrue: [^'' asText]
		ifFalse: [^(model at: currentCategory) contents]! !

!OutlineBrowser methodsFor: 'text' stamp: 'stp 12/16/1999 07:16'!
exploreLocals
	"Explore the dictionary of local variables for this page."

	(model at: currentCategory) bindings explore.
!
]style[(13 109)f1bcblue;,f1! !

!OutlineBrowser methodsFor: 'text' stamp: 'stp 5/30/1998 05:17'!
text
	"Answer the current category's text."

	| cat |
	currentCategory isNil
		ifTrue: [^'' asText].
	cat := (model at: currentCategory).
	cat isMorph
		ifFalse: ["world ifNil: [viewer ]."
			^cat contents]
		ifTrue: [world ifNil:
			[world := cat.
			]]! !

!OutlineBrowser methodsFor: 'text' stamp: 'stp 12/16/1999 07:17'!
textMenu: aMenu
	"Answer the menu for the text view."
	"HACK..."

	| pMenu labs bytes sels ind |
	pMenu := ParagraphEditor yellowButtonMenu.
	labs := pMenu labelString.
	bytes := 'show bytecodes'.
	ind := labs findString: bytes.
	labs := labs copyReplaceFrom: ind to: ind + bytes size - 1with: 'explore locals'.
	sels := pMenu selections copy.
	sels at: 14 put: #exploreLocals.
	^aMenu labels: labs lines: pMenu lineArray selections: sels! !

!OutlineBrowser methodsFor: 'menu messages' stamp: 'stp 5/19/1998 22:17'!
addCategory
	"Prompt for adding a new category and allow the user to name it."

	| newCategory organization |
	newCategory :=  FillInTheBlank request: 'New Category' initialAnswer: (''). 
	newCategory = '' ifTrue: [^self].
	organization := model organization.
	self currentCategory isNil
		ifTrue: [model at: newCategory put: ((Smalltalk at: #Workspace) new contents: Text new)]
		ifFalse: [organization add: (newCategory -> (((Smalltalk at: #Workspace) new) contents: Text new)) 
				before: (model assAt: currentCategory)].
	currentCategory :=  newCategory.
	self changed: #organizationList.
	self changed: #text! !

!OutlineBrowser methodsFor: 'menu messages'!
inspect
	"Inspect the receiver's model"

	^ model inspect! !

!OutlineBrowser methodsFor: 'menu messages'!
inspectModel
	"Inspect the receiver's model"

	^ model inspect! !

!OutlineBrowser methodsFor: 'menu messages' stamp: 'stp 02/15/98 0-23:'!
printAll
	"Write out the whole outline as a plain text for printing."

	model printAll! !

!OutlineBrowser methodsFor: 'menu messages'!
removeCategory
	"prompt the user and remove the selected category"

	(self confirm: 'Are you certain that you
want to remove category ', currentCategory, '?')
		ifTrue: 
		[model removeKey: currentCategory.
		currentCategory :=  nil.
	].
	self changed: #organizationList.! !

!OutlineBrowser methodsFor: 'menu messages' stamp: 'stp 01/09/2000 21:28'!
renameCategory
	"prompt the user for a new name and rename the selected category"

	| newCategory item |
	newCategory :=  FillInTheBlank request: 'New Category' initialAnswer: currentCategory. 
	newCategory = '' ifTrue: [^self].
	item := model organization detect: [ :ass | ass key = currentCategory] ifNone: [nil].
	item ifNil: [^self].
	item key: newCategory.
	currentCategory :=  newCategory.
	self changed: #organizationList.! !

!OutlineBrowser methodsFor: 'menu messages'!
saveAll
	"save the whole outline"

	model saveAll! !

!OutlineBrowser methodsFor: 'menu messages'!
saveCategory
	"save the currentCategory"

	model saveCategory: currentCategory! !

!OutlineBrowser methodsFor: 'menu messages' stamp: 'stp 10/16/1998 23:54'!
storeHTML
	"Save the whole outline as an HTML Page."

	model storeHTML! !

!OutlineBrowser methodsFor: 'do it'!
bindingOf: aString
	"Answer the variable binding of the given name."

	^currentCategory isNil
		ifTrue: [super bindingOf: aString]
		ifFalse: [(model at: currentCategory) bindingOf: aString]! !

!OutlineBrowser methodsFor: 'do it'!
doItContext
	^ nil! !

!OutlineBrowser methodsFor: 'do it'!
doItReceiver
	^ model at: currentCategory! !

!OutlineBrowser methodsFor: 'do it'!
doItValue: ignored! !

!OutlineBrowser methodsFor: 'do it' stamp: 'stp 5/15/1998 23:50'!
okToChange
	^true 
"	self confirm: '
Do you really want to 
close this outline browser?
'
"
! !


!OutlineBrowser class methodsFor: 'view creation' stamp: 'stp 5/19/1998 19:59'!
openFile: aName
	"OutlineBrowser openFile: 'test.outline'"

	^self openOn: (Outline load: aName) label: aName! !

!OutlineBrowser class methodsFor: 'view creation' stamp: 'stp 05/07/1999 16:46'!
openFile: aName label: lab
	"OutlineBrowser openFile: 'test.outline'"

	^self openOn: (Outline load: aName) label: lab! !

!OutlineBrowser class methodsFor: 'view creation' stamp: 'stp 05/07/1999 16:55'!
openMOn: anOrganization label: aLabel
	"OutlineBrowser openMOn: Outline new label: 'Maintenance'"

	| me topView listView textView|
	me :=  self new model: anOrganization.
	topView := (SystemWindow labelled: aLabel) model: me.
	listView := PluggableListMorph
		on: me 
		list: #organizationList 
		selected: #currentCategoryIndex
		changeSelected: #currentCategoryIndex:
		menu: #organizationMenu:.
	textView :=  PluggableTextMorph 
		on: me
		text: #text
		accept: #acceptText:
		readSelection: nil
		menu: #textMenu:.
	topView addMorph: listView frame: (0 @ 0 extent: 1.0 @ 0.25).
	topView addMorph: textView frame: (0 @ 0.25 corner: 1 at 1).
	^topView openInWorld! !

!OutlineBrowser class methodsFor: 'view creation' stamp: 'stp 05/07/1999 16:54'!
openOn: anOrganization label: aLabel 
	"OutlineBrowser openOn: Outline new label: 'Maintenance' "
	"OutlineBrowser openOn: (Smalltalk at: #SystemOutline) label: 'Squeak Outline' "

	| me topView listView textView|
	World ifNotNil: [^self openMOn: anOrganization label: aLabel].
	anOrganization ifNil: [^self].
	me :=  self new model: anOrganization.
	topView := StandardSystemView new.
	topView model: me.
	topView label: aLabel.
	topView minimumSize: 200 at 300.
	listView := PluggableListView
		on: me 
		list: #organizationList 
		selected: #currentCategoryIndex
		changeSelected: #currentCategoryIndex:
		menu: #organizationMenu:.
	listView window: (0 @ 0 extent: 200 @ 80).
	listView borderWidthLeft: 2 right: 2 top: 2 bottom: 0.
	textView :=  PluggableTextView 
		on: me
		text: #text
		accept: #acceptText:
		readSelection: nil
		menu: #textMenu:.
	textView window: (0 @ 0 extent: 200 @ 300).
	textView borderWidthLeft: 2 right: 2 top: 2 bottom: 2.
	topView addSubView: listView.
	topView
		addSubView: textView
		align: textView viewport topLeft
		with: listView viewport bottomLeft.
	me viewer: textView.
	topView controller open! !

!OutlineBrowser class methodsFor: 'view creation' stamp: 'stp 05/07/1999 16:51'!
openSystemOutline
	"OutlineBrowser openSystemOutline"

	(Smalltalk includesKey: #SystemOutline)
		ifTrue: [self openOn: (Smalltalk at: #SystemOutline) label: 'Squeak Outline']! !


!Symbol methodsFor: 'testing'!
isSymbol
	"Answer true."

	^true! !


!Text methodsFor: 'testing'!
isString
	"Answer true (i.e., lie about it)."

	^true! !


!TextEmphasis class methodsFor: 'as yet unclassified' stamp: 'stp 5/19/1998 18:36'!
code: c
	^ self new emphasisCode: c! !

OutlineBrowser open: (Outline load: 'intro.outline') label: 'Introduction to Squeak'!
-------------- next part --------------
'From Squeak2.8alpha of 13 January 2000 [latest update: #1974] on 15 May 2000 at 6:27:01 pm'!

!DisplayScreen class methodsFor: 'snapshots' stamp: 'stp 5/15/2000 17:04'!
splash
	"Put up the pretty splash screen effect."
	"DisplayScreen splash"

	| logo disp box y text insetX insetX2 insetY |
	logo := ImageReadWriter formFromFileNamed: 'squeak.gif'.
	text := ImageReadWriter formFromFileNamed: 'text.gif'.
	box := Display boundingBox.
	y := box height // 2.

"Fade to black, then to blue"
	Display fadeImageFine: ((Form extent: Display extent depth: Display depth) 
				fillWithColor: Color black) at: 0 at 0.
	Display fadeImageFine: ((Form extent: Display extent depth: Display depth) 
				fillWithColor: Color blue) at: 0 at 0.
	
"roll logo across, wipe text"
	insetX := 64.
	insetX2 := insetX * 2.
	insetY := 16.
	disp := logo.
	insetX to: (text width + logo width + insetX2) by: 2 do:
		[ :x | 
		x \\ 8 = 0 ifTrue: [disp := logo rotateBy: x * 2].		" magic number..."
		disp displayAt: x at y.
		text displayOn: Display at: insetX2 at y+insetY 
				clippingBox: (insetX2 at y+insetY extent: x-insetX at text height)].
	(Delay forSeconds: 1) wait.
	Display restore! !

!DisplayScreen class methodsFor: 'snapshots' stamp: 'stp 5/15/2000 13:52'!
startUp  "DisplayScreen startUp"
	"DisplayScreen actualScreenSize"

	Display setExtent: self actualScreenSize depth: Display depth.
	Display beDisplay.
	DisplayScreen splash! !

!SystemDictionary class methodsFor: 'initialization' stamp: 'stp 5/15/2000 18:25'!
initialize
	"SystemDictionary initialize"

	| oldList |
	oldList _ StartUpList.
	StartUpList _ OrderedCollection new.
	"These get processed from the top down..."
	Smalltalk addToStartUpList: Delay.		"add this before DisplayScreen"
	Smalltalk addToStartUpList: DisplayScreen.
	Smalltalk addToStartUpList: Cursor.
	Smalltalk addToStartUpList: InputSensor.
	Smalltalk addToStartUpList: ProcessorScheduler.  "Starts low space watcher and bkground."
	Smalltalk addToStartUpList: FileDirectory.  "Enables file stack dump and opens sources."
	Smalltalk addToStartUpList: ShortIntegerArray.
	Smalltalk addToStartUpList: ShortRunArray.
	Smalltalk addToStartUpList: CrLfFileStream.
	oldList ifNotNil: [oldList do: [:className | Smalltalk at: className
						ifPresent: [:theClass | Smalltalk addToStartUpList: theClass]]].
	Smalltalk addToStartUpList: ImageSegment.
	Smalltalk addToStartUpList: PasteUpMorph.
	Smalltalk addToStartUpList: ControlManager.

	oldList _ ShutDownList.
	ShutDownList _ OrderedCollection new.
	"These get processed from the bottom up..."
	Smalltalk addToShutDownList: DisplayScreen.
	Smalltalk addToShutDownList: Form.
	Smalltalk addToShutDownList: ControlManager.
	Smalltalk addToShutDownList: StrikeFont.
	Smalltalk addToShutDownList: Color.
	Smalltalk addToShutDownList: FileDirectory.
	Smalltalk addToShutDownList: Delay.
	Smalltalk addToShutDownList: SoundPlayer.
	Smalltalk addToShutDownList: HttpUrl.
	Smalltalk addToShutDownList: Password.
	Smalltalk addToShutDownList: PWS.
	Smalltalk addToShutDownList: MailDB.
	Smalltalk addToShutDownList: ImageSegment.

	oldList ifNotNil: [oldList reverseDo: [:className | Smalltalk at: className
						ifPresent: [:theClass | Smalltalk addToShutDownList: theClass]]]! !

SystemDictionary initialize!


-------------- next part --------------
A non-text attachment was scrubbed...
Name: squeak.gif
Type: image/gif
Size: 1957 bytes
Desc: Unknown Document
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20000516/c60142eb/squeak.gif
-------------- next part --------------
A non-text attachment was scrubbed...
Name: text.GIF
Type: image/gif
Size: 5167 bytes
Desc: Unknown Document
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20000516/c60142eb/text.gif
-------------- next part --------------
'Introduction'
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string: 'Introduction to Squeak in 4 easy steps

This outline introduces the main concepts of Squeak Smalltalk. Its contents are executable and you should try all our suggested exercises. There is much more to Smalltalk and the references listed at the end provide additional information.

' runs: (RunArray runs: #(281 ) values: ((OrderedCollection new) add: ((Array new: 1) at: 1 put: (TextFontChange fontNumber: 1); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'1: Objects and Messages'
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string: 'Part 1: Objects and messages

1. Everything in Smalltalk is on object, and all work is done by sending
messages to objects.

To execute the following examples,
- select the text using the left mouse button (as in a word processor)
- execute text with Print it command in right mouse button <operate> menu:

3 squared				"receiver is small integer 3"
''abc'' asUppercase		"receiver is string ''abc'' "
200 factorial

Smalltalk syntax: Object always comes first (receiver), message follows.

2. There are exactly three kinds of messages: Unary, binary, and keyword

Unary (message is a ''word'', there are no arguments):

	3 negated
	''abcdefg'' vowels

Binary (message is a special character such as + - , and it is followed by exactly one argument)

	3 + 5			"message (properly message selector) is +, argument is small integer object 5)
	''abc'' , ''xyz''		"message selector is , and argument is ''xyz'')

Keyword (message is one or more keywords (word followed by :), each keyword followed by argument)

	3 raisedTo: 17			"message selector is raisedTo: and argument is 17"
	3 between: 5 and: 10		"message selector is between:and: and arguments are 5 and 10"
	$d between: $a and:$r	"receiver is character d, message selector is between:and: and arguments are characters a and r"
	Dialog request: ''Your name, please'' initialAnswer: ''John''

3. Each message returns an object and messages can thus be combined

	(5 factorial) between: (3 squared) and: (3 raisedTo: 5)

4. Messages are executed from left to right; bracketed first, unary first,
binary next, keyword last

	3 + 2 raisedTo: 2 squared 
is the same as
	(3+2) raisedTo: (2 squared)

This rule applies to everything, there are no other message preferences. So

	5 + 3 * 4
is the same as
	(5+3)*4

5. A sequence of messages to the same receiver can be cascaded

In the following examples, select the two consecutive lines of code
(including the comment) and execute with Do it from <operate> menu. Look at
the Visual Launcher to see the result.

Transcript clear.		"Note period separating this statement from the next"
Transcript show: ''Hello world''

has the same effect as

Transcript clear;		"Note semicolon instead of period"
	show: ''Hello world''	"Receiver is not repeated"

6. Variables

You can assign an object to variable for later use. Object not assigned to a variable immediately become unavailble and are automatically removed by the garbage collector.
All variables must be declared before the first statement. The declaration lists variable names but does not specify any type.

| price tax total |
price := (Dialog request: ''Please enter price'' initialAnswer: ''100'') asNumber.
tax := (Dialog request: ''Please enter price %''  initialAnswer: ''10'') asNumber.
total := price + (price * tax / 100).
Transcript clear;
        show: ''price: '', price printString; cr;
        show: ''tax: '', tax printString; cr;
        show: ''total: '', total printString

' runs: (RunArray runs: #(2905 ) values: ((OrderedCollection new) add: ((Array new: 1) at: 1 put: (TextFontChange fontNumber: 1); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'2: Classes and Instances'
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string: 'Part 2: Classes and their instances

1. An object may have properties (state)

A person object may have a first name and a last name - two properties.
A book may have an author, a title, a publisher, and contents - four
properties.
To examine the properties of the obeject returned by the following
expression, execute with Inspect from the <operate> menu
3 @ 5
Rectangle origin: (3 @ 5) corner: (25 at 30)
The rectangle above is a composite object - its component have properties.
To see them, execute ''Dive'' in the <operate> menu of the inspector. (To
return to previous level, execute ''Pop''.)

2. Every object is an instance of a class

3 is an instance of class SmallInteger - check this by executing each of the
following lines with Print it
3 class
3 @ 5
Rectangle origin: (3 @ 5) corner: (25 at 30)
Question for you: What is the class of $3, the class of ''3'' ?

3. A class is a template for creating its instances

A class defines the instance variables in which an object stores its
properties, and the messages that the object understands. (definitions of
messages are called methods.)

To see the definition of a class, use the Browser. Open one from the
launcher (command Browse or button) and look at the definition of class
Point. (Execute Find from the <operate> menu of the upper left view).

Questions: What are the instance variables of classes Point and Fraction?

4. Smalltalk library of classes is divided into categories

Categories are shown in the upper left view. Each class is in a category,
categories don''t overlap.
The only purpose of categories is to group related classes.

Question: What are the categores of Rectangle, Date, String?

5. A class is an object and understands its own set of messages

Class messages are mostly used to create instances: print individually
Circle center: 23 @ 12 radius: 15
Time now
Date today
This message returns a Date object, an instance of Date, and you can send it
a Date instance messages such as
Date today previous: #Monday
Question: #Monday is not a string, what kind of object is it?
Class names begin with upper case letters so you can see that center:radius:
is a class message.
Sometimes, class messages return relevant related information. Print
Date daysInYear: 2000
This message returns

6. A class may have many methods; methods are thus grouped into protocols

Protocols are only for organizing methods, just like categories organize
classes. Use the Browser to view them.
In the Browser, the views at the top are (left-to-right):
- categories
- classes in selected category
- protocols in selected class
- methods in selected protocol (when you select one, the text view at the
bottom shows its definition)
Buttons instance and class are for selecting whether you want to see
instance methods or class methods.

Questions:
What are the class protocols of Date? What are its instance protocols?
What are the methods in the Date instance protocol inquiries?

7. Class hierarchy - inheritance

Every class (except one) has exactly one superclass and inherits its class
and instance methods and variables.
To see what it is, select the class in the Browser and look at the
definition in the text view at the bottom.
Question: What is the superclass of SmallInteger, Date, Rectangle?
If A is a superclass of B, B inherits all A definitions. If B is a
superclass of C, C inherits all B definitions, and thus all A definitions as
well. Inheritance is transitive.
Going up the inheritance chain, you eventually reach class Object, the
superclass of all classes. All classes inherit all definitions of Object.
To see the class hierarchy of a class (all its superclasses and subclasses),
select the class in Browser and select Hierarchy in the View menu bar
command (don''t select any protocols).
Question: What are all superclasses and subclasses of class Integer?

' runs: (RunArray runs: #(3832 ) values: ((OrderedCollection new) add: ((Array new: 1) at: 1 put: (TextFontChange fontNumber: 1); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'3: Important Classes and Methods'
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string: 'Part 3: Essential classes and methods

VisualWorks library contains too many classes for any one person to know.
The following are the essential one.
Note that there are not only more useful classes but also many more useful
messages. To find about them, use the Browser.

1. Object
All classes inherit its methods. The most common ones are

- printString - converts an object to a string as in
3 printString or (13 at 15)printString or
use it when you need a string :-)
Equality and equivalence (identity)
= means that two objects are equal in some programmer-defined way
== means that they are one and the same object.
So two book objects may be defined as equal when they have the same author
and title. Then two books with the same author and title but different
publisher will be equal but not equivalent.
~= means not equal
~~ means not equivalent

2. Numbers
This is a group of classes including integers, floats, fractions,
fixed-point numbers, complex numbers (extension from included parcel - see
later), and others. Numbers have the obvious protocols for arithmetic and
mathem
atical functions. Check them out, for example, in class ArithmeticValue and
try (Print it)
3 + 6 / 5
15 log
0.3 sin

3. Strings, symbols, characters, dialogs

Strings understand messages for inserting substrings, searching, and other
useful things. Look at the protocols in class String and its superclasses
and try the following with Print it:

''abc'' < ''xyz''
''abcdefg'' findString: ''de'' startingAt: 1        "Important: Indexed
collections of objects such as strings begin at index 1"
''abcdefg'' size

A string is a collection of characters and literal characters are obtained
as in
$a
$3
Character is a subclass of Magnitude (as is Date and Time and all number
classes) and can thus be compared as in
$a < $d
Some useful characters can be obtained from the class using class messages
such as
Character cr
Character esc

Symbols are just like strings but they are unique whereas strings are not.
Try

''abc'' = ''abc''
''abc'' == ''abc''
and (for symbols)
#abc = #abc
#abc == #abc

Symbols are required as arguments in some messages, but their main use is
for method selectors. So their instance protocols include
#+ isKeyword
#between:and: keywords
and others. Try them out.

Class Dialog contains a number of useful messages for obtaining data from
the user. All are class messages. Try

Dialog request: ''What is your name?'' initialAnswer: ''Mr. T''     "Returns a
string"

Dialog          "Returns selection given by the values: argument"
                choose: ''Which one do you want?''
                fromList: #(''first'' ''second'' ''third'' ''fourth'')
                values: #(1 2 3 4)
                lines: 8
                cancel: [#noChoice]

Dialog confirm: ''Delete all horrible memories?''         "Returns true or
false"

Dialog warn: ''This is a warning''        "Returns nil - the UndefinedObject"

4. Boolean

Classes True and False. Used mainly for control of flow. Try
(4 < 5) ifTrue: [Transcript clear; show: ''4 is less than 5'']
(14 < 5) ifTrue: [Transcript clear; show: ''14 is less than 5'']
(4 < 5) ifTrue: [Transcript clear; show: ''4 is less than 5'']
                ifFalse: [Transcript clear; show: ''4 is NOT less than 5'']
(14 < 5) ifTrue: [Transcript clear; show: ''4 is less than 5'']
                ifFalse: [Transcript clear; show: ''4 is NOT less than 5'']

The construct including statements in square brackets is called a block
closure (or simply a block). A block is an object containing several
statements that are evaluated as dictated by the program.
You can also apply logical operations such as
(3 < 4) & (5 < 6)               "logical AND"
(3 < 4) | (5 < 6)               "logical OR"
(3 < 4) not                     "logical negation"

And and not also have the following versions:
(3 < 4) and: [5 < 6]
(3 < 4) or: [5 < 6]

The first form evaluate both sides, the form with blocks does not evaluate
the block if it is not necessary.
Question: Write a test to check that the ''partially evaluating'' version does
not evaluate the block when not necessary.

5. Blocks

Blocks are instances of class BlockClosure. They are used for many things
but one of the most common uses is iteration - evaluation of a block over
and over while a condition holds, does not hold, etc. Try the following c
ode fragments:
| count |
count := 0.
[count < 100] whileTrue: [count := count + 1].
Transcript clear; show: count printString

| count |
count := 0.
[count squared > 100] whileFalse: [count := count + 1].
Transcript clear; show: count printString

| count |
count := 0.
[count := count + 1. count < 100] whileTrue.
Transcript clear; show: count printString

Transcript clear.
3 timesRepeat: [Transcript show: ''Testing!''; cr]

Transcript clear.
1 to: 5 do: [: n| Transcript show: n printString; tab; show: n squared
printString; cr]

This block has a block argument. That''s because the definition of message
to:do: requires it. In this case, the argument simply assumes consecutive
values of 1, 2, and 3.
Question: Is there a method that allows you to specify the step. (Hint:
Think of the class in which it would be defined.)
6. Collections

Collections are one Smalltalk''s greatest strengths. They include collections
with indexed elements (array, ordered collection, sorted collection, and
others), and unordered collections (such as sets and dictionaries). Ind
exed collections are indexed from 1.

The main protocols are
creation: typically use new or new: as in (try it)
Array new: 5
OrderedCollection new

converting: convert one kind into another - try and observe the result
#(13 56 23 8) asSortedCollection                "the receiver is a literal
array"
#(1 1 1 3 5 6 6 2 2) asSet

enumeration: accessing collection elements and possibly doing something with
them. Try the following:

Transcript clear.
#(1 2 3 4) do: [:element| Transcript show: element squared printString; cr]
"use Do it"

#(1 5 2 89 34 53) select: [:element| element > 28]
"use Inspect or Print it"
#(1 5 2 89 34 53) reject: [:element| element > 28]
"use Inspect or Print it"
#(1 5 2 89 34 53) collect: [:element| element > 28]
"use Inspect or Print it"

All collections understand all these messages and all Smalltalk programmers
use them extensively.
Check the enumeration protocol of Collection and its subclasses for more.

testing: mainly testing whether a collection contains an element. Try
#(1 2 3 4 5) includes: 4
#(1 2 3 4 5) contains: [:number| number squared > 50]

Briefly about specific collection classes:
Collection is an abstract class - it has no instances and its only purpose
is to define everything that all collections share. Its most important
concrete subclasses are

Array - fixed size, very efficient in operation, automatically checks that
index is within bounds. Cannot grow.
OrderedCollections - similar to Array but can grow - grows automatically
when its curent capacity is filled.
SortedCollection - like OrderedCollection but automatically sorts its
elements. By default uses sort block
[:element1 :element2 | element1 < element2]
to decide whether element1 should be located before element2 or not. But you
can define your own sort block, as in
#(1 2 3 4 5 6 7 8) asSortedCollection: [:x :y| (x rem: 4) < (y rem: 4)]
"What is this? Try it."
Set - unordered collection, no index, automatically eliminates duplicates:
#(1 1 1 2 2 2 3 3 3) asSet
Dictionary - a set of Associations, where an association is a key-value
pair, as an entry in a dictionary. Try
Dictionary withKeysAndValues: #(''overdo'' ''do to death, go to extremes''
''overheated'' ''agitated, excited'' ''playmate'' ''buddy, companion'')

' runs: (RunArray runs: #(7596 ) values: ((OrderedCollection new) add: ((Array new: 1) at: 1 put: (TextFontChange fontNumber: 1); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
'4: Developing an Application in Squeak'
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string: 'Part 4: Developing a Smalltalk application

 What does it mean to develop a Smalltalk application?

A Smalltalk application is a collection of classes and when the application
runs, it creates objects that send messages to one another. There is no
''main program'' or ''main object''.
Typically, an application has a user interface with one or more windows, and
its operation is triggered by user actions.
Most of the classes in the application come from the library (numbers,
windows, etc.), some may be extended by the programmer, and some classes are
typically developed specifically for the application - for example Book,
Patron, Clerk, and Catalog for a book library application.
Classes are typically divided into two groups - the domain classes that
represent objects from the problem domain (such as Book, Patron, Clerk, and
Catalog above), and user interface classes (windows with widgets).
Typically, an application is started by sending the open message to its main
window. As an example, the Browser is an application and you can open it by
executing (with Do it)
FullSystemBrowser open
or, for a different configuration
FullSystemBrowser openOnAllNamespaces

2. Defining a new method
To define a new method, select either the instance or the class view in the
Browser, select a protocol (to create a new protocol, use Add in the
protocol view), and then write the method according to the template, as in (
presumably to be defined in ArithmeticValue)

cubed
"Calculate the cube of a number"
        ^self * self * self

Then click Accept in the <operate> menu and if you have not made any
mistakes, the new mehod will be added to the library. (To save it in the
''image'' file, you must save from the launcher, either now or later, using
Save
as, or you can save on exit.)
A few notes:
- self refers to the receiver, as an example, in 3 cubed, self would be 3
- ^ means ''return the result of the following expression. This cause the
method to terminate execution and exit, returning the specified result. If
you don''t exit with the ^ operator, the method will return the receiver.
To see the difference, look at method clear in class TextVCollector (defines
the Transcript and does not use the ^ operator) and use Print it to evaluate
Transcript clear
It returns the sender - a description of the Transcript.

3. Debugging
Your method may not work the first time. If this happens, Smalltalk will
open an Exception window that can be used to open the debugger to see what
is wrong and made corrections. The Exception window also opens if you sen
d the wrong message to the wrong object. Try

3 asUppercase

and you will get the exception SmallInteger doesNotUnderstand #asUppercase.
If you open the debugger, you will see a stack of messages currently active,
with the failing message near the top. If you select it, you will se
e its definition.
You can also insert a ''breakpoint'' to interrupt execution at some point and
continue executing step by step. Try

| price tax total |
price := (Dialog request: ''Please enter price'' initialAnswer: ''100'')
asNumber.
tax := (Dialog request: ''Please enter price %''  initialAnswer: ''10'')
asNumber.
self halt.
total := price + (price * tax / 100).
Transcript clear;
        show: ''price: '', price printString; cr;
        show: ''tax: '', tax printString; cr;
        show: ''total: '', total printString

Smalltalk will open an Exception window saying ''Halt encountered''. Open the
debugger, select ''unbound method'' (that''s the code from this workspace, and
continue executing it using either Step or Send - try it. The view at
 the bottom are inspectors on the instance variables of the receiver (left)
and temporary variables and message arguments (right).
You can change the code of the method (execute Accept when done) and
continue. You can also change the values in the two inspectors at the
bottom.

4.Defining a class

Class are collected in namespaces. A namespace is simply a way to get around
the problem that in previous versions of VisualWorks, class names had to be
unique. This meant that two different applications could only be com
bined if their developers didn''t use the same name for any of the classes in
their respective products. A namespace makes it possible to ignore class
names in other namespaces - within one namespace, class names must be u
nique, but two different namespaces may contain classes with identical names
without any conflict.
To create a class, you must thus decide on the namespace - either use an
existing one or create a new namespace. See on-line help for details.
The next step is to decide on a category for your class. Select an existing
one if appropriate, or create a new one if necessary, using the <operate>
menu in the category view of the Browser.
The next decision is to select the superclass of your new class. A subclass
is generalization, and a subclasses is specialization. So your superclass
should be a class that performs a more general purpose than your new cl
ass. As an example, Vehicle and Car are a reasonable superclass - subclass
pair. Similarly Account and SavingsAccount.
If you can''t think of a suitable existing superclass, make your class a
subclass of Object.
Next, fill in the template for a new class. It appears in the Browser when a
category is selected but no class. It looks like this:
Smalltalk.Root defineClass: #NameOfClass
        superclass: #{NameOfSuperclass}
        indexedType: #none
        private: false
        instanceVariableNames: ''instVarName1 instVarName2''
        classInstanceVariableNames: ''''
        imports: ''''
        category: ''Interface-Dialogs''
Edit the text by using your clas name on the first line, superclass name on
the second line, and adding instance variables on the fifth line. (The rest
are more advanced parameters that you initially don''t need.) Then exe
cute Accept from the <operate) menu.
And then add instance and class protocols as necessary.

5. Developing an application

Developing an application means extending existing classes and adding new
ones. This subject is beyond the scope of this introduction but many
Smalltalk programmers like to use the very direct methodology known as
Extreme Programming or XP and described in Kent Beck''s book referenced
below.
In developing the application, you will probably first develop and test
domain objects, and then implement the user interface. Developing the user
interface is relatively easy with the UIPainter tool of VisualWorks that
allows you to ''paint'' windows with widgets on the screen and link them with
your domain objects. The on-line help accessible from the launcher explains
the details.

' runs: (RunArray runs: #(6624 ) values: ((OrderedCollection new) add: ((Array new: 1) at: 1 put: (TextFontChange fontNumber: 1); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-


More information about the Squeak-dev mailing list