[ENH] OutlineBrowser

Stephen T. Pope stp at create.ucsb.edu
Sat Dec 4 03:06:26 UTC 1999


--------------108CCEC95E79F85A72D1BA80
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit



The attached files are a stand-alone file-in of the Outline and
OutlineBrowser classes and a simple version of the SystemOutline (based
on the standard Squeak readme files) as an example of a useful outline.

Bug reports or enhancements are welcome...

-- 

stp
  Stephen Travis Pope
  stp at create.ucsb.edu -- http://www.create.ucsb.edu/~stp
--------------108CCEC95E79F85A72D1BA80
Content-Type: text/plain; charset=us-ascii; x-mac-type="54455854"; x-mac-creator="522A6368";
 name="Outlines.3Dece650pm.cs"
Content-Transfer-Encoding: 7bit
Content-Description: Unknown Document
Content-Disposition: inline;
 filename="Outlines.3Dece650pm.cs"


'From Squeak2.6 of 11 October 1999 [latest update: #1559] on 3 December 1999 at 6:50:13 pm'!
Model subclass: #Outline
	instanceVariableNames: 'organization fileName keySeparator entrySeparator '
	classVariableNames: 'Default '
	poolDictionaries: ''
	category: 'Interface-Outlines'!
Outline class
	instanceVariableNames: ''!
Browser subclass: #OutlineBrowser
	instanceVariableNames: 'model currentCategory viewer world '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Interface-Outlines'!
OutlineBrowser class
	instanceVariableNames: ''!

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

	^ false! !


!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 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: 'stgp 11/19/1998 22:20'!
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.
	Cursor write showWhile:
		[organization do:
			[ :ass |
			ass key storeOn: aFS.
			aFS nextPutAll: keySeparator.
			ass value storeOn: aFS.
			aFS nextPutAll: entrySeparator]].
	aFS close.! !

!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]!
]style[(9 860)f1bcblue;,f1! !


!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 12/3/1999 18:22'!
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 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 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 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'!
textMenu
	"Answer the menu for the text view."

	^SelectionMenu
			labels: 'again\undo\copy\cut\paste\do it\print it\inspect\accept\cancel' withCRs
			lines: #(2 5 8)
			selectors: #(again undo 
				copySelection cut paste 
				doIt printIt inspectIt 
				accept cancel )! !

!OutlineBrowser methodsFor: 'text' stamp: 'stp 5/15/1998 23:36'!
textMenu: aMenu
	"Answer the menu for the text view."

	^aMenu
			labels: 'again\undo\copy\cut\paste\do it\print it\inspect\accept\cancel' withCRs
			lines: #(2 5 8)
			selections: #(again undo 
				copySelection cut paste 
				doIt printIt inspectIt 
				accept cancel )! !

!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 12/3/1999 18:29'!
renameCategory
	"prompt the user for a new name and rename the selected category"

	| newCategory assoc |
	newCategory :=  FillInTheBlank request: 'New Category' initialAnswer: currentCategory. 
	newCategory = '' ifTrue: [^self].
	assoc := model organization detect: [ :ass | ass key = currentCategory] ifNone: [nil].
	assoc ifNil: [^self].
	assoc 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 12/3/1999 18:33'!
openSystemOutline
	"OutlineBrowser openSystemOutline"

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

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


Smalltalk at: #SystemOutline put: (Outline load: 'Squeak2.6.outline')!

OutlineBrowser openSystemOutline!

--------------108CCEC95E79F85A72D1BA80
Content-Type: text/plain; charset=iso-8859-1; x-mac-type="54455854"; x-mac-creator="522A6368";
 name="Squeak2.6.outline"
Content-Transfer-Encoding: quoted-printable
Content-Description: Unknown Document
Content-Disposition: inline;
 filename="Squeak2.6.outline"


'Welcome to Squeak 2.5'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: '       Squeak 2.6
                   (c) 1996 Apple Computer, Inc.
                     (c) 1997-1999 Walt Disney
                       ALL RIGHTS RESERVED.
Squeak is a work in progress based on Smalltalk-80, with which it is stil=
l reasonably compatible.

The Interpreter
Squeak includes a complete simulation of its ObjectMemory, Interpreter, a=
nd BitBlt, each of which began with the "Blue Book" spec. The object memo=
ry is a completely new direct-pointer object model with compact headers a=
nd an incremental compacting garbage collector. The interpreter has been =
worked over for efficiency, and improved handling of 32-bit LargeIntegers=
 allows it to simulate itself at reasonable speed. See the various class =
comments in the Squeak Interpreter category. The Squeak system also inclu=
des a translator to C. Together these can generate complete C source code=
 for the interpreter. If you take advantage of this capability to port th=
e system to other platforms, we would like to hear about it.

Color graphics
Squeak''s BitBlt has been retrofitted with support for variable-depth col=
or and many performance enhancements. It has several added functions incl=
uding a paint mode that supports transparency, and an alpha-blend mode fo=
r 32-bit color. It also has a "warp-drive" variant that will scale, rotat=
e, and otherwise deform bitmaps in a single pass. Interested users will w=
ant to try
	Display restoreAfter: [WarpBlt test1], and
	Display restoreAfter: [WarpBlt test3].
The warp drive is also capable of limited anti-aliasing. You can compare =
the results by executing
	Display restoreAfter: [WarpBlt test12].
Two other demos of possible interest (see comments) are
	Display restoreAfter: [BitBlt alphaBlendDemo], and
	Display restoreAfter: [BitBlt antiAliasDemo].

Sound
Squeak includes base classes and some simple primitives that support real=
-time background generation of sound and music. Interested users will wan=
t to try
	AbstractSound stereoBachFugue play.
Squeak also includes a MIDI file reader. If you are connected to a networ=
k, you should try one of...
	MIDIFileReader playURLNamed:
	  ''http://squeak.cs.uiuc.edu/Squeak2.0/midi/wtellovr.mid''.
	MIDIFileReader playURLNamed:
	  ''http://squeak.cs.uiuc.edu/Squeak2.0/midi/toccFugueDmin.mid''.
If you''re short on horsepower, you''ll do better with...
	MIDIFileReader playURLNamed: =

	  ''http://squeak.cs.uiuc.edu/Squeak2.0/midi/tlmnflut.mid''.
Of course, you can change the instrumentation, and even edit the instrume=
nts while these are playing.

Morphic
Morphic is a completely new graphics framework for Squeak. Examples can b=
e explored in the ''Play With Me'' windows, or by following the accompany=
ing Morphic scripting tutorial. We have loaded lots of things into Morphi=
c. It''s a little cluttered and a bit slow, but it''s an architecture we =
like, and we''ll be cleaning it up and tuning it over the next year.

Balloon
Squeak now includes a completely new outline-based graphics subsystem nam=
ed Balloon. Balloon graphics are independent of scale and rotation, and m=
ay be rendered simply or with 2 degrees of anti-aliasing. For a quick dem=
onstration, execute...
	(FlashMorphReader on: (HTTPSocket
		httpGet: ''http://www.audi.co.uk/flash/intro1.swf'' =

		accept:''application/x-shockwave-flash''))
	processFile startPlaying openInWorld.
This example also demonstrates that Squeak includes a fairly complete imp=
lementation of the ShockWave graphics file format, with conversion to Bal=
loon graphical objects. Since it''s all in Squeak, you can stop the playe=
r and take apart the morphic balloon objects.

Balloon has also been interfaced to TrueType outline fonts. There is an e=
xample in Play With Me - 3 (this uses 16-bit color).

