[squeak-dev] The Trunk: Morphic-cwp.616.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Apr 2 23:59:41 UTC 2012


Colin Putney uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-cwp.616.mcz

==================== Summary ====================

Name: Morphic-cwp.616
Author: cwp
Time: 2 April 2012, 4:22:03.778 pm
UUID: 01a6b217-a640-4e87-8874-f466fc4d0974
Ancestors: Morphic-cwp.591, Morphic-cmm.615

merge

=============== Diff against Morphic-cwp.591 ===============

Item was changed:
  ----- Method: LazyListMorph>>display:atRow:on: (in category 'drawing') -----
  display: item atRow: row on: canvas
  	"display the given item at row row"
  
+ 	| drawBounds emphasized rowColor itemAsText |
+ 	itemAsText := item asStringOrText.
+ 	emphasized := itemAsText isText 
+ 		ifTrue: [font emphasized: (itemAsText emphasisAt: 1)] 
- 	| drawBounds emphasized rowColor |
- 	emphasized := item isText 
- 		ifTrue: [font emphasized: (item emphasisAt: 1)] 
  		ifFalse: [font].
  	rowColor := self colorForRow: row.
  	drawBounds := self drawBoundsForRow: row.
  	drawBounds := drawBounds intersect: self bounds.
  	(self icon: row) ifNotNil: 
  		[ :icon || top |
  		top := drawBounds top + ((drawBounds height - icon height) // 2).
  		canvas translucentImage: icon at: drawBounds left @ top.
  		drawBounds := drawBounds left: drawBounds left + icon width + 2 ].
+ 	canvas drawString: itemAsText in: drawBounds font: emphasized color: rowColor!
- 	canvas drawString: item in: drawBounds font: emphasized color: rowColor!

Item was changed:
  ----- Method: LazyListMorph>>drawOn: (in category 'drawing') -----
  drawOn: aCanvas
  	| |
  	listItems size = 0 ifTrue: [ ^self ].
   
  	self drawSelectionOn: aCanvas.
  
  	(self topVisibleRowForCanvas: aCanvas) to: (self bottomVisibleRowForCanvas: aCanvas) do: [ :row |
  		(listSource itemSelectedAmongMultiple:  row) ifTrue: [
  			self drawBackgroundForMulti: row on: aCanvas. ].
+ 		self display: (self item: row) atRow: row on: aCanvas.
- 		self display: (self item: row) asStringOrText atRow: row on: aCanvas.
  	].
  
  	listSource potentialDropRow > 0 ifTrue: [
  		self highlightPotentialDropRow: listSource potentialDropRow on: aCanvas ].!

Item was removed:
- ----- Method: Morph>>connections (in category 'accessing') -----
- connections
- 	"Empty method in absence of connectors"
- 	^ #()!

Item was changed:
  ----- Method: Morph>>dismissMorph (in category 'meta-actions') -----
  dismissMorph
+ 	"This is called from an explicit halo destroy/delete action.
+ 	So first disconnect all constraints to keep the graph up to date."
- 	"This is called from an explicit halo destroy/delete action."
  
+ 	(self respondsTo: #disconnectAllConstraints) "Connectors package"
+ 		ifTrue: [ self perform: #disconnectAllConstraints ].
+ 	(self respondsTo: #releaseGraphModels) "CGPrereqs package (Connectors)"
+ 		ifTrue: [ self perform: #releaseGraphModels ].
+ 	self world ifNotNilDo: 
+ 			[:w |  w abandonAllHalos; stopStepping: self].
- 	| w |
- 	w := self world ifNil:[^self].
- 	w abandonAllHalos; stopStepping: self.
  	self delete!

Item was changed:
  ----- Method: Morph>>exportAsBMP (in category 'menus') -----
  exportAsBMP
  	| fName |
  	fName := UIManager default request:'Please enter the name' translated initialAnswer: self externalName,'.bmp'.
  	fName isEmpty ifTrue:[^self].
+ 	self exportAsBMPNamed: fName!
- 	self imageForm writeBMPfileNamed: fName.!

Item was added:
+ ----- Method: Morph>>exportAsBMPNamed: (in category 'menus') -----
+ exportAsBMPNamed: aString 
+ 	self imageForm writeBMPfileNamed: aString!

Item was changed:
  ----- Method: Morph>>exportAsGIF (in category 'menus') -----
  exportAsGIF
  	| fName |
  	fName := UIManager default request:'Please enter the name' translated initialAnswer: self externalName,'.gif'.
  	fName isEmpty ifTrue:[^self].
+ 	self exportAsGIFNamed: fName!
- 	GIFReadWriter putForm: self imageForm onFileNamed: fName.!

Item was added:
+ ----- Method: Morph>>exportAsGIFNamed: (in category 'menus') -----
+ exportAsGIFNamed: aString 
+ 	GIFReadWriter
+ 		putForm: self imageForm
+ 		onFileNamed: aString!

Item was changed:
  ----- Method: Morph>>exportAsJPEG (in category 'menus') -----
  exportAsJPEG
- 	"Export the receiver's image as a JPEG"
- 
  	| fName |
  	fName := UIManager default request: 'Please enter the name' translated initialAnswer: self externalName,'.jpeg'.
  	fName isEmpty ifTrue: [^ self].
+ 	self exportAsJPEGNamed: fName!
- 	self imageForm writeJPEGfileNamed: fName!

Item was added:
+ ----- Method: Morph>>exportAsJPEGNamed: (in category 'menus') -----
+ exportAsJPEGNamed: aString 
+ 	self imageForm writeJPEGfileNamed: aString!

Item was changed:
  ----- Method: Morph>>exportAsPNG (in category 'menus') -----
  exportAsPNG
  	| fName |
  	fName := UIManager default request:'Please enter the name' translated initialAnswer: self externalName,'.png'.
  	fName isEmpty ifTrue:[^self].
+ 	self exportAsPNGNamed: fName!
- 	PNGReadWriter putForm: self imageForm onFileNamed: fName.!

Item was added:
+ ----- Method: Morph>>exportAsPNGNamed: (in category 'menus') -----
+ exportAsPNGNamed: aString 
+ 	PNGReadWriter
+ 		putForm: self imageForm
+ 		onFileNamed: aString!

Item was removed:
- ----- Method: Morph>>wantsEmbeddingsVocabulary (in category 'accessing') -----
- wantsEmbeddingsVocabulary
- 	"Empty method in absence of connectors"
- 	^ false!

Item was changed:
  ----- Method: TextComposer>>composeAllRectangles: (in category 'as yet unclassified') -----
  composeAllRectangles: rectangles
  
  	| charIndexBeforeLine numberOfLinesBefore reasonForStopping |
  
  	actualHeight := defaultLineHeight.
  	charIndexBeforeLine := currCharIndex.
  	numberOfLinesBefore := lines size.
  	reasonForStopping := self composeEachRectangleIn: rectangles.
  
  	currentY := currentY + actualHeight.
  	currentY > theContainer bottom ifTrue: [
  		"Oops -- the line is really too high to fit -- back out"
  		currCharIndex := charIndexBeforeLine.
  		lines size - numberOfLinesBefore timesRepeat: [lines removeLast].
  		^self
  	].
  	
  	"It's OK -- the line still fits."
  	maxRightX := maxRightX max: scanner rightX.
+ 	1 to: rectangles size - 1 do: [ :i | |lineIndex|
- 	1 to: rectangles size - 1 do: [ :i |
  		"Adjust heights across rectangles if necessary"
+ 		lineIndex:=lines size - rectangles size + i.
+ 		(lines size between: 1 and: lineIndex) ifTrue: 
+ 			[(lines at: lineIndex)
+ 				lineHeight: lines last lineHeight
+ 				baseline: lines last baseline] 
- 		(lines at: lines size - rectangles size + i)
- 			lineHeight: lines last lineHeight
- 			baseline: lines last baseline
  	].
  	isFirstLine := false.
  	reasonForStopping == #columnBreak ifTrue: [^nil].
  	currCharIndex > theText size ifTrue: [
  		^nil		"we are finished composing"
  	].
  	!

Item was changed:
  ----- Method: TextEditor>>explainDelimitor: (in category 'explain') -----
  explainDelimitor: string
  	"Is string enclosed in delimitors?"
  
  	| str |
  	(string at: 1) isLetter ifTrue: [^nil].  "only special chars"
  	(string first = string last) ifTrue:
  			[^ self explainChar: (String with: string first)]
  		ifFalse:
  			[(string first = $( and: [string last = $)]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = $[ and: [string last = $]]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = ${ and: [string last = $}]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = $< and: [string last = $>]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = $# and: [string last = $)]) ifTrue:
+ 				[^'"An instance of class Array.  The Numbers, Characters, Symbols or Arrays between the parenthesis are the elements of the Array."'].
- 				[^'"An instance of class Array.  The Numbers, Characters, or Symbols between the parenthesis are the elements of the Array."'].
  			string first = $# ifTrue:
  				[^'"An instance of class Symbol."'].
  			(string first = $$ and: [string size = 2]) ifTrue:
  				[^'"An instance of class Character.  This one is the character ', (String with: string last), '."'].
  			(string first = $:) ifTrue:
+ 				[string = ':=' ifTrue:
+ 					[^'"Colon equals means assignment.  The value of the expression after the := is stored into the variable before it."'].
+ 				str := string allButFirst.
+ 				(self explainTemp: str) ifNotNil:
+ 					[^'"An argument to this block will be bound to the temporary variable ', str, '."']]].
- 				[str := string allButFirst.
- 				(self explainTemp: str) ifNotNil: [
- 					^'"An argument to this block will be bound to the temporary variable ',
- 						str, '."']]].
  	^ nil!

Item was changed:
  ----- Method: TextEditor>>notify:at:in: (in category 'new selection') -----
  notify: aString at: anInteger in: aStream 
  	"The compilation of text failed. The syntax error is noted as the argument, 
  	aString. Insert it in the text at starting character position anInteger."
  
+ 	self insertAndSelect: aString at: (anInteger max: 1)!
- 	| pos |
- 	pos := self selectionInterval notEmpty
- 		ifTrue: [
- 			self startIndex + anInteger - 1 ]
- 		ifFalse: [anInteger].
- 	self insertAndSelect: aString at: (pos max: 1)!

Item was changed:
+ TextEditor subclass: #TextMorphEditor
+ 	instanceVariableNames: ''
- ParagraphEditor subclass: #TextMorphEditor
- 	instanceVariableNames: 'morph oldInterval pivotBlock editHistory'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Morphic-Text Support'!
  
+ !TextMorphEditor commentStamp: 'dtl 1/21/2012 18:02' prior: 0!
+ This is a stub class to replace the original implementation of a ParagraphEditor for TextMorphs, which has since been replaced by TextEditor. This implementation is retained for the benefit of external packages such as Connectors and FreeType that may have dependencies on TextMorphEditor.
- !TextMorphEditor commentStamp: '<historical>' prior: 0!
- This is the ParagraphEditor for TextMorphs.
  
+ The comment below is from the class comment of the original TextMorphEditor.
- 
- 
  -----
  In the past, BookMorphs had the ability to have each page be on the server as a .sp SqueakPage file.  The index of the book was a .bo file.  In text, Cmd-6 had a LinkTo option that linked to a page by its name, or created a new page of that name.  It assumed the book was on a server with a file per page.  Ted removed that code, and kept a copy on his disk in 'TME-ChngEmphasis.st for .bo .sp'!

Item was removed:
- ----- Method: TextMorphEditor>>accept (in category 'menu messages') -----
- accept
- 	"Save the current text of the text being edited as the current acceptable version for purposes of canceling.  Allow my morph to take appropriate action"
- 	morph acceptContents!

Item was removed:
- ----- Method: TextMorphEditor>>addEditCommand: (in category 'multi level undo') -----
- addEditCommand: anEditCommand
- 
- 	self editHistory rememberCommand: anEditCommand.
- "
- 	Debug dShow: anEditCommand newText.
- 	Debug dShow: anEditCommand replacedText.
- "
- 
- 
- !

Item was removed:
- ----- Method: TextMorphEditor>>againOrSame: (in category 'private') -----
- againOrSame: bool 
- 	| bk keys |
- 	(bk := morph ownerThatIsA: BookMorph) ifNotNil: 
- 			[(keys := bk valueOfProperty: #tempSearchKey ifAbsent: [nil]) ifNil: 
- 					["Cmd-f"
- 
- 					keys := bk valueOfProperty: #searchKey ifAbsent: [nil]	"Cmd-g"]
- 				ifNotNil: [bk removeProperty: #tempSearchKey].
- 			keys ifNotNil: 
- 					[keys notEmpty
- 						ifTrue: 
- 							[bk findText: keys.
- 							^(morph respondsTo: #editView) 
- 								ifTrue: [morph editView selectionInterval: self selectionInterval]]]].
- 	super againOrSame: bool.
- 	(morph respondsTo: #editView) 
- 		ifTrue: [morph editView selectionInterval: self selectionInterval]!

Item was removed:
- ----- Method: TextMorphEditor>>align (in category 'menu messages') -----
- align
- 	"Align text according to the next greater alignment value,
- 	cycling among leftFlush, rightFlush, center, and justified."
- 	self changeAlignment.
- 	self recomputeInterval!

Item was removed:
- ----- Method: TextMorphEditor>>bindingOf: (in category 'binding') -----
- bindingOf: aString
- 	^model bindingOf: aString!

Item was removed:
- ----- Method: TextMorphEditor>>cancel (in category 'menu messages') -----
- cancel
- 	"Cancel the changes made so far to this text"
- 	morph cancelEdits!

Item was removed:
- ----- Method: TextMorphEditor>>changeEmphasis: (in category 'editing keys') -----
- changeEmphasis: aStream
- 	"Change the emphasis of the current selection."
- 	| retval |
- 	retval := super changeEmphasis: aStream.
- 	paragraph composeAll.
- 	self recomputeInterval.
- 	morph updateFromParagraph.
- 	^retval!

Item was removed:
- ----- Method: TextMorphEditor>>changeEmphasisOrAlignment (in category 'attributes') -----
- changeEmphasisOrAlignment
- 	| aList reply  code align menuList startIndex alignSymbol |
- 	self flag: #arNote. "Move this up once we get rid of MVC"
- 	startIndex := self startIndex.
- 	aList := #(normal bold italic narrow underlined struckOut leftFlush centered rightFlush justified).	
- 	align := paragraph text alignmentAt: startIndex 
- 		ifAbsent:[paragraph textStyle alignment].
- 	alignSymbol := TextAlignment alignmentSymbol: align.
- 	code := paragraph text emphasisAt: startIndex.
- 	menuList := WriteStream on: Array new.
- 	menuList nextPut: (code isZero ifTrue:['<on>'] ifFalse:['<off>']), 'normal' translated.
- 	menuList nextPutAll: (#(bold italic underlined struckOut) collect:[:emph|
- 		(code anyMask: (TextEmphasis perform: emph) emphasisCode)
- 			ifTrue:['<on>', emph asString translated]
- 			ifFalse:['<off>',emph asString translated]]).
- 	((paragraph text attributesAt: startIndex forStyle: paragraph textStyle)
- 		anySatisfy:[:attr| attr isKern and:[attr kern < 0]]) 
- 			ifTrue:[menuList nextPut:'<on>', 'narrow' translated]
- 			ifFalse:[menuList nextPut:'<off>', 'narrow' translated].
- 	menuList nextPutAll: (#(leftFlush centered rightFlush justified) collect:[:type|
- 		type == alignSymbol
- 			ifTrue:['<on>',type asString translated]
- 			ifFalse:['<off>',type asString translated]]).
- 	aList := #(normal bold italic underlined struckOut narrow leftFlush centered rightFlush justified).
- 	reply := UIManager default chooseFrom: menuList contents values: aList lines: #(1 6).
- 	reply notNil ifTrue:
- 		[(#(leftFlush centered rightFlush justified) includes: reply)
- 			ifTrue:
- 				[self setAlignment: reply.
- 				paragraph composeAll.
- 				self recomputeInterval]
- 			ifFalse:
- 				[self setEmphasis: reply.
- 				paragraph composeAll.
- 				self recomputeSelection.
- 				self mvcRedisplay]].
- 	^ true!

Item was removed:
- ----- Method: TextMorphEditor>>changeSelectionFontTo: (in category 'attributes') -----
- changeSelectionFontTo: aFont
- 	| attr |
- 	aFont ifNil:[^self].
- 	attr := TextFontReference toFont: aFont.
- 	paragraph text addAttribute: attr from: self startIndex to: (self stopIndex-1 min: paragraph text size).
- 	paragraph composeAll.
- 	self recomputeInterval.
- 	morph changed.!

Item was removed:
- ----- Method: TextMorphEditor>>changeStyle (in category 'attributes') -----
- changeStyle
- 	"Let user change styles for the current text pane."
- 	| aList reply style theStyle menuList |
- 	self flag: #arNote. "Move this up once we get rid of MVC"
- 	aList := StrikeFont actualFamilyNames.
- 	theStyle := paragraph textStyle.
- 	menuList := aList collect:[:styleName|
- 		"Hack!! use defaultFont for comparison - we have no name that we could use for compare and the style changes with alignment so they're no longer equal."
- 		(TextConstants at: styleName) defaultFont == theStyle defaultFont
- 			ifTrue:['<on>', styleName]
- 			ifFalse:['<off>',styleName]].
- 	theStyle = TextStyle default
- 		ifTrue:[menuList addFirst: '<on>DefaultTextStyle']
- 		ifFalse:[menuList addFirst: '<off>DefaultTextStyle'].
- 	aList addFirst: 'DefaultTextStyle'.
- 	reply := UIManager default chooseFrom: menuList values: aList lines: #(1).
- 	reply ifNotNil:
- 		[(style := TextStyle named: reply) ifNil: [Beeper beep. ^ true].
- 		paragraph textStyle: style copy.
- 		paragraph composeAll.
- 		self recomputeSelection.
- 		self mvcRedisplay].
- 	^ true!

Item was removed:
- ----- Method: TextMorphEditor>>changeTextFont (in category 'attributes') -----
- changeTextFont
- 	"Present a dialog which allows the user to select a font, and if one is chosen, apply it to the current selection.	If there is no selection, or the selection is empty, apply it to the whole morph."
- 	| curFont startIndex chooser newFont |
- 	startIndex := self startIndex.
- 	curFont := (paragraph text fontAt: startIndex withStyle: paragraph textStyle).
- 	morph openModal: (
- 		Cursor wait showWhile: [ 
- 			(chooser := FontChooserTool default
- 				withTitle: 'Change the selected text''s font to...' translated
- 				for: self 
- 				setSelector: #changeSelectionFontTo:
- 				getSelector: curFont)
- 			"Do not allow changing the emphasis; we don't know how to deal with
- 			a 'pre-emphasized' font here, so bail."
- 				offerStyleList: false;
-  				open]).
- 	newFont := chooser result.
- 	newFont ifNotNil:[self changeSelectionFontTo: newFont].!

Item was removed:
- ----- Method: TextMorphEditor>>chooseColor (in category 'editing keys') -----
- chooseColor
- 	| attribute |
- 	attribute := TextColor color: Color black. "default"
- 	"Make a new Text Color Attribute, let the user pick a color, and return the attribute"
- 	NewColorPickerMorph useIt
- 		ifTrue: [ (NewColorPickerMorph on: attribute) openNear: morph fullBoundsInWorld ]
- 		ifFalse:
- 			[ ColorPickerMorph new
- 				 choseModalityFromPreference ;
- 				 sourceHand: morph activeHand ;
- 				 target: attribute ;
- 				 selector: #color: ;
- 				 originalColor: Color black ;
- 				
- 				putUpFor: morph
- 				near: morph fullBoundsInWorld ].
- 	^ attribute!

Item was removed:
- ----- Method: TextMorphEditor>>closeTypeIn (in category 'multi level undo') -----
- closeTypeIn
- 
- 	| begin stop rInterval nInterval newText |
- 
- 	(UndoMessage sends: #noUndoer) ifFalse:[^super closeTypeIn].
- 	Preferences multipleTextUndo ifTrue: 
- 		[
- 		beginTypeInBlock == nil ifFalse:
- 			[
- 				begin := self startOfTyping.
- 				stop := self stopIndex.
- 				rInterval := (begin "+ UndoMessage argument" 
- 																to: begin + UndoSelection size - 1).
- 				nInterval := begin to: stop - 1.
- 				(nInterval = rInterval) ifTrue:[ ^super closeTypeIn ].
- 				newText := nInterval size > 0
- 										ifTrue: [ paragraph text 
- 																copyFrom: nInterval first 
- 																to: nInterval last ]
- 										ifFalse: [ self nullText ].
- 				self addEditCommand: 
- 				 	(EditCommand
- 							textMorph: morph
- 							replacedText: UndoSelection copy
- 							replacedTextInterval: rInterval
- 							newText: newText 
- 							newTextInterval: nInterval)
- 			].
- 		].
- 	
- 	"Call the super regardless, just to keep the standard undo machine happy"
- 	^super closeTypeIn
- !

Item was removed:
- ----- Method: TextMorphEditor>>controlInitialize (in category 'controlling') -----
- controlInitialize
- 	"No-op for MVC ParagraphEditor compatibility"!

Item was removed:
- ----- Method: TextMorphEditor>>controlTerminate (in category 'controlling') -----
- controlTerminate
- 	"No-op for MVC ParagraphEditor compatibility"!

Item was removed:
- ----- Method: TextMorphEditor>>dispatchOnCharacter:with: (in category 'typing support') -----
- dispatchOnCharacter: char with: typeAheadStream
- 	"Carry out the action associated with this character, if any.
- 	Type-ahead is passed so some routines can flush or use it."
- 
- 	((char == Character cr) and: [morph acceptOnCR])
- 		ifTrue:
- 			[sensor keyboard.  "Gobble cr -- probably unnecessary."
- 			self closeTypeIn.
- 			^ true].
- 
- 	^ super dispatchOnCharacter: char with: typeAheadStream!

Item was removed:
- ----- Method: TextMorphEditor>>editHistory (in category 'multi level undo') -----
- editHistory
- 	^morph editHistory
- !

Item was removed:
- ----- Method: TextMorphEditor>>fakeSensorWithEvent: (in category 'typing support') -----
- fakeSensorWithEvent: anEvent
- 	"Pass the event to a polling-friendly-sensor-fake so that old st-80 code shall still work"
- 	self sensor: (KeyboardBuffer new startingEvent: anEvent).!

Item was removed:
- ----- Method: TextMorphEditor>>find (in category 'menu messages') -----
- find
- 	super find.
- 	morph installEditorToReplace: self!

Item was removed:
- ----- Method: TextMorphEditor>>flash (in category 'displaying') -----
- flash
- 	^ morph flash!

Item was removed:
- ----- Method: TextMorphEditor>>inspectIt: (in category 'editing keys') -----
- inspectIt: characterStream 
- 	"Inspect the selection -- invoked via cmd-i.  If there is no current selection, use the current line."
- 
- 	sensor keyboard.		"flush character"
- 	self inspectIt.
- 	^ true!

Item was removed:
- ----- Method: TextMorphEditor>>isInTypeRun (in category 'multi level undo') -----
- isInTypeRun
- 	^beginTypeInBlock ~~ nil
- !

Item was removed:
- ----- Method: TextMorphEditor>>keyStroke: (in category 'events') -----
- keyStroke: anEvent
- 	self fakeSensorWithEvent: anEvent.
- 	self readKeyboard!

Item was removed:
- ----- Method: TextMorphEditor>>morph (in category 'accessing') -----
- morph
- 	^ morph!

Item was removed:
- ----- Method: TextMorphEditor>>morph: (in category 'accessing') -----
- morph: aMorph
- 	"Install a link back to the morph being edited (esp for text links)"
- 	morph := aMorph !

Item was removed:
- ----- Method: TextMorphEditor>>mouseDown: (in category 'events') -----
- mouseDown: evt 
- 	"An attempt to break up the old processRedButton code into threee phases"
- 	| clickPoint |
- 
- 	oldInterval := self selectionInterval.
- 	clickPoint := evt cursorPoint.
- 	(paragraph clickAt: clickPoint for: model controller: self) ifTrue: [
- 		pivotBlock := paragraph characterBlockAtPoint: clickPoint.
- 		self markBlock: pivotBlock.
- 		self pointBlock: pivotBlock.
- 		evt hand releaseKeyboardFocus: self.
- 		^ self].
- 	evt shiftPressed
- 		ifFalse:
- 			[self closeTypeIn.
- 			pivotBlock := paragraph characterBlockAtPoint: clickPoint.
- 			self markBlock: pivotBlock.
- 			self pointBlock: pivotBlock.]
- 		ifTrue:
- 			[self closeTypeIn.
- 			self mouseMove: evt].
- 	self storeSelectionInParagraph!

Item was removed:
- ----- Method: TextMorphEditor>>mouseMove: (in category 'events') -----
- mouseMove: evt 
- 	"Change the selection in response to moue-down drag"
- 
- 	pivotBlock ifNil: [^ self].  "Patched during clickAt: repair"
- 	self pointBlock: (paragraph characterBlockAtPoint: (evt cursorPoint)).
- 	self storeSelectionInParagraph!

Item was removed:
- ----- Method: TextMorphEditor>>mouseUp: (in category 'events') -----
- mouseUp: evt
- 	"An attempt to break up the old processRedButton code into threee phases"
- 	oldInterval ifNil: [^ self].  "Patched during clickAt: repair"
- 	(self hasCaret 
- 		and: [oldInterval = self selectionInterval])
- 		ifTrue: [self selectWord].
- 	self setEmphasisHere.
- 	(self isDisjointFrom: oldInterval) ifTrue:
- 		[otherInterval := oldInterval].
- 	self storeSelectionInParagraph!

Item was removed:
- ----- Method: TextMorphEditor>>multiRedo (in category 'multi level undo') -----
- multiRedo
- 	^self multiRedoWithCount: 1
- !

Item was removed:
- ----- Method: TextMorphEditor>>multiRedo: (in category 'multi level undo') -----
- multiRedo: readAheadStream
- 	sensor keyboard. 	"flush character"
- 	self closeTypeIn.
- 	self multiRedoWithCount: 1.
- 	^true
- !

Item was removed:
- ----- Method: TextMorphEditor>>multiRedoWithCount: (in category 'multi level undo') -----
- multiRedoWithCount: count
- 
- 	| command i lastCommand newSelection saveSelection history |
- 
- 	count > 0 ifFalse:[ ^self ].
- 
- 	history := self editHistory.
- 	(command := history nextCommand) isNil
- 			ifTrue:[ ^self multiUndoError: 'Nothing to redo'].
- 
- 	saveSelection := self selectionInterval.
- 	self deselect.
- 	i := 0.
- 	[i < count] whileTrue: 
- 		[
- 		history redo.
- 		lastCommand := command.
- 		((i := i + 1) < count) ifTrue:
- 			[
- 			(command := history nextCommand) ifNil:[
- 				self multiUndoError: ('Only ', (i - 1) asString, ' commands to redo.').
- 				i := count.]]].
- 
- 	(newSelection := lastCommand redoSelectionInterval) isNil
- 			ifTrue:[ self selectInterval: saveSelection]
- 			ifFalse:[ self selectInterval: newSelection].
- 
- !

Item was removed:
- ----- Method: TextMorphEditor>>multiUndo (in category 'multi level undo') -----
- multiUndo
- 	^self multiUndoWithCount: 1
- !

Item was removed:
- ----- Method: TextMorphEditor>>multiUndoError: (in category 'multi level undo') -----
- multiUndoError: eString
- 
- 	Beeper beep
- !

Item was removed:
- ----- Method: TextMorphEditor>>multiUndoWithCount: (in category 'multi level undo') -----
- multiUndoWithCount: count
- 
- 	| command i lastCommand saveSelection newSelection history |
- 
- 	count > 0 ifFalse:[ ^self ].
- 	history := self editHistory.
- 	(command := history commandToUndo) 
- 		ifNil:[ ^self multiUndoError: 'Nothing to undo'].
- 		
- 	saveSelection := self selectionInterval.
- 	self deselect.
- 	i := 0.
- 	[i < count] whileTrue: 
- 		[history undo.
- 		lastCommand := command.
- 		((i := i + 1) < count) ifTrue:
- 			[(command := history commandToUndo) ifNil:[
- 				self multiUndoError: ('Only ', (i - 1) asString, ' commands to undo.').
- 				i := count. ]]].
- 
- 	(newSelection := lastCommand undoSelectionInterval) isNil
- 			ifTrue:[ self selectInterval: saveSelection]
- 			ifFalse:[ self selectInterval: newSelection].
- 
- !

Item was removed:
- ----- Method: TextMorphEditor>>mvcRedisplay (in category 'menu messages') -----
- mvcRedisplay
- 	"Ignore mvcRedisplay requests."!

Item was removed:
- ----- Method: TextMorphEditor>>noUndoReplace:with: (in category 'multi level undo') -----
- noUndoReplace: anInterval with: aText
- "This is the zap that multilevel undo uses to do edits. This method bypasses any undo/redo plumbing (in contrast to zapSelection:).  This method is called by an EditCommand (which wants to carry out its paragraph surgery without adding another command to the editHistory)"
- 
- 	| start stop |
- 	self deselect.
- 	start := (anInterval first max: 1).
- 	stop := (anInterval last min: paragraph text size).
- 	(aText isEmpty and: [stop > start]) ifTrue:
- 		["If deleting, then set emphasisHere from 1st character of the deletion"
- 		emphasisHere := (paragraph text attributesAt: start forStyle: paragraph textStyle)
- 					select: [:att | att mayBeExtended]].
- "Debug dShow: ('zap start->stop: ', (start to: stop) asString)."
- 	paragraph 
- 		replaceFrom: start 
- 		to: stop 
- 		with: aText 
- 		displaying: false.  
- 
- 	UndoMessage sends: #noUndoer . "Keep the normal undo machine happy"
- 	self userHasEdited  " -- note text now dirty"
- !

Item was removed:
- ----- Method: TextMorphEditor>>offerFontMenu (in category 'attributes') -----
- offerFontMenu
- 	"Present a menu of available fonts, and if one is chosen, apply it to the current selection.  
- 	Use only names of Fonts of this paragraph  "
- 	| aList reply curFont menuList |
- true ifTrue:[^self changeTextFont].
- 	self flag: #arNote. "Move this up once we get rid of MVC"
- 	curFont := (paragraph text fontAt: self startIndex withStyle: paragraph textStyle) fontNameWithPointSize.
- 	aList := paragraph textStyle fontNamesWithPointSizes.
- 	menuList := aList collect:[:fntName|
- 		fntName = curFont ifTrue:['<on>',fntName] ifFalse:['<off>',fntName]].
- 	reply := UIManager default chooseFrom: menuList values: aList.
- 	reply ~~ nil ifTrue:
- 		[self replaceSelectionWith:
- 			(Text string: self selection asString 
- 				attribute: (TextFontChange fontNumber: (aList indexOf: reply)))] !

Item was removed:
- ----- Method: TextMorphEditor>>offerMenuFromEsc: (in category 'menu commands') -----
- offerMenuFromEsc: characterStream 
- 	"The escape key was hit while the receiver has the keyboard focus; take action"
- 
- 	^ ActiveEvent shiftPressed 
- 		ifTrue:
- 			[self escapeToDesktop: characterStream]
- 		ifFalse:
- 			[self raiseContextMenu: characterStream]!

Item was removed:
- ----- Method: TextMorphEditor>>raiseContextMenu: (in category 'nonediting/nontyping keys') -----
- raiseContextMenu: characterStream 
- 	(morph respondsTo: #editView)
- 		ifTrue: [morph editView yellowButtonActivity: ActiveEvent shiftPressed]
- 		ifFalse: [sensor keyboard.
- 			"consume the character"
- 			morph yellowButtonActivity: false].
- 	^ true!

Item was removed:
- ----- Method: TextMorphEditor>>readKeyboard (in category 'typing support') -----
- readKeyboard
- 	super readKeyboard.
- 	self storeSelectionInParagraph!

Item was removed:
- ----- Method: TextMorphEditor>>scrollBy: (in category 'scrolling') -----
- scrollBy: ignore 
- 	"Ignore scroll requests."!

Item was removed:
- ----- Method: TextMorphEditor>>select (in category 'current selection') -----
- select
- 	"Ignore selection redraw requests."!

Item was removed:
- ----- Method: TextMorphEditor>>selectAndScroll (in category 'current selection') -----
- selectAndScroll
- 	"Ignore scroll requests."!

Item was removed:
- ----- Method: TextMorphEditor>>selectAndScrollToTop (in category 'mvc compatibility') -----
- selectAndScrollToTop
- 	"Scroll until the selection is in the view and then highlight it."
- 
- 	| lineHeight deltaY rect deltaX |
- 	lineHeight := paragraph textStyle lineGrid.
- 	rect := morph owner bounds.
- 	deltaY := self stopBlock top - rect top.
- 	deltaY ~= 0 ifTrue: [
- 		deltaX := 0.
- 		deltaY := (deltaY abs + lineHeight - 1 truncateTo: lineHeight) negated.
- 		morph editView scrollBy: deltaX at deltaY]!

Item was removed:
- ----- Method: TextMorphEditor>>selectForTopFrom:to: (in category 'mvc compatibility') -----
- selectForTopFrom: start to: stop
- 
- 	self selectFrom: start to: stop.
- 	morph editView ifNotNil: [self selectAndScrollToTop]!

Item was removed:
- ----- Method: TextMorphEditor>>selectFrom:to: (in category 'new selection') -----
- selectFrom: start to: stop
- 	"Select the specified characters inclusive."
- 	self selectInvisiblyFrom: start to: stop.
- 	self closeTypeIn.
- 	self storeSelectionInParagraph.
- 	self setEmphasisHere.
- !

Item was removed:
- ----- Method: TextMorphEditor>>setSearch: (in category 'accessing') -----
- setSearch: aString
- 	| bk |
- 	"Set the FindText and ChangeText to seek aString; except if already seeking aString, leave ChangeText alone so again will repeat last replacement."
- 
- 	(bk := morph ownerThatIsA: BookMorph) ifNotNil: [
- 		bk setProperty: #tempSearchKey 
- 			toValue: (aString findTokens: Character separators)].
- 
- 	aString ifNotNil: [
- 		FindText string = aString
- 			ifFalse: [FindText := ChangeText := aString asText]].!

Item was removed:
- ----- Method: TextMorphEditor>>storeSelectionInParagraph (in category 'mvc compatibility') -----
- storeSelectionInParagraph
- 	paragraph selectionStart: self startBlock selectionStop: self stopBlock!

Item was removed:
- ----- Method: TextMorphEditor>>tempCommand: (in category 'editing keys') -----
- tempCommand: characterStream 
- 	"Experimental.  Triggered by Cmd-t; put trial cmd-key commands here to see how they work, before hanging them on their own cmd accelerators."
- 	Sensor keyboard.
- 	morph tempCommand.
- 	^ true!

Item was removed:
- ----- Method: TextMorphEditor>>textAlignment (in category 'attributes') -----
- textAlignment
- 	"Answer 1..4, representing #leftFlush, #rightFlush, #centered, or #justified"
- 	^paragraph text alignmentAt: startBlock stringIndex
- 		ifAbsent: [paragraph textStyle alignment]!

Item was removed:
- ----- Method: TextMorphEditor>>textAlignmentSymbol (in category 'attributes') -----
- textAlignmentSymbol
- 	^#(leftFlush rightFlush centered justified) at: self textAlignment
- 	!

Item was removed:
- ----- Method: TextMorphEditor>>totalTextHeight (in category 'as yet unclassified') -----
- totalTextHeight
- 
- 	^paragraph lines last bottom!

Item was removed:
- ----- Method: TextMorphEditor>>transformFrom: (in category 'accessing') -----
- transformFrom: owner
- 	^morph transformFrom: owner!

Item was removed:
- ----- Method: TextMorphEditor>>undo (in category 'multi level undo') -----
- undo
- 	"Reset the state of the paragraph prior to the previous edit.
- 	 If another ParagraphEditor instance did that edit, UndoInterval is invalid;
- 	 just recover the contents of the undo-buffer at the start of the paragraph."
- 
- 	Preferences multipleTextUndo 
- 		ifTrue: [ ^self multiUndo ]
- 		ifFalse:[ ^super undo ].
- !

Item was removed:
- ----- Method: TextMorphEditor>>updateMarker (in category 'scrolling') -----
- updateMarker
- 	"Ignore scrollbar redraw requests."
- !

Item was removed:
- ----- Method: TextMorphEditor>>userHasEdited (in category 'accessing') -----
- userHasEdited
- 	"Note that my text is free of user edits."
- 
- 	morph hasUnacceptedEdits: true!

Item was removed:
- ----- Method: TextMorphEditor>>userHasNotEdited (in category 'mvc compatibility') -----
- userHasNotEdited
- 	"Note that my text is free of user edits."
- 
- 	morph hasUnacceptedEdits: false!

Item was removed:
- ----- Method: TextMorphEditor>>visibleHeight (in category 'as yet unclassified') -----
- visibleHeight
- 
- 	^morph owner bounds height!

Item was removed:
- ----- Method: TextMorphEditor>>yellowButtonDown: (in category 'events') -----
- yellowButtonDown: event
- 	"Process a yellow button event. Answer true if the event was handled, false otherwise."
- 	(paragraph attributesAt: event cursorPoint) do:[:attr|
- 		attr menu ifNotNil:[
- 			attr menu openAt: event cursorPoint.
- 			^true]].
- 	^false!

Item was removed:
- ----- Method: TextMorphEditor>>zapSelectionWith: (in category 'menu messages') -----
- zapSelectionWith: aText
- 	"**overridden to inhibit old-style display"
- 	| start stop rText rInterval isInTypeRun |
- 	self deselect.
- 	start := self startIndex.
- 	stop := self stopIndex.
- 	(aText isEmpty and: [stop > start]) ifTrue:
- 		["If deleting, then set emphasisHere from 1st character of the deletion"
- 		emphasisHere := (paragraph text attributesAt: start forStyle: paragraph textStyle)
- 					select: [:att | att mayBeExtended]].
- 	(start = stop and: [aText size = 0]) ifFalse:
- 		[
- 		"===Support for multilevel undo start ==="
- 		rText := (paragraph text copyFrom: start to: (stop - 1)).
- 		rInterval := start to: (stop - 1).
- 		isInTypeRun := self isInTypeRun.
- 		"===Support for multilevel undo end ==="
- 		
- 		paragraph replaceFrom: start to: stop - 1
- 			with: aText displaying: false.  "** was true in super"
- 		self wasComposition ifTrue: [wasComposition := false. self setPoint: start + 1].
- 		self computeIntervalFrom: start to: start + aText size - 1.
- 		UndoInterval := otherInterval := self selectionInterval.
- 
- 		"===Support for multilevel undo start ==="
- 		 (Preferences multipleTextUndo and: [isInTypeRun not])ifTrue:
- 				[ self addEditCommand: 
- 							(EditCommand
- 									textMorph: morph
- 									replacedText: rText
- 									replacedTextInterval: rInterval
- 									newText: aText 
- 									newTextInterval: super selectionInterval)].
- 		"===Support for multilevel undo end ==="].
- 
- 	self userHasEdited  " -- note text now dirty"!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>extendingTheSystem (in category 'submenu - help') -----
  extendingTheSystem
  	^'"Note: Please edit this workspace and add your own contributions.
  To submit it to the inbox open the Monticello browser and submit it from there.
  Save the package ''* Morphic'' to the inbox."
  
  "Updating your system:
  The following will set the default update URL to receive development updates. 
  For developers and dare-devils only."
  
  MCMcmUpdater defaultUpdateURL: ''http://source.squeak.org/trunk''.
  
  "Installing new packages: 
  The following expression show how to load many interesting packages into Squeak."
  
  "FFI: http://source.squeak.org/FFI.html"
  (Installer repository: ''http://source.squeak.org/FFI'')
  	install: ''FFI-Pools'';
  	install: ''FFI-Kernel'';
  	install: ''FFI-Tests'';
  	install: ''FFI-Win32'';
  	install: ''FFI-MacOS'';
  	install: ''FFI-Unix''.
  
  "OCompletion provides source code completion as you type"
  (Installer ss project: ''OCompletion'') install: ''Ocompletion''.
  (Smalltalk at: #ECToolSet) register.
  (Smalltalk at: #ToolSet) default: (Smalltalk at: #ECToolSet).
  
  "Omnibrowser, including Refactoring engine"
  (Installer ss project: ''MetacelloRepository'') install: ''ConfigurationOfOmniBrowser''.
  ((Smalltalk at: #ConfigurationOfOmniBrowser) project perform: #lastVersion) load: #( Dev ).
  
+ "OpenGL"
+ "First load FFI"
+ (Installer repository: ''http://www.squeaksource.com/CroquetGL'')
+ 	install: ''3DTransform'';
+ 	install: ''OpenGL-Pools'';
+ 	install: ''OpenGL-Core''.
+ "OpenGL example"
+ 
  "Seaside 2.8 http://www.seaside.st"
  (Installer ss project: ''MetacelloRepository'') install: ''ConfigurationOfSeaside28''.
  "WAKom startOn: 9090"
  
  "Seaside 2.8 Examples http://www.seaside.st"
  (Installer ss project: ''MetacelloRepository'') install: ''ConfigurationOfSeaside28Examples''.
  (Smalltalk at: #ConfigurationOfSeaside28Examples) load.
  
  "Seaside 3.0 http://www.seaside.st"
  (Installer ss project: ''MetacelloRepository'') install: ''ConfigurationOfSeaside30''.
  (Smalltalk at: #ConfigurationOfSeaside30) load.
  (Smalltalk at: #WAPharoServerAdaptorBrowser) open.
  
  "Pier CMS: http://www.piercms.com"
  (Installer ss project: ''MetacelloRepository'') install: ''ConfigurationOfPier2''.
  (Smalltalk at: #ConfigurationOfPier2) load.
  
  (Installer lukas project: ''pier2'') install: ''Pier-Blog''.
  (Installer lukas project: ''pier2'') install: ''Pier-Book''.
  (Installer lukas project: ''pier2addons'') install: ''Pier-Setup''.
  (Smalltalk at: #PRDistribution)  new register.
  
  "Open Cobalt: http://opencobalt.org (Best to run this from an image in an open cobalt directory)"
  Installer ss project: ''TweakCore''; install: ''update''.
  [Installer ss project: ''TweakExtras''; install: ''update'']
  	on: (Smalltalk at: #CUnsynchronizedModification) do: [:ex | ex resume].
  Installer cobalt project: ''Tweak'';
  	answer: ''Would you like to conserve memory at all costs?'' with: true;
  	answer: ''Password for interactive VNC connections?'' with: ''cobalt'';
  	answer: ''Would you like to add the RFBServer to the World open menu?'' with: true;
  	install: ''update''
  !!
+ ]style[(189 2 139 15 17 1 32 3 108 2 40 12 11 1 30 3 8 1 11 3 8 1 12 3 8 1 11 3 8 1 11 3 8 1 11 3 8 1 10 3 57 12 2 1 8 1 13 2 8 1 13 13 3 1 10 2 8 13 3 1 8 2 8 12 3 1 10 4 43 12 2 1 8 1 21 2 8 1 28 3 1 10 3 1 27 1 1 7 1 8 1 12 2 5 4 3 5 8 1 16 12 11 1 39 3 8 1 13 3 8 1 14 3 8 1 13 2 16 2 35 12 2 1 8 1 21 2 8 1 26 2 21 2 44 12 2 1 8 1 21 2 8 1 34 13 3 1 33 2 4 3 35 12 2 1 8 1 21 2 8 1 26 13 3 1 25 2 4 13 3 1 28 2 4 3 34 12 2 1 8 1 21 2 8 1 22 13 3 1 21 2 4 14 5 1 8 1 7 2 8 1 11 13 5 1 8 1 7 2 8 1 11 13 5 1 8 1 13 2 8 1 12 13 3 1 15 3 3 1 8 3 97 11 2 1 8 1 11 2 8 1 8 13 2 1 8 1 13 2 8 1 8 3 3 12 3 1 28 2 3 3 2 1 1 1 2 1 6 13 6 1 8 1 7 3 7 1 49 1 5 1 4 3 7 1 43 1 5 1 8 3 7 1 61 1 5 1 4 3 8 1 8 1)c000126126,cblack;,c000126126,cblack;,c000000126,cblack;,c126000126,cblack;,c000126126,cblack;,c000126126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000126126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000126126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000126000,cblack;,c000000126,cblack;,c000000126,c000126000,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000126126,cblack;,c000126126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000126126,cblack;,c000126126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000126126,cblack;,c000126126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000126126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000126126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000126126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,cgray;,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000000,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000126,cblack;,c000000126,cblack;,c126000000,cblack;,c000000126,cblack;,c126000126,cblack;!!' readStream nextChunkText!
- ]style[(189 2 139 15 17 1 32 3 108 2 40 12 11 1 30 3 8 1 11 3 8 1 12 3 8 1 11 3 8 1 11 3 8 1 11 3 8 1 10 3 57 12 2 1 8 1 13 2 8 1 13 13 3 1 10 2 8 13 3 1 8 2 8 12 3 1 10 4 44 11 2 1 8 1 21 2 8 1 28 14 3 1 1 28 7 11 11 2 5 4 3 5 35 12 2 1 8 1 21 2 8 1 26 2 21 2 44 12 2 1 8 1 21 2 8 1 34 13 3 1 33 2 4 3 35 12 2 1 8 1 21 2 8 1 26 13 3 1 25 2 4 13 3 1 28 2 4 3 34 12 2 1 8 1 21 2 8 1 22 13 3 1 21 2 4 14 5 1 8 1 7 2 8 1 11 13 5 1 8 1 7 2 8 1 11 13 5 1 8 1 13 2 8 1 12 13 3 1 15 3 3 1 8 101 460 1)c000120120,cblack;,c000120120,cblack;,c000000120,cblack;,c120000120,cblack;,c000120120,cblack;,c000120120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000125125,cblack;,c000000125,cblack;,c000000125,cblack;,c125000125,cblack;,c000000125,cblack;,c125000125,cblack;,c000000125,cblack;,c000000125,cblack;,c000000125,cblack;,c000000125,cblack;,c000000125,cblack;,c000000125,cblack;,c000000125,cblack;,c000000125,cblack;,c000120120,cblack;,c000000123,cblack;,c000000123,cblack;,c123000123,cblack;,c000000123,cblack;,c123000123,cblack;,c000000120,cblack;,c000000120,cblack;,c000000123,cblack;,c000000123,cblack;,c000000123,cblack;,c000000123,cblack;,c000120120,cblack;,c000000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000120120,cblack;,c000120120,cblack;,c000000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000120120,cblack;,c000000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000120120,cblack;,c000000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c120000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,c000000120,cblack;,,cblack;!!' readStream nextChunkText!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>squeakOnlineResources (in category 'submenu - help') -----
  squeakOnlineResources
  	^'Squeak web sites
+ 	Main Squeak site						http://www.squeak.org
+ 	Weekly Squeak							http://news.squeak.org
+ 	Oversight Board						http://board.squeak.org
+ 	Downloads for many versions			http://ftp.squeak.org
+ 	Development of the virtual machine	http://squeakvm.org
+ 	Google+ Page
+ 		https://plus.google.com/u/0/b/115950529692424242526/
- 	http://www.squeak.org	- The main Squeak site.
- 	http://news.squeak.org	- The Weekly Squeak
- 	http://board.squeak.org	- The Squeak Oversight Board
- 	http://ftp.squeak.org	- Downloads for many Squeak versions.
- 	http://squeakvm.org	- Development of the Squeak virtual machine
  	
  Squeak-dev - The main Squeak mailing list
  	http://lists.squeakfoundation.org/mailman/listinfo/squeak-dev
  	http://dir.gmane.org/gmane.comp.lang.smalltalk.squeak.general
  	http://n4.nabble.com/Squeak-Dev-f45488.html
  
  Squeak-Beginners - The place to ask even the most basic questions
  	http://lists.squeakfoundation.org/mailman/listinfo/beginners
  	http://dir.gmane.org/gmane.comp.lang.smalltalk.squeak.beginners
  	http://n4.nabble.com/Squeak-Beginners-f107673.html
  
  Squeak By Example
  	http://www.squeakbyexample.org/
  
  Squeak, Open Personal Computing and Multimedia
  	http://coweb.cc.gatech.edu/squeakbook/
  	http://stephane.ducasse.free.fr/FreeBooks/CollectiveNBlueBook/
  
  Squeak, Open Personal Computing for Multimedia
  	http://www.cc.gatech.edu/~mark.guzdial/drafts/
  	http://stephane.ducasse.free.fr/FreeBooks/GuzdialBookDrafts/
  
  More Books about Squeak and Smalltalk
  	http://stephane.ducasse.free.fr/FreeBooks.html
  !!
+ ]style[(16 316 41 173 65 181 17 35 46 106 46 112 37 49)bu,,bu,,bu,,bu,,bu,,bu,,bu,!!' readStream nextChunkText!
- ]style[(16 274 41 173 65 181 17 35 46 106 46 112 37 49)bu,,bu,,bu,,bu,,bu,,bu,,bu,!!' readStream nextChunkText!

Item was added:
+ ----- Method: TheWorldMainDockingBar>>welcomeFutureDirections (in category 'submenu - help') -----
+ welcomeFutureDirections
+ 	
+ 	^'
+ - This image is ~15M. If you execute - Smalltalk unloadAllKnownPackages - it will become ~10M 
+ 
+ - A SqueakCore image is available at http://ftp.squeak.org/4.3
+ 
+ - A reasonable target is the creation of a smaller image, which may be a task before the community
+ 
+ - A place to explore where to make reductions is likely the removal/replacement of GUIs
+ 
+ - Once we have a smaller core image, we can employ Andreas Raab''s memo [1] on how to load code back into the image. This will be based on tests delineating the separate responsibilities of core and application developers
+ 
+  [1]]http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-May/150658.html
+ 
+ '!

Item was removed:
- ----- Method: TheWorldMainDockingBar>>welcomeToSqueak42 (in category 'submenu - help') -----
- welcomeToSqueak42
- 	^'This is a list of the main achievements that went into the trunk image.
- 
- Ready for next-generation VM
- A new virtual-machine, known as "Cog", is about to be released for Squeak.  It''s a complete rewrite from the ground-up, employing a Context-to-Stack mapping design onto which a JIT compiler for Intel-compatible hardware results in, roughly, a 3X, across-the-board performance improvement.  Specific Benchmarks vary much more widely (from 1x to 5x, with some people claiming 10x for specifics.
- 
- Significant class-library and IDE improvements
- Many enhancements, fixes, documentation and performance improvements to the class-library and IDE tools.  A new number parser allows greater flexibility in the expression of numbers.  Finalization enhancements.
- 
- An efficient window-resizing gesture allows Squeak windows to be quickly and easily manipulated, much like modern "tabletop" technologies.
- 
- There were also many enhancements to the internal text editor.
- 
- High-precision Clock
- Squeak''s internal timer clock has been improved from millisecond to microsecond level precision. 
- 
- A Tidier image
- A tidier image and code-base. Introduced a cleanUp protocol, removed the last direct users of CrLfFileStream, j3 support, SyntaxError, and more. Various packages and fonts can now be unloaded, if a smaller image is desired.
- 
- The last of the underscore assignments have been replaced with ANSI assignments.
- 
- There was also a significant refactoring and unification of Smalltalk and SmalltalkImage globals. 
- 
- stdio interface
- Squeak now includes an API for accessing the operating system stdio (supported only on newer VM''s). 
- 
- Industrial command-line interface
- The command-line interface has been improved to properly support relative-path qualification to the input script. 
- 
- Compatible with signature Squeak packages
- This version of the Squeak platform is compatible with several unique packages like Croquet[*], Tweak, Seaside, muO, Magma, and more.  See "Extending the System" under the Help menu for more information.
- 
- Better Documentation
- HelpSystem has been added to the core image to provide a light-weight framework for improved documentation. It can be accessed via Help>>Help Browser. Various bits of documentation, including how to load some important packages, has been added.
- 
- SUnit
- All test cases now have an associated timeout after which the test is considered failed. The purpose of the timeout is to catch issues like infinite loops, unexpected user input etc. in automated test environments. Timeouts can be set on an individual test basis using the <timeout: seconds> tag or for an entire test case by implementing the #defaultTimeout method.
- 
- Graphics
- Reading PNG images has been significantly sped up for some common cases. The improvements are in 50-200x range and heavily affect interactive uses of such files.
- 
- Stricter Rectangles assert screen coordinate orientation. Empty Rectangles no longer #intersect: anything. 
- 
- Support for translucent fonts.
- 
- MVC
- Support for classic MVC has been restored to Squeak.  MVC provides a primitive, but ultra-high-speed user-interface based on classic model-view-controller architecture.
- !!
- ]style[(73 28 394 48 416 20 100 14 408 15 103 33 115 1 1 41 206 20 247 5 369 8 303 5 170),bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,!!' readStream nextChunkText!

Item was added:
+ ----- Method: TheWorldMainDockingBar>>welcomeToSqueak43 (in category 'submenu - help') -----
+ welcomeToSqueak43
+ 	^'Squeak 4.3 - Rice Paper 
+ 
+ This is a list of the main achievements that went into the trunk image.
+ 
+ Networking
+ - better control of socket connection timeouts
+ 
+ Threads
+ - added support for threaded VMs
+ 
+ Package Management
+ - packages specifiable either with or without a version-number in Installer
+ - extended support for MCConfigurations to regular MCDirectoryRepositorys
+ 
+ Math
+ - corrected Complex so arcSin and arcCos let (1 arTanh) return inf
+ 
+ User Interface
+ - full-screen toggle option has been moved out from the menu and onto the bar directly just to the right of the clock for one-click access 
+ - rejection of literals with superfluous # at the beginning like #$a #123 ##foo ##(1 2 3)
+ - TextEditor is event driven sensor usage is banned from it
+ - ancient behavior of selecting whole text when clicking twice before first or twice after last character is restored
+ - drag/drop between inspectors changed to drag a field onto another field to replace the object in it
+ - updated button for "what to show" on CodeHolder similar to Squeak 3.8 
+ - changes enabling both Yellow and Blue buttons from a two-button mouse in Cog VM
+ 
+ Compiler
+ - Compiler changed to create subclasses of CompiledMethod
+ - blocks and MessageSends are exchangeable in more situations
+ 
+ Morphic
+ - SMxMorphicProject now able to host a SimpleMorphic World
+ - when present a SMxMorphicProject is made available in the World menu
+ !!
+ ]style[(24 75 10 48 9 34 18 152 4 69 14 667 8 120 1 1 7 131)FBitstreamVeraSans#20.0,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,!!' readStream nextChunkText!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>welcomeWorkspacesOn: (in category 'submenu - help') -----
  welcomeWorkspacesOn: menu
  
  	menu addItem:[:item|
  		item
+ 			contents: 'Welcome to Squeak 4.3' translated;
- 			contents: 'Welcome to Squeak 4.2' translated;
  			help: 'A Welcome Workspace' translated;
  			target: self;
  			selector: #showWelcomeText:label:in:;
  			arguments: {
+ 				#welcomeToSqueak43. 
+ 				'Welcome to Squeak 4.3'. 
+ 				(200 at 200 extent: 500 at 300)
+ 			}].
+ 	menu addItem:[:item|
+ 		item
+ 			contents: 'Welcome Future Directions' translated;
+ 			help: 'A Welcome Workspace' translated;
+ 			target: self;
+ 			selector: #showWelcomeText:label:in:;
+ 			arguments: {
+ 				#welcomeFutureDirections. 
+ 				'Future Directions'. 
- 				#welcomeToSqueak42. 
- 				'Welcome to Squeak 4.2'. 
  				(140 at 140 extent: 500 at 300)
  			}].
  	menu addItem:[:item|
  		item
  			contents: 'The Squeak User Interface' translated;
  			help: 'A Welcome Workspace' translated;
  			target: self;
  			selector: #showWelcomeText:label:in:;
  			arguments: {
  				#squeakUserInterface. 
  				'The Squeak User Interface'. 
  				(160 at 160 extent: 500 at 300)
  			}].
  	menu addItem:[:item|
  		item
  			contents: 'Working With Squeak' translated;
  			help: 'A Welcome Workspace' translated;
  			target: self;
  			selector: #showWelcomeText:label:in:;
  			arguments: {
  				#workingWithSqueak. 
  				'Working With Squeak'. 
  				(180 at 180 extent: 500 at 300)
  			}].
  	menu addItem:[:item|
  		item
  			contents: 'License Information' translated;
  			help: 'A Welcome Workspace' translated;
  			target: self;
  			selector: #showWelcomeText:label:in:;
  			arguments: {
  				#licenseInformation. 
  				'License Information'. 
  				(200 at 200 extent: 500 at 300)
  			}].!



More information about the Squeak-dev mailing list