Balloon-3D
New to Squeak 2.4 is the first Balloon 3D engine. It can be seen in actio=
n by entering Play With Me - 7, and running the script there. Note: you M=
UST have a Squeak 2.4 or later VM and a Squeak3D plugin in the same folde=
r with it to run PWM-7.

Networking
This version of Squeak supports sockets. If you are on a web-connected ne=
twork, you might want to try...
	HTTPSocket httpShowGif:
		''http://squeak.cs.uiuc.edu/Squeak2.0/midi/Squeakers.GIF''.
There are many more examples in the Socket class.

Also included with this release is a complete WikiWiki server. See the ac=
companying information on WikiWiki.

Squeak''s FileList has also been extended with network access. This featu=
re is newly added, and will probably require a little shaking down and tu=
ning.
' runs: (RunArray runs: #(17 240 15 720 14 755 5 729 7 358 7 805 10 245 1=
0 503 ) values: ((OrderedCollection new) add: ((Array new: 3) at: 1 put: =
(TextFontChange basicNew instVarAt: 1 put: 5; yourself); at: 2 put: (Text=
Color basicNew instVarAt: 1 put: (Color r: 1.0 g: 0.0 b: 0.0); yourself);=
 at: 3 put: (TextEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put:=
 true; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontCha=
nge basicNew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new:=
 2) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); a=
t: 2 put: (TextEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: t=
rue; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChang=
e basicNew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 2=
) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); at:=
 2 put: (TextEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: tru=
e; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange =
basicNew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 2) =
at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); at: 2=
 put: (TextEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: true;=
 yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange ba=
sicNew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 2) at=
: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); at: 2 p=
ut: (TextEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: true; y=
ourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange basi=
cNew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 2) at: =
1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); at: 2 put=
: (TextEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: true; you=
rself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange basicN=
ew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 2) at: 1 =
put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); at: 2 put: =
(TextEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: true; yours=
elf); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange basicNew=
 instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 2) at: 1 pu=
t: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); at: 2 put: (T=
extEmphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: true; yoursel=
f); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange basicNew i=
nstVarAt: 1 put: 1; yourself); yourself); yourself))); instVarAt: 3 put: =
nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'About Squeak 2.5'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Basic help information is now available in two external media:

The ReadMe.txt file. If all else fails, read this in a text editor. You s=
hould be able to see it in a Squeak window by clicking on...
	(FileStream oldFileNamed: ''ReadMe.txt'') edit.

The latest version of the Squeak Release documentation on the web, as mai=
ntained by The Squeak Team. These pages are more likely to be current, as=
 they are maintained in a Swiki server. We thank Mark Guzdial at Georgia =
Tech for making this server available. You can browse it in any web brows=
er using the URL below, or, if you enjoy the thrill of running thousands =
of lines of brand-new code, just click on...
	http://minnow.cc.gatech.edu/SqueakDoc.1

In addition, you will likely want to browse other sites on the web, inclu=
ding...
http://www.squeak.org/ -- The Squeak home page and UIUC archive
http://minnow.cc.gatech.edu/squeak.1 -- The Squeak Wiki at Georgia Tech.
http://www.create.ucsb.edu/squeak/ -- Stephen Pope''s U.S. mirror site at=
 UCSB.
http://www.sugarWeb.com -- Smalltalk User Group of Argentina (SUGAR)

European users may wish to use:
ftp://alix.inria.fr/pub/squeak -- Ian Puimarta''s site at INRIA in France=
 for Mac and Unix versions of Squeak.
ftp://ftp.cs.uni-magdeburg.de/pub/Smalltalk/free/squeak/win32 -- Andreas =
Raab''s site at Univ. of Magdeburg in Germany for Mac and Windows version=
s of Squeak.
' runs: (RunArray runs: #(201 45 416 39 675 ) values: ((OrderedCollection=
 new) add: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt:=
 1 put: 1; yourself); yourself); add: ((Array new: 2) at: 1 put: (TextFon=
tChange basicNew instVarAt: 1 put: 1; yourself); at: 2 put: (TextDoIt bas=
icNew instVarAt: 1 put: '(FileStream oldFileNamed: ''ReadMe.txt'') edit.'=
; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange b=
asicNew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 2) a=
t: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); at: 2 =
put: (TextURL basicNew instVarAt: 1 put: 'http://minnow.cc.gatech.edu/Squ=
eakDoc.1'; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFon=
tChange basicNew instVarAt: 1 put: 1; yourself); yourself); yourself))); =
instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'The Squeak User Interface'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'The Squeak Screen
To resize the Squeak Screen, click and drag the bottom right corner (just=
 pretend it has a grow box), and then choose ''restore display'' from the=
 screen menu. We''ll clean this up soon.

Windows
To close a window, click in the left box of its title bar. To collapse or=
 expand a window, click in the right box. To change the name of a window,=
 click in its title, and edit the name in the resulting dialog box.

Windows can be moved by dragging their title bar, provided that you click=
 in the shaded regions. To change the size of a window, move the mouse ne=
ar a corner or border and, when the cursor changes, click and drag.

Panes
Many windows are made up of panes, and many of these have scroll bars on =
the left (naturally - that''s where most text is ;-). Scroll bars are div=
ided into 4 narrow strips, and the cursor changes to tell you which reagi=
on you are in. Three cursors inform you of normal up/down/jump scrolling =
(try them now), and the fourth indicates availability of a pop-up menu re=
lating to the pane you are in.

Menus
Pane menus (often different in different panes) can also be invoked by op=
tion-click (and hold) in most panes, and window menus can be invoked by c=
md-click. Many menu commands can also be invoked by cmd-key combinations,=
 indicated in the menus. The global ''screen menu'' can be invoked simply=
 by clicking in the gray area within the Squeak screen, but outside any S=
queak windows.

Color
Squeak graphics support 1, 2, 4, 8, 16, and 32-bit color. To change the r=
esolution of the Squeak screen, execute any of
	Display newDepth: 1.
	Display newDepth: 2.
	Display newDepth: 4.
	Display newDepth: 8.
	Display newDepth: 16.
	Display newDepth: 32.
Note that common choices are available in the screen ''do...'' menu. Natu=
rally, you will want some reasonable correspondence between this choice a=
nd the setting of your monitor.

The screen will consume more memory in higher resolutions, but Squeak is =
careful to use only 1-bit pixels for most text window images. The window =
menu offers a choice whether to save only two colors or all colors of a g=
iven window (as well as a coice of background shade).

Projects
Project windows are actually more like doors than windows, since you can =
enter them by clicking in the interior. You can create new ones by choosi=
ng ''open...project'' from the screen menu. To exit a project (and return=
 to its containing project), choose ''exit project'' from the screen menu=
=2E Each project maintains its own set of windows, its own set of changes=
, and its own screen color depth.

Typing
The _ character in Squeak is really an underbar; that''s how you type it.=
 Note that :=3D is an acceptable alternative for assignment.

The Squeak text editor supports many editing operations that can be invok=
ed by cammonad keys. For a full list of these operations, choose ''help''=
 from the screen menu, then choose ''command-key help''

' runs: (RunArray runs: #(17 187 7 434 5 399 5 382 5 709 8 398 6 334 ) va=
lues: ((OrderedCollection new) add: ((Array new: 1) at: 1 put: (TextFontC=
hange basicNew instVarAt: 1 put: 3; yourself); yourself); add: ((Array ne=
w: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yourself);=
 yourself); add: ((Array new: 1) at: 1 put: (TextFontChange basicNew inst=
VarAt: 1 put: 3; yourself); yourself); add: ((Array new: 1) at: 1 put: (T=
extFontChange basicNew instVarAt: 1 put: 2; yourself); yourself); add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 3; yo=
urself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange basic=
New instVarAt: 1 put: 2; yourself); yourself); add: ((Array new: 1) at: 1=
 put: (TextFontChange basicNew instVarAt: 1 put: 3; yourself); yourself);=
 add: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 pu=
t: 2; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChan=
ge basicNew instVarAt: 1 put: 3; yourself); yourself); add: ((Array new: =
1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yourself); yo=
urself); add: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVar=
At: 1 put: 3; yourself); yourself); add: ((Array new: 1) at: 1 put: (Text=
FontChange basicNew instVarAt: 1 put: 2; yourself); yourself); add: ((Arr=
ay new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 3; yours=
elf); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange basicNew=
 instVarAt: 1 put: 2; yourself); yourself); yourself))); instVarAt: 3 put=
: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Managing and Saving Changes'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Starting and Quitting
Obviously you have figured out how to start the system. The approved meth=
od is to double-click on an image, although if you have several different=
 interpreters, you may want to drag the image to the appropriate interpet=
er.

To quit a Squeak session, choose ''quit'' with or without saving from the=
 screen menu. If you save, your image file will be overwritten. You may c=
hoose ''save as...'' to write a newly named copy of your image and change=
s (see below).

Image File
All of the objects -- classes, dictionaries, windows and other objects th=
at make up the Squeak environment are stored in an image file (this must =
always be named ''SomeName.image''). For this reason, when you start up a=
n image, everything is right where you left it when you last saved the im=
age.

Sources and Changes
For various reasons, the source code associated with the image is stored =
in two other files. The code of the system as originally delivered (vers =
2.0) is stored in the file ''SqueakV2.sources'', and the sources for ever=
ything done since that time is in the changes file (which must similarly =
be named ''SomeName.changes'').

Storing the source code in a separate file has several advantages. To beg=
in with, if you have been working for a couple of hours, and your dog rol=
ls over the power cord, you will still have a sequential record of all yo=
ur program edits, and these can be perused and replayed with numerous too=
ls such as changes: post-snapshot log. This feature has also saved many a=
 hacker who got too adventurous in changing the system he or she was usin=
g.

Also, if you wish to run the system with severely limited resources, it c=
an be operated without any source code, owing to its ability to decompile=
 the bytecode methods into a readable and editable version of the origina=
l source code (only comments and temporary variable names are lost).

Finally, since the changes file does not consume memory space, Squeak kee=
ps a continuous log of all your program changes, and these can be examine=
d and reinstated at any time (see ''versions'' option in browser selector=
 pane).

FileOut, FileIn
In addition to the ''save'' command that saves the entire state of your S=
queak image, individual methods, categories and classes may be ''filed ou=
t''. This option is available in most browsers, and it results in the cre=
ation of a text file with an appropriate name, incorporating the code in =
question.

The format of this file is special, in that it can be read back into the =
same or another Squeak image to recreate those same classes and methods i=
n a new environment.

ChangeLists, ChangeSets, and ChangeSorters
A ChangeList is a method-by-method view of a fileOut. Note that the chang=
es-file record of all your program edits uses the same fileOut format, so=
 a ChangeList can browse the change history of any Squeak session. The re=
cent change log option of the changes... menu is one example; other examp=
les in ChangeList public access include viewing other Smalltalk source co=
de files. This can be easly invoked through the FileList ''browse changes=
'' option.

In addition to the sequential changes-file record of all changes, whateve=
r project you are in, a ChangeSet keeps a more dictionary-like record of =
what has been changed. This allows you to fairly easily make a fileOut of=
 just the most recent versions of a bunch of related changes that constit=
ute your work on that project.

ChangeSorters allow one to organize all system changes into a number of i=
ndependent ChangeSets. One word of caution: at the present, unaccepted ch=
anges in a changeSorter window will be lost if you exit the window and re=
turn later, due to over-ambitious automatic updating.

Projects offer a natural way of organizing related work, windows and chan=
geSets. The effect is almost like many separate images in one, except (!)=
 that all projects share the same code, regardless of where else it may b=
e changed.

Organizing your Disk (on the Mac)
Squeak will look for its sources file both in the folder in which the ima=
ge was started, and in the folder in which the VM exists. It is simplest =
to put the sources together with the VM, and then you can use any numbe o=
f image/changes pairs anywhere on your disk.

If you wish to maintain different versions of the VM on your disk, here i=
s the easiest way: put all VMs in a single folder, along with the sources=
=2E Then in any folder with images for version X, put an alias of the VM =
for version X, and drag your image onto the VM alias to start it.

' runs: (RunArray runs: #(21 4466 ) values: ((OrderedCollection new) add:=
 ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 3;=
 yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange ba=
sicNew instVarAt: 1 put: 2; yourself); yourself); yourself))); instVarAt:=
 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Pluggable Views'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Version 2.0 of Squeak includes a complete rewrite of all the MVC windo=
ws to use pluggable views. A pluggable view has a set of selectors that p=
arameterize its model interface in such a way that instances of the same =
view class can be used on many different models. This simplifies and fact=
ors the system -- we were able to reclaim about 50 classes (!) from the o=
ld MVC system in the course of this rewrite. More importantly, it left us=
 with only a handful of classes to convert in order to run all our existi=
ng development system in a morphic-only world. Nearly the entire view mec=
hanism has been funnelled down to
	PluggableListView
	PluggableTextView
	PluggableButtonView

for which we have written morphic counterparts,

	PluggableListMorph
	PluggableTextMorph
	PluggableButtonMorph.

' runs: (RunArray runs: #(792 ) values: ((OrderedCollection new) add: ((A=
rray new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; you=
rself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Morphic Squeak'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'It is possible in Version 2.0 to run the entire Squeak development env=
ironment in morphic. You do this by opening a morphic project, and choosi=
ng ''windows...'' from the morphic world menu (use ctrl-click). This part=
 of the system is still smoking -- essentially none of it existed a month=
 ago. Some parts are slow, some parts may fail, but we feel it is instruc=
tive to see an entirely new viewing mechanism running the same old MVC ap=
plications.

' runs: (RunArray runs: #(449 ) values: ((OrderedCollection new) add: ((A=
rray new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; you=
rself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Scripting and End-user Access'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Squeak Version 2 includes sketches of two entire end-user programming =
paradigms, intregrated with the morphic environment.

One is a wiring metaphor inspired by Fabrik, that allows simple component=
 assembly to be performed the way you put a stereo system together. The i=
mplementation is just a toy (no real dataflow model or encapsulation yet)=
 but you may enjoy the demonstration in Play With Me - 6.

The other is a tile-based interface that offers viewers and scriptors as =
iconic and active counterparts to Squeak''s textual and more passive insp=
ectors and browsers. It has been taken fairly far in a number of directio=
ns, as you may discover by following the introductory tour "Programming i=
n Morphic".


As an explorer of Squeak, you need to know that these environments are on=
ly sketches. We are excited about them. We are working actively on them. =
But they are not complete, they are not foolproof, and they are not well =
documented (but then what is?). We share them in the same spirit that we =
share Squeak: we invite you to play with us, to share our discovery, and =
perhaps to work with us as we move forward.

Programming in Morphic

Two quite different styles of programming in Morphic are available in Squ=
eak 2.0: "Classic Morphic Programming" and "Scripting with Players".


(I) Classic Morphic Programming

This is the kind of programming for which Morphic was originally designed=
, and excellent examples of clean and attractive style using that approac=
h can be found, for example, in BookPageSorterMorph and EnvelopeEditorMor=
ph.

In "Classic Morphic Programming" style, you define your own subclasses of=
 one or more generic Morph classes, and blend them into a working subsyst=
em. Here, you''re directly extending Morphic, in grand and time-honored S=
malltalk manner. The fundamental tool here is the Browser: you locate and=
 familiarize yourself with particular Morphic classes, and you then subcl=
ass the ones that you decide are appropriate for your application.

Most current Squeak users will prefer this traditional, mature, analytic,=
 browser-based Smalltalk approach,

If you''re still curious about the other style, read on...


(II) Scripting with Players -- The "User-Scripting" Style

The second style of programming is rather more informal, more like "scrat=
ch programming", somewhat comparable to what we Smalltalkers do when we u=
se a Workspace to construct and evaluate various lines of code for some e=
xploration or calculation in Smalltalk, and also comparable to the kind o=
f scripting done by users of systems like HyperCard and HyperStudio, etc.=


In the User-Scripting style, you construct surface graphics by directly a=
ssembling standard Morphic parts -- e.g. Rectangles, Images, Joysticks, e=
tc., by dragging them from a Parts Bin and arranging them as desired, and=
 then you add user-defined state and behavior by adding instance variable=
s and writing methods for "Players" who represent the individual morphs y=
ou wish to script.

The user thus does not directly subclass any particular kind of Morph, bu=
t rather she assembles? Morphs and gives them special state and behavior =
by associating them with "Players", which are the fundamental user-script=
able object types for User Scripting.

(The basic hookup is that every Morph can have, optionally, a Player as i=
ts "player", and every Player has an associated Morph that it "wears" as =
its "costume". Player itself is a class with lots of capability but very =
little instance state; user-defined Players are all implemented as compac=
t, single-instance subclasses of Player.)

' runs: (RunArray runs: #(1117 22 2408 ) values: ((OrderedCollection new)=
 add: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 pu=
t: 2; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChan=
ge basicNew instVarAt: 1 put: 3; yourself); yourself); add: ((Array new: =
1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yourself); yo=
urself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Blanket Disclaimer and Warning'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'In Squeak 2.2 we offer only a very early take on User Scripting. It ha=
s many rough edges, consumes lots of memory, can leave garbage around tha=
t will bloat your image,

It is tempting to dwell at length on "Disclaimers" about User Scripting, =
but we shall resist, beyond saying: this is early work, preliminary, much=
 in flux, with bugs, inconsistencies, significant gaps in design, and muc=
h that definitely will be changing before long.

If you wish to play with this stuff anyway, please do so in a spirit of h=
igh adventure, and be sure to protect yourself by doing your exploring in=
 a "throw-away" copy of your image, not in something you intend to save a=
nd build on. These are very early days!


Live Examples Coming Later

In due course, we will be placing on the Squeak web site some "live examp=
les" of use of "Player Scripting".

Eventually, we expect that full, interactive, mutlimedia-based Squeak tut=
orials, constructed entirely within the User Scripting domain, will be do=
wnloadable from the Web and will be immediately active and usable.

Technical limitations have kept us from doing that now, and space conside=
rations have kept us from implanting live examples in this release image.=


Good advice for the moment (except for the most adventurous) is to wait u=
ntil those live examples are available on the net. They should make it mu=
ch easier to absorb the basics of user-scripting, without having to wade =
through so much prose.

' runs: (RunArray runs: #(1440 ) values: ((OrderedCollection new) add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'The Three Basic Elements of User Scripting'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: '(1) The "Halo" -- lets you interact with any object you can touch (i.e=
=2E, any morph).

Alt-Click on a morph to bring up its halo. Successive alt-clicks will tra=
nsfer the halo to the next morph in the hierarchy -- experiment with this=
=2E Mouse over the various halo handles and read the help-balloons that w=
ill pop up to explain what each handle does. The name of the object that =
currently bears a halo will be seen at the base of its halo (and a click =
on the name will let you edit it.) Note: on a Mac, Alt-Click is Apple-Cli=
ck.


(2) The "Viewer" -- a dynamic graphical Inspector and Browser.

To get a Viewer for an object, drag from the cyan handle of its halo, and=
 a Viewer will stick to the mouse; place it wherever you wish.

Use the top part of the viewer to see and change properties of the object=
; use the bottom part of the viewer to see and invoke scripts for the obj=
ect. And use the buttons provided to add your own instance variables and =
your own methods to the object.


(3) The "Scriptor" -- a place to define, edit, test, save, and schedule a=
ctual scripts.

In order to succeed with user scripting, you will need to be able quickly=
 to get a Halo on any object, open a Viewer on any object, and get a Scri=
ptor for any object.

' runs: (RunArray runs: #(1239 ) values: ((OrderedCollection new) add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Getting started with Scripting'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Preliminaries

Choose "project (construction)" or "morphic construction window" from the=
 "open new" menu. Drag a Playfield (light green rectangle) from the parts=
 bin and drop it somewhere. Drag a Star from parts bin, and drop it in th=
e Playfield. Alt-click on the star to bring up its halo. Tear off a "view=
er" for the star by dragging from its cyan halo handle. Drop that viewer =
somewhere nearby (but preferably NOT in the Playfield)

Balloon help over the various crude controls in the Viewer will give you =
a general orientation.


Exercise 1 -- Relationship between an object and its viewer.

a. Play with the star via its halo. Drag it around, rotate it, resize it,=
 change other things via its red-dot halo menu, and watch the changes in =
the viewer. (You may need to click to another "bank" of parts to find the=
 group of information you''re interested in; use the little left and righ=
t arrows )

b. Play with the star via its viewer -- set its heading, its scale factor=
, its border width, its color, etc., and notice the effects on the star i=
tself.

Anything you can manipulate in the viewer can also be manipulated via scr=
ipts, and the viewer gives you access to scripting, as will be seen below=
=2E


Exercise 2 -- Sending requests directly to an object from its viewer.

In the lower part of the viewer are some sample lines of script. (Look at=
 the other banks to see the full vocabulary.)

You can click on any of the yellow "run it!" (exclamation point) buttons =
to send that line of command to the star. You can change the values of pa=
rameters there in the viewer.

Make the star turn by hitting ! for "star turn by 5". Hold down that ! bu=
tton to keep the star turning. Change the "5" to larger and smaller value=
s, and to negative values (by clicking on the little carets that control =
these things) and notice the effect

We''re not "scripting" yet because we''re still manually issuing one comm=
and at a time. Scripting is simply the process of assembling a sequence o=
f such commands in a "Scriptor", so they will all run, in sequence, when =
asked.


Exercise 3 -- Making a simple script

Drag from the "star turn by 5" line of the viewer, and drop onto the "des=
ktop" of the world. A Scriptor will result -- your own script, with the "=
star turn by 5" command already in there as its first line.

Drag from the "star forward by 5" line of the viewer, and drop that down =
inside the same Scriptor. You have now created a two-line script, that te=
lls the star to turn and move forward.

Let the cursor drift over each of the five buttons at the top of the Scri=
ptor, and read the balloon help of each to get an idea of what they do.

Click on the "!" and the script runs. Hold down, it keeps running. Change=
 the amount-to-turn-by and the amount-to-move-forward-by and run again.

Now try out various alternatives for when? the script should run. Initial=
ly, when it says "Normal" in the Scriptor, it''s just cold code waiting t=
o be called by someone, such as by the yellow "!" button.

So now make it run continuously -- choose "ticking" from the script-statu=
s menu that pops up when you click on "Normal". The star should now start=
 animating continuously, until you change its status or until you hit the=
 "Stop" button.

While it''s animating, change the parameters to "forward" and "turn" in t=
he Scriptor, to achieve different curvature and speed as it putts along.

Now for fun you might find the "Pen" area in the star''s Viewer, and chan=
ge the star''s "PenDown" to true. It will start laying down ink as it mov=
es, and now by adjusting parameters to move and turn in the Scriptor, you=
 can do a kind of scripted drawing.

Once you''ve started this, resist the temptation to change the pen''s col=
or and size in the viewer, because you might get distracted from the real=
 business of scripting.

Exercise 4 -- Hooking up a script to the user interface

Above, you made the star''s script "run all the time". Now go back to tha=
t same menu in its scriptor, and tell it to run on "mouseDown". Then mous=
e down on the star and watch the script run once.

Experiment with all the different choices -- mouseDown, mouseStillDown, m=
ouseUp, mouseEnter, mouseLeave. For "countinuous controls" such as scroll=
 bars and sliders, "mouseStillDown" is a good choice. For traditional "bu=
ttons", "mouseUp" is a traditional choice, though some controls feel bett=
er when they react on mouseDown.

You can have one script do something on mouseDown, and another on mouseUp=
, etc. One easy thing to try is to have the button change color (to somet=
hing darker, for example) upon mouseDown, and then change back to its ori=
ginal color upon mouseUp.


Exercise 5 -- Naming and saving a script.

Thus far, we''ve been working with a "temporary script". If you want to m=
ake it a permanent part of the object, choose "name and save this script"=
, and give it a name, such as "wander".

As soon as you''ve done this, you''ll see "wander" show up in the star''s=
 Viewer, alongside "forward by", "turn by", "make sound", etc.

Your "wander" script has now become a formal part of the object -- you''v=
e added a method to your object. It can now be deployed in viewers and sc=
riptors just like the system-defined scripts such as "forward by". And it=
 can be called by any other script.

Exercise 6 -- Substituting your own (textual) Smalltalk code

Here we will make a button that, when pressed, files out your current cha=
nge set. This is to illustrate the fact that you can always "escape" from=
 the tile-scripting framework to write your own arbitrary Smalltalk code.=


Get a parts bin.

Drag out an ellipse.

Drag out a "Text for Editing", and edit its text to say "File Out Changes=
".

Place the text over the ellipse, nicely centered (resize the ellipse as n=
eeded), then bring up the halo for the text and choose "embed" from its m=
enu, and embed it in the oval

=46rom the Text''s halo menu, choose "lock", so that the label won''t go =
into text-editing mode when the mouse comes down on it -- that''s not wha=
t we want here.

Next, bring up the ellipse''s halo and from the halo tear off a Viewer.

Name the ellipse "TestButton" (you can edit the name in the halo or at th=
e top of the viewer).

=46rom the viewer, tear off a "TestButton make sound croak" phrase, and d=
rop it on the world''s desktop. A scriptor opens up around it.

=46rom the scriptor''s menu, choose "name and save this script", and give=
 it a name like "doFileout".

=46rom the scriptor''s status menu, change "normal" to "mouseUp". This wi=
ll allow it to behave like a traditional button.

Test the button -- when you click on it, you should hear a croak sound.

Now chose "edit script textually" in the scriptor. This will give you a m=
essage-editing window in which you can type arbitrary Smalltalk code, and=
 it will be invoked whenever the script is triggered, be it via ticking, =
mouse actions, or being called from another script.

So now we type in whatever script we want, in plain Smalltalk, and submit=
 it. For the moment, you might edit the method to look like this:

doFileout Transcript cr; nextPutAll: ''Testing One Two Three...''. self b=
eep: ''croak''.

Now make sure a Transcript is open, and then try the script out. When you=
 click on the button, your message should show up in the Transcript and y=
ou should hear the croak.

This shows that the hookup is working. Now all that remains is to edit th=
e method to do something useful; in this case, it will look like this:

doFileout Smalltalk changes fileOut. self beep: ''croak''

Now, whenever you click on this button, the current change set will be fi=
led out and you will get a frogly confirmation.


(7) Adding instance variables to an object.

Hit the "add inst var" button in a Viewer to add an instance variable. Th=
e new instance variable starts out bearing a number, but you can change i=
ts type at any time. The type affects what form its readout (in the Viewe=
r) will take, and also where you can drop a tile representing the value i=
n a scriptor (numbers can be dropped on numbers, etc.)

If the type is a number, for example, you''ll get a textual readout with =
arrows to change the values manually. But if the type is "player" (i.e. o=
bject-reference, or "alias", if you will), then the readout is a graphica=
l thumbnail of the current referent.


(8) Scripting one morph to chase another

Get a morph (which you''ve named, say, "rabbit") busily animating with an=
 ever-ticking script involving "forward by" and either "turn by" or "boun=
ce".

Construct another Morph, name it "chaser" and script it to pursue the ani=
mating morph by giving it an ever-ticking script of the form:

chaser move toward dot

dot here refers to a little, faint object near the left edge of the windo=
w -- the one object in the world that starts out life with "identity", th=
is serves as the sample parameter for any Player-valued scripting element=
, just like the "5" in "forward by 5" serves as a sample parameter for "f=
orward by".

To make the object move not toward dot but rather toward the "rabbit" you=
''ve earlier animated, you''ll want to tear off a tile to represent the r=
abbit. There is a handle on the left edge of the Halo which, when you mou=
se down on it, will yield you just such a tile. Get it, and drop it over =
the "dot" tile, and it will replace that tile, so that your script will n=
ow read:

chaser move toward rabbit

[For extra credit, you can adjust the speed at which pursuit takes place =
by adding a numeric slot to chaser and calling it "speed".]


(9) Controlling an object with a Joystick

Generally you create scripts by dragging tiles from the viewer; this give=
s you simple scripts (which already are syntactically correct, and are fu=
lly functional) to start out with, and then you proceed to modify them.

One essential operation is dropping a tile into another tile bearing the =
same type of information; this results in the old tile being replaced by =
whatever you dropped.

Thus, for example,

Paint an airplane using the simple painting tools:

Drag from the crude green arrow in a Parts Bin (which indicates "paint a =
new object") and drop somewhere on a Playfield. Paint a rough airplane-li=
ke figure facing upward, then hit the "Keep" button. This is your airplan=
e. Open up its Viewer, and name it "airplane".

Make a script for the airplane that starts out: airplane forward by 5 air=
plane turn by 5

Get a fresh Joystick from the Parts Bin, and bring up a Viewer for it. Go=
 to the parts bank that shows the joystick-specific parts, "leftRight", "=
upDown", "angle", and "amount".

Drag from the tile showing the word "leftRight"; tiles for "joystick''s l=
eftRight" will stick to the mouse.

DROP that "joystick''s leftRight" directly onto the "5", to make the airp=
lane''s script read: airplane turn by joystick''s leftRight

Now make this script run all the time ("ticking"), and you can spin the a=
irplane by moving the joystick''s handle to the left or to the right.

A simple extension (left to the reader) is to add a "forward by" command =
to the same script, and have the amount by which it is to go forward be o=
btained from some other number that a Joystick is able to report. It''s f=
un to explore various possibilities for mapping the joystick parameters i=
nto the parameters for the "turn" and "forward" commands. Since the Joyst=
ick delivers four different numbers, you could hook them up to other thin=
gs about your airplane (such as its color or its scale factor) and end up=
 with some rather unusual controls!

' runs: (RunArray runs: #(11366 ) values: ((OrderedCollection new) add: (=
(Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; y=
ourself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'More about Morphic Scripting'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'About Assignment

The top part of the viewer consists of rows of the form:

airplane''s heading <- 0.

If you drag from the green-and-purple left-arrow, you''ll get an "assignm=
ent phrase", which is a line of code that lets you "assign a new value" f=
or the heading. Plop it down in a script just like any other command.

Actually, there are four kinds of assignment: simple assignment, incremen=
ting, decrementing, and multiplying; you move among them by hitting the c=
arets on the assignment tile in the Scriptor. A simple exploration will r=
eveal how they work, but be careful with the muliplying assignment -- you=
r numbers can quickly get big.



Advice, Bugs, Things To Avoid, etc.

(1) You will by now have noticed that when you drop a line of script on t=
he Morphic "desktop", it sprouts a "scriptor" around itself, ready for ed=
iting and running. This is often what you want, but when it gets annoying=
, which is to say, when you find you''d like to be able to drop naked lin=
es of script and have them stay as naked lines of script, for later use, =
you can drop them into any "Playfield" (PasteUpMorph) rather than onto th=
e World desktop, and you can avoid this sprouting. (Whether or not a Play=
field automatically expands a dropped phrase into a complete Scriptor is =
governed by the "automatic phrase expansion" option, which will be found =
in the its "playfield options" menu.)


(2) A nice standard kind of script for lots of experimentation is: star f=
orward by 10 "move forward ten units" star bounce silence "if hit wall of=
 container, bounce silently"


(3) Scripts that are "ticking" provide a "live" feel, making experimentat=
ion quite easy.


(4) Be sure to try out use of the "pen" for laying down color trails. The=
 "colorUnder" and "colorSees" tiles provide ways that objects can easily =
interact with their surroundings.


(5) The "conditional" in the tile-scripting system is the "Test/Yes/No" c=
omplex (your basic if/then/else); in the test pane go boolean-valued thin=
gs; into the Yes and No panes go any sequence of commands.

(6) When an object is scripted to handle the mouse, you won''t be able to=
 drag it with the mouse. To drag such an object, bring up its halo, and d=
rag it from its black-dot or brown-dot handle.


(7) At present, there is no protection against script cycles, so that you=
 can get yourself in trouble with two scripts or more scripts that end up=
 calling each other.


(8) Before trying to duplicate a scripted object, make sure that all its =
scripts are "saved and named", so that the duplicate you make will have t=
he same scripts.

' runs: (RunArray runs: #(2560 ) values: ((OrderedCollection new) add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Next Steps'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'This User-Scripting regime is still in its infancy, as is the document=
ation about how to use it. We put it out at this time only in hope that s=
ome users will find something of interest in spite of the rough state of =
the design and the code (and in spite of the numerous temporary perturbat=
ions it has caused to an otherwise elegant Morphic graphics system.)

Coming in the foreseeable future are extensions of the user-scripting des=
ign to cover "aliases", "collections", the "stack/card" dichotomy, file-b=
ased factoring of content, Finder-like analogies for content, integration=
 with projects, navigation morphs, integration with the more generic Morp=
hc inspector and browser tools, and more.

Much of this design space has been explored in various earlier prototypes=
 we''ve worked on, so we''re not starting from ground zero, but there is =
plenty of architectural work still to be done before we emerge with a cle=
an and minimal design that will extend user scripting to span the space o=
f the "multimedia, hypermedia, and simulation tool" that we believe it ma=
y become.

Many changes are on the way. We warmly welcome participation by the Squea=
k community as we pursue this work, which is quite at right angles to the=
 traditional course of Smalltalk. Just, please, don''t at this stage coun=
t on user-scripting to be compact, reliable, consistent, transportable, o=
r stable. If you can thrive on such slippery ice, please join us now! Oth=
erwise, give it a chance to mature over the coming months.

' runs: (RunArray runs: #(1492 ) values: ((OrderedCollection new) add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Brainstorming and Engineering'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'The Squeak team works in periods of expansion, when we try new approac=
hes and write lots of new code, and periods of reflection, where we re-fa=
ctor, clean up and document (well... sometimes ;-). It is important for c=
ritics to understand that the morphic system and the end-user programming=
 systems that are embedded in it, are still in an expanding brainstorming=
 phase. We know that the clean morphic protocols have become a huge, conf=
using hodge-podge.

But this is important. Morphic is being taken in new directions, includin=
g flexing, scripting, and viewing. When we have gained experience with th=
ese new areas, when we have learned from working with some real users, th=
en we will better understand the real kernel of this architecture, and we=
 can return to clean it all up and cast it clearly in the metaphor that w=
e don''t fully understand right now.

' runs: (RunArray runs: #(861 ) values: ((OrderedCollection new) add: ((A=
rray new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; you=
rself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Source Code Updates'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Tired of waiting months for the next release?

Now you can get code updates automatically loaded into any Squeak attache=
d to the internet. Choose ''update code from server'' in the ''help...'' =
menu. (Wait, or have a Transcript open to watch the progress.) The Squeak=
 team will be putting approved changes to Squeak on two servers, at UIUC =
and at WebPage.com. Updates are numbered and are loaded in order.

We''ve been using Updates in our group at Disney for six months and it ha=
s really improved our productivity. If you want to set up your own Update=
 server for your own organization, please contact Ted Kaehler. It is an e=
asy way to distribute changes to a group of people who all use Squeak.

' runs: (RunArray runs: #(698 ) values: ((OrderedCollection new) add: ((A=
rray new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; you=
rself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Two Virtual Machines'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'With the release of Squeak 2.0 we are including two complete copies of=
 the Squeak VM. The first, referred to generally as "Squeak VM 2.0" is si=
mply an updated version of the standard bytecode interpreter that we have=
 been using for the last year or so.

The second, referred to as "Squeak Jitter", translates Squeak bytecodes o=
n demand to a more efficient representation for faster execution. This pr=
oject is the work of Ian Piumarta at INRIA in France. While we and he hav=
e tested it quite thoroughly, you need to know that it is still in an ear=
ly experimental stage -- it is likely to be less stable than the normal i=
ntepreter. At the same time, "Jitter", as Ian affectionately calls it, do=
es run faster in many cases, and will probably show further substantial p=
erformance gains over the next couple of months.

If you are interested in Jitter, it is entirely written in Squeak, and ca=
n be browsed in the ''Squeak-Jitter'' category. If you are not interested=
, it can all be removed as described under "Image Size".

' runs: (RunArray runs: #(1022 ) values: ((OrderedCollection new) add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Image Size'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'We have intentionally included more features with the Squeak 2.2 relea=
se than most people will use. If space is of concern, many of these facil=
ities can be removed to produce a considerably smaller image.

We are in the process of sanitizing and automating this removal process. =
Right now, you can execute the following to achieve the approximate savin=
gs given...
	Smalltalk discardVMConstruction. "663k"
	Smalltalk discardSoundSynthesis. "330k"
	Smalltalk discardOddsAndEnds. "228k"
	Smalltalk discardNetworking. "261k"
	Smalltalk discardMorphic. "2,231k"
The above altogether saves around 3.5 megabytes. Executing
	Smalltalk majorShrink
will do even more and should yield a final image size of around 800k. The=
re will be loose ends in that image that may cause errors when you attemp=
t to use facilities that have been removed, but this is usually not fatal=
=2E We will be updating the various shrinking routines to improve this pr=
ocess, and they can be browsed in the ''shrinking'' category of SystemDic=
tionary.

Want to squeeze Squeak into a PDA? After executing the above shrinking ro=
utines, you can go on to execute
	Smalltalk abandonSources.
This will compile method temp names into a compact trailer on every metho=
d, allowing the entire system to be browsed by decompiling with temp name=
s preserved. This means there is no need to store the sources file on a v=
ery small machine. While comments are not available in system code after =
abandoning sources, all the code you write will be preserved properly in =
the changes file, so that you can upload it to a full Squeak when you ret=
urn from your backpack trip.

' runs: (RunArray runs: #(1624 ) values: ((OrderedCollection new) add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'The Wiki Wiki Server'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Swiki -- A Server of Web Pages That Any User Can Modify

Version 2 of Squeak includes a complete editable web server. Every web pa=
ge on a Swiki web site has a button that says, "Edit this Page". It gives=
 you the contents of the the page in a scrolling window. When you change =
it and "Save", the page is instantly changed. The user can work from any =
web browser. Changing a page is so easy enough that a workgroup or class =
will quickly create an evolving spiderwork of their own pages.

To start your own Swiki, see the instructions in (PWS class howToStart), =
and get a folder with necessary template files from...
 http://www.cc.gatech.edu/fac/mark.guzdial/squeak/pws/ =


Thanks to Mark Guzdial, Georg Gollmann, and Mark''s students, and to the =
father of WikiWiki, Ward Cunningham.

' runs: (RunArray runs: #(788 ) values: ((OrderedCollection new) add: ((A=
rray new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; you=
rself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Stylized Text and Links in Source Code'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Remember the discussion after OOPSLA about better documentation and na=
vigation? Thanks to the work of Ted Kaehler, this version of Squeak allow=
s creation of hyperlinks in text, and preserves them (and most text style=
s) in source code and class comments! This makes it possible to document =
Squeak more effectively than before, as you will see from the limited exa=
mples in the Sample Documentation window. Links can be created using CMD-=
6, and they can deactivated by selecting (with an extra leading character=
, or from back to front) and using CMD-0. Here is an example link: Text.

We hope over the next month or two to rewrite all class comments to take =
advantage of this new capability and establish a real "backbone" to Squea=
k''s on-line documentation. You will notice a new switch in the browser, =
suggested by Scott Wallace, that facilitates access to class comments for=
 just this reason.

If you never put links or emphasis in your source code, everything should=
 work just as before. FileOuts may include style information after each m=
ethod. If you need to bring a new fileOut into an older system, read the =
file ''readFileinsWithStyle.cs'' into your older system first.
' runs: (RunArray runs: #(1180 ) values: ((OrderedCollection new) add: ((=
Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); yourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'GUI Help'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Squeak GUI Help

Outline=1D=1D=1D=1D=1D=1D
	Basic GUI: Windows and Scrolling=1C=1C=1C=1C
	Menus
	Text Editor
	Launcher
	Getting More Help

Standard Lower-case command keys
a	Select all
b	Browse it
c	Copy
d	Do it
e	Exchange
f	Find
g	Find again
h	Set Search String
i	Inspect it
j	Again once
k	Set font
l	Cancel
m	Implementors of it
n	Senders of it
o	Spawn
p	Print it
q	Query symbol
r	Recognizer
s	Save (i.e. accept)
u	Align
v	Paste
w	Delete preceding word
x	Cut
y	Swap characters
z	Undo

Upper-case command keys
(Hold down Cmd & Shift, or Ctrl key)
A	Advance argument
B	Browse it in this same browser (in System browsers only)
C	Compare argument to clipboard
D	Duplicate
F	Insert ''ifFalse:''
J	Again many
K	Set style
L	Outdent (move selection one tab-stop left)
N	References to it
R	Indent (move selection one tab-stap right)
S	Search
T	Insert ''ifTrue:''
W	Selectors containing it
V	Paste author''s initials
<return>		Insert return followed by as many tabs as the previous line
		(with a further adjustment for additional brackets in that line)

esc		Select current type-in
shift-delete		Forward delete character (not currently undo-able)

[	Enclose within [ and ], or remove enclosing [ and ]
(	Enclose within ( and ), or remove enclosing ( and )  NB: use ctrl (
{	Enclose within { and }, or remove enclosing { and }
<	Enclose within < and >, or remove enclosing < and >
''	Enclose within '' and '', or remove enclosing '' and ''
"	Enclose within " and ", or remove enclosing " and "

1	10 point font
2	12 point font
3	18 point font (not in base image)
4	24 point font (not in base image)
5	8 point font (not in base image)

6	add color / make active
	(nb: to remove the active quality of text, you must select
	more than the active part and then use command-0)

7	bold
8	italic
9	narrow
0	plain text (resets all emphasis)
-	underlined
=3D	struck out

LauncherView Buttons
	Open Browser
		(PackageBrowser by default, or old Browser if LeftShift)
	Open File List
	Open Workspace
	Select from Changes Menu
	Save Snapshot
	Help
' runs: (RunArray runs: #(15 2 13 89 32 315 23 1336 20 153 ) values: ((Ar=
ray new: 10) at: 1 put: ((Array new: 1) at: 1 put: (TextFontChange basicN=
ew instVarAt: 1 put: 3; yourself); yourself); at: 2 put: ((Array new: 1) =
at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); yours=
elf); at: 3 put: ((Array new: 1) at: 1 put: (TextFontChange basicNew inst=
VarAt: 1 put: 2; yourself); yourself); at: 4 put: ((Array new: 1) at: 1 p=
ut: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); yourself); a=
t: 5 put: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: =
1 put: 3; yourself); yourself); at: 6 put: ((Array new: 1) at: 1 put: (Te=
xtFontChange basicNew instVarAt: 1 put: 1; yourself); yourself); at: 7 pu=
t: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: =
3; yourself); yourself); at: 8 put: ((Array new: 1) at: 1 put: (TextFontC=
hange basicNew instVarAt: 1 put: 1; yourself); yourself); at: 9 put: ((Ar=
ray new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 3; your=
self); yourself); at: 10 put: ((Array new: 1) at: 1 put: (TextFontChange =
basicNew instVarAt: 1 put: 1; yourself); yourself); yourself))); instVarA=
t: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'System Workspace'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: '        Squeak Version 1.1
			 September 24, 1996
   Copyright (c) 1981, 1982 Xerox Corp.
 Copyright (c) 1996 Interval Research Corp.
 Copyright (c) 1985-96 Apple Computer, Inc.
		  All rights reserved.

The Squeak team gratefully acknowledges contributions to this image by me=
mbers of the Homeworks project at Interval.

Changes and Files
Smalltalk noChanges.
Smalltalk condenseChanges
DisplayScreen removeFromChanges.
Smalltalk changes asSortedCollection
Smalltalk browseChangedMessages
(FileStream fileNamed: ''changes.st'') fileOutChanges.
(FileStream fileNamed: ''PenChanges.st'') fileOutChangesFor: Pen.
(FileStream oldFileNamed: ''Toothpaste.st'') fileIn.
(FileStream oldFileNamed: ''housekeeping.st'') edit.
FileDirectory filesMatching: ''*.st''
(FileStream oldFileNamed: ''listing29mar100pm.cs'') insertLineFeeds

Inquiry
InputState browseAllAccessesTo: ''SystemStartupList''.
Smalltalk browseAllCallsOn: #changed:.
Smalltalk browseAllImplementorsOf: #confirmFirstUseOfStyle
Smalltalk browseAllCallsOn:
	(Smalltalk associationAt: #Voices)
Smalltalk browseAllCallsOn:
	(Cursor classPool associationAt: #ReadCursor).
Smalltalk browseAllCallsOn:
	(Undeclared associationAt: #Disk)
Smalltalk browseAllMethodsInCategory: #examples
(Smalltalk collectPointersTo: StrikeFont someInstance) inspect.
Smalltalk garbageCollect.
FileStream instanceCount =

FormView allInstances inspect.
Smalltalk browse: Random

HouseCleaning
Undeclared inspect.
Smalltalk cleanOutUndeclared.
(Object classPool at: #DependentsFields) inspect.
Smalltalk reclaimDependents.
Symbol rehash.
Transcript clear.
Smalltalk forgetDoIts.
Smalltalk removeKey: #GlobalName.
Smalltalk declare: #GlobalName
	from: Undeclared.

Globals
Smalltalk keys select: [:k | ((Smalltalk at: k) isKindOf: Behavior) not]
	Display -- a DisplayScreen
	Processor -- a ProcessorScheduler =

	ScheduledControllers -- a ControlManager
	Sensor -- an InputSensor
	Transcript -- a TextCollector
	SourceFiles -- Array of FileStreams
	SystemOrganization -- a SystemOrganizer
	StartUpList -- an OrderedCollection
	ShutDownList -- an OrderedCollection

Variable Pools (Dictionaries)
	Smalltalk =

	FilePool
	TextConstants
	Undeclared

System Files
Smalltalk closeSourceFiles.
Smalltalk openSourceFiles.
SourceFiles _ Array new: 2.

Measurements
Utilities garbageCollectReportString ''13,370,176 bytes available''
Symbol instanceCount 12907
Time millisecondsToRun: [10 benchmark] 266
MessageTally spyOn: [100 timesRepeat: [3.14159 printString]]
MessageTally tallySends: [3.14159 printString]
' runs: (RunArray runs: #(15 18 5 175 120 17 472 7 577 13 271 7 472 12 85=
 12 248 ) values: ((Array new: 17) at: 1 put: ((Array new: 2) at: 1 put: =
(TextFontChange basicNew instVarAt: 1 put: 1; yourself); at: 2 put: (Text=
Emphasis basicNew instVarAt: 1 put: 1; instVarAt: 2 put: true; yourself);=
 yourself); at: 2 put: ((Array new: 2) at: 1 put: (TextFontChange basicNe=
w instVarAt: 1 put: 3; yourself); at: 2 put: (TextEmphasis basicNew instV=
arAt: 1 put: 1; instVarAt: 2 put: true; yourself); yourself); at: 3 put: =
((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; =
yourself); yourself); at: 4 put: ((Array new: 1) at: 1 put: (TextFontChan=
ge basicNew instVarAt: 1 put: 2; yourself); yourself); at: 5 put: ((Array=
 new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yoursel=
f); yourself); at: 6 put: ((Array new: 2) at: 1 put: (TextFontChange basi=
cNew instVarAt: 1 put: 2; yourself); at: 2 put: (TextEmphasis basicNew in=
stVarAt: 1 put: 4; instVarAt: 2 put: true; yourself); yourself); at: 7 pu=
t: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: =
1; yourself); yourself); at: 8 put: ((Array new: 2) at: 1 put: (TextFontC=
hange basicNew instVarAt: 1 put: 2; yourself); at: 2 put: (TextEmphasis b=
asicNew instVarAt: 1 put: 4; instVarAt: 2 put: true; yourself); yourself)=
; at: 9 put: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarA=
t: 1 put: 1; yourself); yourself); at: 10 put: ((Array new: 2) at: 1 put:=
 (TextFontChange basicNew instVarAt: 1 put: 2; yourself); at: 2 put: (Tex=
tEmphasis basicNew instVarAt: 1 put: 4; instVarAt: 2 put: true; yourself)=
; yourself); at: 11 put: ((Array new: 1) at: 1 put: (TextFontChange basic=
New instVarAt: 1 put: 1; yourself); yourself); at: 12 put: ((Array new: 2=
) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yourself); at:=
 2 put: (TextEmphasis basicNew instVarAt: 1 put: 4; instVarAt: 2 put: tru=
e; yourself); yourself); at: 13 put: ((Array new: 1) at: 1 put: (TextFont=
Change basicNew instVarAt: 1 put: 1; yourself); yourself); at: 14 put: ((=
Array new: 2) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yo=
urself); at: 2 put: (TextEmphasis basicNew instVarAt: 1 put: 4; instVarAt=
: 2 put: true; yourself); yourself); at: 15 put: ((Array new: 1) at: 1 pu=
t: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); yourself); at=
: 16 put: ((Array new: 2) at: 1 put: (TextFontChange basicNew instVarAt: =
1 put: 2; yourself); at: 2 put: (TextEmphasis basicNew instVarAt: 1 put: =
4; instVarAt: 2 put: true; yourself); yourself); at: 17 put: ((Array new:=
 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 1; yourself); y=
ourself); yourself))); instVarAt: 3 put: nil; yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-
'Squeak Performance Benchmarks'
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-
(Workspace basicNew instVarAt: 1 put: nil; instVarAt: 2 put: (Text string=
: 'Simple Squeak Benchmarks

Send speed in sends/sec:

[ | siz col r t |
siz :=3D 64.
col :=3D OrderedCollection new: siz.
Cursor wait showWhile:
	[siz timesRepeat:
		[t _ Time millisecondsToRun: [r _ 26 benchFib].
		col add: (r // t * 1000)]].
Transcript show: ''	max: '', col max printString, '' 	avg: '', =

			col average truncated printString; cr]

 637000 -- G3/266 (tower)
 654000 -- 8600/300
 561000 -- 6500/300
 561000 -- G3 (desktop)
 1094000 -- PowerBook G3 292 MHz/jitter
 1296000 -- PowerBook G3 400 MHz VM 2.5

Bytecode speed in bytecodes/sec:

[ | siz col t |
siz :=3D 64.
col :=3D OrderedCollection new: siz.
Cursor wait showWhile:
	[siz timesRepeat:
		[t :=3D Time millisecondsToRun: [20 benchmark].
		col add: (10000000 // t * 1000)]].
Transcript show: ''	max: '', col max printString, '' 	avg: '', =

			col average truncated printString; cr]

 15384000 -- G3/266 (tower)
 14992000 -- 8600/300
 13623000 -- G3 (desktop)
 20964000 -- PowerBook G3 292 MHz/jitter
 31055000 -- PowerBook G3 400 MHz VM 2.5
' runs: (RunArray runs: #(24 1 1 970 ) values: ((OrderedCollection new) a=
dd: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt: 1 put:=
 3; yourself); yourself); add: ((Array new: 1) at: 1 put: (TextFontChange=
 basicNew instVarAt: 1 put: 1; yourself); yourself); add: ((Array new: 1)=
 at: 1 put: (TextFontChange basicNew instVarAt: 1 put: 2; yourself); your=
self); add: ((Array new: 1) at: 1 put: (TextFontChange basicNew instVarAt=
: 1 put: 1; yourself); yourself); yourself))); instVarAt: 3 put: ((Dictio=
nary new) add: ('coll'->nil); yourself); yourself)
-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=
=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D-=3D=
-

--------------108CCEC95E79F85A72D1BA80--





More information about the Squeak-dev mailing list