[squeak-dev] The Trunk: Morphic-dtl.297.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jan 4 23:50:47 UTC 2010


David T. Lewis uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-dtl.297.mcz

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

Name: Morphic-dtl.297
Author: dtl
Time: 3 January 2010, 11:54:26 am
UUID: b656a757-aedc-47a4-9014-21327212c021
Ancestors: Morphic-ar.296

Add TextEditor>>explainDelimitor: copied from ParagraphEditor, required for explain function in code panes.

Run FixUnderscores on package Morphic to update methods adopted from Cuis.
Note: Did not fix underscores in MorphicModel class>>compileAccessorsFor:


=============== Diff against Morphic-ar.296 ===============

Item was changed:
  ----- Method: TextEditor>>reverseSelection (in category 'current selection') -----
  reverseSelection
  	"Reverse the valence of the current selection highlighting."
+ 	selectionShowing := selectionShowing not.
- 	selectionShowing _ selectionShowing not.
  	paragraph reverseFrom: self pointBlock to: self markBlock!

Item was changed:
  ----- Method: TextEditor>>completeSymbol:lastOffering: (in category 'private') -----
  completeSymbol: hintText lastOffering: selectorOrNil
  	"Invoked by Ctrl-q when there is only a caret.
  		Do selector-completion, i.e., try to replace the preceding identifier by a
  		selector that begins with those characters & has as many keywords as possible.
  	 	Leave two spaces after each colon (only one after the last) as space for
  		arguments.  Put the caret after the space after the first keyword.  If the
  		user types Ctrl-q again immediately, choose a different selector.
  	 Undoer: #undoQuery:lastOffering:; Redoer: itself.
  	If redoing, just redisplay the last offering, selector[OrNil]."
  
  	| firstTime input prior caret newStart sym kwds outStream |
+ 	firstTime := self isRedoing
+ 		ifTrue: [prior := sym := selectorOrNil. true]
- 	firstTime _ self isRedoing
- 		ifTrue: [prior _ sym _ selectorOrNil. true]
  		ifFalse: [hintText isNil].
  	firstTime
  		ifTrue: "Initial Ctrl-q (or redo)"					
+ 			[caret := self startIndex.
- 			[caret _ self startIndex.
  			self selectPrecedingIdentifier.
+ 			input := self selection]
- 			input _ self selection]
  		ifFalse: "Repeated Ctrl-q"
+ 			[caret := UndoInterval first + hintText size.
- 			[caret _ UndoInterval first + hintText size.
  			self selectInvisiblyFrom: UndoInterval first to: UndoInterval last.
+ 			input := hintText.
+ 			prior := selectorOrNil].
- 			input _ hintText.
- 			prior _ selectorOrNil].
  	(input size ~= 0 and: [sym ~~ nil or:
+ 			[(sym := Symbol thatStarts: input string skipping: prior) ~~ nil]])
- 			[(sym _ Symbol thatStarts: input string skipping: prior) ~~ nil]])
  		ifTrue: "found something to offer"
+ 			[newStart := self startIndex.
+ 			outStream := WriteStream on: (String new: 2 * sym size).
+ 			1 to: (kwds := sym keywords) size do:
- 			[newStart _ self startIndex.
- 			outStream _ WriteStream on: (String new: 2 * sym size).
- 			1 to: (kwds _ sym keywords) size do:
  				[:i |
  				outStream nextPutAll: (kwds at: i).
+ 				i = 1 ifTrue: [caret := newStart + outStream contents size + 1].
- 				i = 1 ifTrue: [caret _ newStart + outStream contents size + 1].
  				outStream nextPutAll:
  					(i < kwds size ifTrue: ['  '] ifFalse: [' '])].
+ 			UndoSelection := input.
- 			UndoSelection _ input.
  			self deselect; zapSelectionWith: outStream contents asText.
  			self undoer: #undoQuery:lastOffering: with: input with: sym]
  		ifFalse: "no more matches"
  			[firstTime ifFalse: "restore original text & set up for a redo"
+ 				[UndoSelection := self selection.
- 				[UndoSelection _ self selection.
  				self deselect; zapSelectionWith: input.
  				self undoer: #completeSymbol:lastOffering: with: input with: prior.
+ 				Undone := true].
- 				Undone _ true].
  			morph flash].
  	self selectAt: caret!

Item was changed:
  ----- Method: SmalltalkEditor class>>initializeShiftCmdKeyShortcuts (in category 'keyboard shortcut tables') -----
  initializeShiftCmdKeyShortcuts 
  	"Initialize the shift-command-key (or control-key) shortcut table."
  	"NOTE: if you don't know what your keyboard generates, use Sensor kbdTest"
  	"wod 11/3/1998: Fix setting of cmdMap for shifted keys to actually use the 
  	capitalized versions of the letters.
  	TPR 2/18/99: add the plain ascii values back in for those VMs that don't return the shifted values."
  
  	"SmalltalkEditor initialize"
  
  	| cmds |
  	super initializeShiftCmdKeyShortcuts.
  	
+ 	cmds := #(
- 	cmds _ #(
  		$a	argAdvance:
  		$b	browseItHere:
  		$e	methodStringsContainingIt:
  		$f	displayIfFalse:
  		$g	fileItIn:
  		$i	exploreIt:
  		$n	referencesToIt:
  		$t	displayIfTrue:
  		$v	pasteInitials:
  		$w	methodNamesContainingIt:
  	).
  	1 to: cmds size by: 2 do: [ :i |
  		shiftCmdActions at: ((cmds at: i) asciiValue + 1) put: (cmds at: i + 1).			"plain keys"
  		shiftCmdActions at: ((cmds at: i) asciiValue - 32 + 1) put: (cmds at: i + 1).		"shifted keys"
  		shiftCmdActions at: ((cmds at: i) asciiValue - 96 + 1) put: (cmds at: i + 1).		"ctrl keys"
  	].!

Item was changed:
  ----- Method: TextEditor>>crWithIndent: (in category 'typing/selecting keys') -----
  crWithIndent: characterStream 
  	"Replace the current text selection with CR followed by as many tabs
  	as on the current line (+/- bracket count) -- initiated by Shift-Return."
  	| char s i tabCount |
  	sensor keyboard.		"flush character"
+ 	s := paragraph string.
+ 	i := self stopIndex.
+ 	tabCount := 0.
+ 	[(i := i-1) > 0 and: [(char := s at: i) ~= Character cr]]
- 	s _ paragraph string.
- 	i _ self stopIndex.
- 	tabCount _ 0.
- 	[(i _ i-1) > 0 and: [(char _ s at: i) ~= Character cr]]
  		whileTrue:  "Count tabs and brackets (but not a leading bracket)"
+ 		[(char = Character tab and: [i < s size and: [(s at: i+1) ~= $[ ]]) ifTrue: [tabCount := tabCount + 1].
+ 		char = $[ ifTrue: [tabCount := tabCount + 1].
+ 		char = $] ifTrue: [tabCount := tabCount - 1]].
- 		[(char = Character tab and: [i < s size and: [(s at: i+1) ~= $[ ]]) ifTrue: [tabCount _ tabCount + 1].
- 		char = $[ ifTrue: [tabCount _ tabCount + 1].
- 		char = $] ifTrue: [tabCount _ tabCount - 1]].
  	characterStream crtab: tabCount.  "Now inject CR with tabCount tabs"
  	^ false!

Item was changed:
  ----- Method: Editor>>selectWord (in category 'new selection') -----
  selectWord
  	"Select delimited text or word--the result of double-clicking."
  
  	| openDelimiter closeDelimiter direction match level leftDelimiters rightDelimiters
  	string here hereChar start stop |
+ 	string := self string.
+ 	here := self pointIndex.
- 	string _ self string.
- 	here _ self pointIndex.
  	(here between: 2 and: string size)
  		ifFalse: ["if at beginning or end, select entire string"
  			^self selectFrom: 1 to: string size].
+ 	leftDelimiters := '([{<''"
- 	leftDelimiters _ '([{<''"
  '.
+ 	rightDelimiters := ')]}>''"
- 	rightDelimiters _ ')]}>''"
  '.
+ 	openDelimiter := string at: here - 1.
+ 	match := leftDelimiters indexOf: openDelimiter.
- 	openDelimiter _ string at: here - 1.
- 	match _ leftDelimiters indexOf: openDelimiter.
  	match > 0
  		ifTrue: 
  			["delimiter is on left -- match to the right"
+ 			start := here.
+ 			direction := 1.
+ 			here := here - 1.
+ 			closeDelimiter := rightDelimiters at: match]
- 			start _ here.
- 			direction _ 1.
- 			here _ here - 1.
- 			closeDelimiter _ rightDelimiters at: match]
  		ifFalse: 
+ 			[openDelimiter := string at: here.
+ 			match := rightDelimiters indexOf: openDelimiter.
- 			[openDelimiter _ string at: here.
- 			match _ rightDelimiters indexOf: openDelimiter.
  			match > 0
  				ifTrue: 
  					["delimiter is on right -- match to the left"
+ 					stop := here - 1.
+ 					direction := -1.
+ 					closeDelimiter := leftDelimiters at: match]
- 					stop _ here - 1.
- 					direction _ -1.
- 					closeDelimiter _ leftDelimiters at: match]
  				ifFalse: ["no delimiters -- select a token"
+ 					direction := -1]].
+ 	level := 1.
- 					direction _ -1]].
- 	level _ 1.
  	[level > 0 and: [direction > 0
  			ifTrue: [here < string size]
  			ifFalse: [here > 1]]]
  		whileTrue: 
+ 			[hereChar := string at: (here := here + direction).
- 			[hereChar _ string at: (here _ here + direction).
  			match = 0
  				ifTrue: ["token scan goes left, then right"
  					hereChar tokenish
  						ifTrue: [here = 1
  								ifTrue: 
+ 									[start := 1.
- 									[start _ 1.
  									"go right if hit string start"
+ 									direction := 1]]
- 									direction _ 1]]
  						ifFalse: [direction < 0
  								ifTrue: 
+ 									[start := here + 1.
- 									[start _ here + 1.
  									"go right if hit non-token"
+ 									direction := 1]
+ 								ifFalse: [level := 0]]]
- 									direction _ 1]
- 								ifFalse: [level _ 0]]]
  				ifFalse: ["bracket match just counts nesting level"
  					hereChar = closeDelimiter
+ 						ifTrue: [level := level - 1"leaving nest"]
- 						ifTrue: [level _ level - 1"leaving nest"]
  						ifFalse: [hereChar = openDelimiter 
+ 									ifTrue: [level := level + 1"entering deeper nest"]]]].
- 									ifTrue: [level _ level + 1"entering deeper nest"]]]].
  
+ 	level > 0 ifTrue: ["in case ran off string end"	here := here + direction].
- 	level > 0 ifTrue: ["in case ran off string end"	here _ here + direction].
  	direction > 0
  		ifTrue: [self selectFrom: start to: here - 1]
  		ifFalse: [self selectFrom: here + 1 to: stop]!

Item was changed:
  ----- Method: TextEditor>>exchangeWith: (in category 'private') -----
  exchangeWith: prior
  	"If the prior selection is non-overlapping and legal, exchange the text of
  	 it with the current selection and leave the currently selected text selected
  	 in the location of the prior selection (or leave a caret after a non-caret if it was
  	 exchanged with a caret).  If both selections are carets, flash & do nothing.
  	 Don't affect the paste buffer.  Undoer: itself; Redoer: Undoer."
  
  	| start stop before selection priorSelection delta altInterval |
+ 	start := self startIndex.
+ 	stop := self stopIndex - 1.
- 	start _ self startIndex.
- 	stop _ self stopIndex - 1.
  	((prior first <= prior last) | (start <= stop) "Something to exchange" and:
  			[self isDisjointFrom: prior])
  		ifTrue:
+ 			[before := prior last < start.
+ 			selection := self selection.
+ 			priorSelection := paragraph text copyFrom: prior first to: prior last.
- 			[before _ prior last < start.
- 			selection _ self selection.
- 			priorSelection _ paragraph text copyFrom: prior first to: prior last.
  
+ 			delta := before ifTrue: [0] ifFalse: [priorSelection size - selection size].
- 			delta _ before ifTrue: [0] ifFalse: [priorSelection size - selection size].
  			self zapSelectionWith: priorSelection.
  			self selectFrom: prior first + delta to: prior last + delta.
  
+ 			delta := before ifTrue: [stop - prior last] ifFalse: [start - prior first].
- 			delta _ before ifTrue: [stop - prior last] ifFalse: [start - prior first].
  			self zapSelectionWith: selection.
+ 			altInterval := prior first + delta to: prior last + delta.
- 			altInterval _ prior first + delta to: prior last + delta.
  			self undoer: #exchangeWith: with: altInterval.
  			"If one was a caret, make it otherInterval & leave the caret after the other"
  			prior first > prior last ifTrue: [self selectAt: UndoInterval last + 1].
+ 			otherInterval := start > stop
- 			otherInterval _ start > stop
  				ifTrue: [self selectAt: altInterval last + 1. UndoInterval]
  				ifFalse: [altInterval]]
  		ifFalse:
  			[morph flash]!

Item was changed:
  ----- Method: TextEditor>>shiftEnclose: (in category 'editing keys') -----
  shiftEnclose: characterStream
  	"Insert or remove bracket characters around the current selection.
  	 Flushes typeahead."
  
  	| char left right startIndex stopIndex oldSelection which text |
+ 	char := sensor keyboard.
+ 	char = $9 ifTrue: [ char := $( ].
+ 	char = $, ifTrue: [ char := $< ].
+ 	char = $[ ifTrue: [ char := ${ ].
+ 	char = $' ifTrue: [ char := $" ].
+ 	char asciiValue = 27 ifTrue: [ char := ${ ].	"ctrl-["
- 	char _ sensor keyboard.
- 	char = $9 ifTrue: [ char _ $( ].
- 	char = $, ifTrue: [ char _ $< ].
- 	char = $[ ifTrue: [ char _ ${ ].
- 	char = $' ifTrue: [ char _ $" ].
- 	char asciiValue = 27 ifTrue: [ char _ ${ ].	"ctrl-["
  
  	self closeTypeIn.
+ 	startIndex := self startIndex.
+ 	stopIndex := self stopIndex.
+ 	oldSelection := self selection.
+ 	which := '([<{"''' indexOf: char ifAbsent: [1].
+ 	left := '([<{"''' at: which.
+ 	right := ')]>}"''' at: which.
+ 	text := paragraph text.
- 	startIndex _ self startIndex.
- 	stopIndex _ self stopIndex.
- 	oldSelection _ self selection.
- 	which _ '([<{"''' indexOf: char ifAbsent: [1].
- 	left _ '([<{"''' at: which.
- 	right _ ')]>}"''' at: which.
- 	text _ paragraph text.
  	((startIndex > 1 and: [stopIndex <= text size])
  			and: [ (text at: startIndex-1) = left and: [(text at: stopIndex) = right]])
  		ifTrue: [
  			"already enclosed; strip off brackets"
  			self selectFrom: startIndex-1 to: stopIndex.
  			self replaceSelectionWith: oldSelection]
  		ifFalse: [
  			"not enclosed; enclose by matching brackets"
  			self replaceSelectionWith:
  				(Text string: (String with: left), oldSelection string, (String with: right) attributes: emphasisHere).
  			self selectFrom: startIndex+1 to: stopIndex].
  	^true!

Item was changed:
  ----- Method: Editor>>backWord: (in category 'typing/selecting keys') -----
  backWord: characterStream 
  	"If the selection is not a caret, delete it and leave it in the backspace buffer.
  	 Else if there is typeahead, delete it.
  	 Else, delete the word before the caret."
  
  	| startIndex |
  	sensor keyboard.
  	characterStream isEmpty
  		ifTrue:
  			[self hasCaret
  				ifTrue: "a caret, delete at least one character"
+ 					[startIndex := 1 max: self markIndex - 1.
- 					[startIndex _ 1 max: self markIndex - 1.
  					[startIndex > 1 and:
  						[(self string at: startIndex - 1) tokenish]]
  						whileTrue:
+ 							[startIndex := startIndex - 1]]
- 							[startIndex _ startIndex - 1]]
  				ifFalse: "a non-caret, just delete it"
+ 					[startIndex := self markIndex].
- 					[startIndex _ self markIndex].
  			self backTo: startIndex]
  		ifFalse:
  			[characterStream reset].
  	^false!

Item was changed:
  ----- Method: TextEditor>>indent:fromStream:toStream: (in category 'private') -----
  indent: delta fromStream: inStream toStream: outStream
  	"Append the contents of inStream to outStream, adding or deleting delta or -delta
  	 tabs at the beginning, and after every CR except a final CR.  Do not add tabs
  	 to totally empty lines, and be sure nothing but tabs are removed from lines."
  
  	| ch skip cr tab prev atEnd |
+ 	cr := Character cr.
+ 	tab := Character tab.
- 	cr _ Character cr.
- 	tab _ Character tab.
  	delta > 0
  		ifTrue: "shift right"
+ 			[prev := cr.
+ 			 [ch := (atEnd := inStream atEnd) ifTrue: [cr] ifFalse: [inStream next].
- 			[prev _ cr.
- 			 [ch _ (atEnd _ inStream atEnd) ifTrue: [cr] ifFalse: [inStream next].
  			  (prev == cr and: [ch ~~ cr]) ifTrue:
  				[delta timesRepeat: [outStream nextPut: tab]].
  			  atEnd]
  				whileFalse:
  					[outStream nextPut: ch.
+ 					prev := ch]]
- 					prev _ ch]]
  		ifFalse: "shift left"
+ 			[skip := delta. "a negative number"
- 			[skip _ delta. "a negative number"
  			 [inStream atEnd] whileFalse:
+ 				[((ch := inStream next) == tab and: [skip < 0]) ifFalse:
- 				[((ch _ inStream next) == tab and: [skip < 0]) ifFalse:
  					[outStream nextPut: ch].
+ 				skip := ch == cr ifTrue: [delta] ifFalse: [skip + 1]]]!
- 				skip _ ch == cr ifTrue: [delta] ifFalse: [skip + 1]]]!

Item was changed:
  ----- Method: TextEditor>>prettyPrint: (in category 'menu messages') -----
  prettyPrint: decorated
  	"Reformat the contents of the receiver's view (a Browser)."
  
  	| selectedClass newText |
  	model selectedMessageName ifNil: [^ morph flash].
+ 	selectedClass := model selectedClassOrMetaClass.
+ 	newText := selectedClass compilerClass new
- 	selectedClass _ model selectedClassOrMetaClass.
- 	newText _ selectedClass compilerClass new
  		format: self text
  		in: selectedClass
  		notifying: self
  		decorated: decorated.
  	newText ifNotNil:
  		[self deselect; selectInvisiblyFrom: 1 to: paragraph text size.
  		self replaceSelectionWith: (newText asText makeSelectorBoldIn: selectedClass).
  		self selectAt: 1]!

Item was changed:
  ----- Method: TextLine>>justifiedPadFor:font: (in category 'scanning') -----
  justifiedPadFor: spaceIndex font: aFont
  	"Compute the width of pad for a given space in a line of justified text."
  
  	| pad |
  	internalSpaces = 0 ifTrue: [^0].
  	^(aFont notNil and:[aFont isSubPixelPositioned])
  		ifTrue:[paddingWidth * 1.0 / internalSpaces]
  		ifFalse:[
+ 			pad := paddingWidth // internalSpaces.
- 			pad _ paddingWidth // internalSpaces.
  			spaceIndex <= (paddingWidth \\ internalSpaces)
  				ifTrue: [pad + 1]
  				ifFalse: [pad]]
  		!

Item was changed:
  ----- Method: TextEditor>>selectedSymbol (in category 'menu messages') -----
  selectedSymbol
  	"Return the currently selected symbol, or nil if none.  Spaces, tabs and returns are ignored"
  
  	| aString |
  	self hasCaret ifTrue: [^ nil].
+ 	aString := self selection string copyWithoutAll:
- 	aString _ self selection string copyWithoutAll:
  		{Character space.  Character cr.  Character tab}.
  	aString size = 0 ifTrue: [^ nil].
  	Symbol hasInterned: aString  ifTrue: [:sym | ^ sym].
  
  	^ nil!

Item was changed:
  ----- Method: TextEditor>>explainTemp: (in category 'explain') -----
  explainTemp: string 
  	"Is string the name of a temporary variable (or block argument variable)?"
  
  	| selectedClass tempNames i reply methodNode method msg |
  	(model respondsTo: #selectedMessageName) ifFalse: [^ nil].
+ 	(msg := model selectedMessageName) ifNil: [^nil].	"not in a message"
+ 	selectedClass := model selectedClassOrMetaClass.
+ 	tempNames := selectedClass parserClass new 
- 	(msg _ model selectedMessageName) ifNil: [^nil].	"not in a message"
- 	selectedClass _ model selectedClassOrMetaClass.
- 	tempNames _ selectedClass parserClass new 
  			parseArgsAndTemps: model selectedMessage notifying: nil.
+ 	method := selectedClass compiledMethodAt: msg.
+ 	(i := tempNames findFirst: [:each | each = string]) = 0 ifTrue: [
- 	method _ selectedClass compiledMethodAt: msg.
- 	(i _ tempNames findFirst: [:each | each = string]) = 0 ifTrue: [
  		(method numTemps > tempNames size)
  			ifTrue: 
  				["It must be an undeclared block argument temporary"
+ 				methodNode := selectedClass compilerClass new
- 				methodNode _ selectedClass compilerClass new
  							parse: model selectedMessage
  							in: selectedClass
  							notifying: nil.
+ 				tempNames := methodNode tempNames]
- 				tempNames _ methodNode tempNames]
  			ifFalse: [^nil]].
+ 	(i := tempNames findFirst: [:each | each = string]) > 0 ifTrue: [i > method numArgs
+ 			ifTrue: [reply := '"is a temporary variable in this method"']
+ 			ifFalse: [reply := '"is an argument to this method"']].
- 	(i _ tempNames findFirst: [:each | each = string]) > 0 ifTrue: [i > method numArgs
- 			ifTrue: [reply _ '"is a temporary variable in this method"']
- 			ifFalse: [reply _ '"is an argument to this method"']].
  	^reply!

Item was changed:
  ----- Method: TextEditor>>undoCutCopy: (in category 'undoers') -----
  undoCutCopy: oldPasteBuffer
  	"Undo of a cut, copy, or any edit that changed CurrentSelection.  Be sure
  	 undo-copy does not lock the model.  Redoer: itself, so never isRedoing."
  
  	| recentCut |
+ 	recentCut := self clipboardText.	
- 	recentCut _ self clipboardText.	
  	UndoSelection size = UndoInterval size
  		ifFalse: [self replaceSelectionWith: UndoSelection].
  	self clipboardTextPut: oldPasteBuffer.
  	self undoer: #undoCutCopy: with: recentCut!

Item was changed:
  ----- Method: TextEditor>>explainInst: (in category 'explain') -----
  explainInst: string 
  	"Is string an instance variable of this class?"
  	| classes cls |
  
  	(model respondsTo: #selectedClassOrMetaClass) ifTrue: [
+ 		cls := model selectedClassOrMetaClass].
- 		cls _ model selectedClassOrMetaClass].
  	cls ifNil: [^ nil].	  "no class known"
+ 	classes := (Array with: cls)
- 	classes _ (Array with: cls)
  				, cls allSuperclasses.
+ 	classes := classes detect: [:each | (each instVarNames
- 	classes _ classes detect: [:each | (each instVarNames
  			detect: [:name | name = string] ifNone: [])
  			~~ nil] ifNone: [^nil].
+ 	classes := classes printString.
- 	classes _ classes printString.
  	^ '"is an instance variable of the receiver; defined in class ' , classes , 
  		'"\' withCRs , classes , ' systemNavigation browseAllAccessesTo: ''' , string , ''' from: ', classes, '.'!

Item was changed:
  ----- Method: TextEditor>>makeCapitalized: (in category 'editing keys') -----
  makeCapitalized: characterStream 
  	"Force the current selection to uppercase.  Triggered by Cmd-X."
  	| prev |
  	sensor keyboard.		"flush the triggering cmd-key character"
+ 	prev := $-.  "not a letter"
- 	prev _ $-.  "not a letter"
  	self replaceSelectionWith: (Text fromString:
  			(self selection string collect:
+ 				[:c | prev := prev isLetter ifTrue: [c asLowercase] ifFalse: [c asUppercase]])).
- 				[:c | prev _ prev isLetter ifTrue: [c asLowercase] ifFalse: [c asUppercase]])).
  	^ true!

Item was changed:
  ----- Method: TextEditor>>blinkPrevParen (in category 'parenblinking') -----
  blinkPrevParen
  	| openDelimiter closeDelimiter level string here hereChar |
+ 	string := paragraph text string.
+ 	here := pointBlock stringIndex.
+ 	openDelimiter := sensor keyboardPeek.
+ 	closeDelimiter := '([{' at: (')]}' indexOf: openDelimiter).
+ 	level := 1.
- 	string _ paragraph text string.
- 	here _ pointBlock stringIndex.
- 	openDelimiter _ sensor keyboardPeek.
- 	closeDelimiter _ '([{' at: (')]}' indexOf: openDelimiter).
- 	level _ 1.
  	[level > 0 and: [here > 2]]
  		whileTrue:
+ 			[hereChar := string at: (here := here - 1).
- 			[hereChar _ string at: (here _ here - 1).
  			hereChar = closeDelimiter
  				ifTrue:
+ 					[level := level - 1.
- 					[level _ level - 1.
  					level = 0
  						ifTrue: [^ self blinkParenAt: here]]
  				ifFalse:
  					[hereChar = openDelimiter
+ 						ifTrue: [level := level + 1]]]!
- 						ifTrue: [level _ level + 1]]]!

Item was changed:
  ----- Method: TextEditor>>doneTyping (in category 'typing support') -----
  doneTyping
+ 	beginTypeInBlock := nil!
- 	beginTypeInBlock _ nil!

Item was changed:
  ----- Method: TextEditor>>explainChar: (in category 'explain') -----
  explainChar: string
  	"Does string start with a special character?"
  
  	| char |
+ 	char := string at: 1.
- 	char _ string at: 1.
  	char = $. ifTrue: [^'"Period marks the end of a Smalltalk statement.  A period in the middle of a number means a decimal point.  (The number is an instance of class Float)."'].
  	char = $' ifTrue: [^'"The characters between two single quotes are made into an instance of class String"'].
  	char = $" ifTrue: [^'"Double quotes enclose a comment.  Smalltalk ignores everything between double quotes."'].
  	char = $# ifTrue: [^'"The characters following a hash mark are made into an instance of class Symbol.  If parenthesis follow a hash mark, an instance of class Array is made.  It contains literal constants."'].
  	(char = $( or: [char = $)]) ifTrue: [^'"Expressions enclosed in parenthesis are evaluated first"'].
  	(char = $[ or: [char = $]]) ifTrue: [^'"The code inside square brackets is an unevaluated block of code.  It becomes an instance of BlockContext and is usually passed as an argument."'].
  	(char = ${ or: [char = $}]) ifTrue: [^ '"A sequence of expressions separated by periods, when enclosed in curly braces, are evaluated to yield the elements of a new Array"'].
  	(char = $< or: [char = $>]) ifTrue: [^'"<primitive: xx> means that this method is usually preformed directly by the virtual machine.  If this method is primitive, its Smalltalk code is executed only when the primitive fails."'].
  	char = $^ ifTrue: [^'"Uparrow means return from this method.  The value returned is the expression following the ^"'].
  	char = $| ifTrue: [^'"Vertical bars enclose the names of the temporary variables used in this method.  In a block, the vertical bar separates the argument names from the rest of the code."'].
  	char = $_ ifTrue: [^'"Left arrow means assignment.  The value of the expression after the left arrow is stored into the variable before it."'].
  	char = $; ifTrue: [^'"Semicolon means cascading.  The message after the semicolon is sent to the same object which received the message before the semicolon."'].
  	char = $: ifTrue: [^'"A colon at the end of a keyword means that an argument is expected to follow.  Methods which take more than one argument have selectors with more than one keyword.  (One keyword, ending with a colon, appears before each argument).', '\\' withCRs, 'A colon before a variable name just inside a block means that the block takes an agrument.  (When the block is evaluated, the argument will be assigned to the variable whose name appears after the colon)."'].
  	char = $$ ifTrue: [^'"The single character following a dollar sign is made into an instance of class Character"'].
  	char = $- ifTrue: [^'"A minus sign in front of a number means a negative number."'].
  	char = $e ifTrue: [^'"An e in the middle of a number means that the exponent follows."'].
  	char = $r ifTrue: [^'"An r in the middle of a bunch of digits is an instance of Integer expressed in a certain radix.  The digits before the r denote the base and the digits after it express a number in that base."'].
  	char = Character space ifTrue: [^'"the space Character"'].
  	char = Character tab ifTrue: [^'"the tab Character"'].
  	char = Character cr ifTrue: [^'"the carriage return Character"'].
  	^nil!

Item was changed:
  ----- Method: TextEditor>>hiddenInfo (in category 'editing keys') -----
  hiddenInfo
  	"In TextLinks, TextDoits, TextColor, and TextURLs, there is hidden info.  Return the entire string that was used by Cmd-6 to create this text attribute.  Usually enclosed in < >."
  
  	| attrList |
+ 	attrList := paragraph text attributesAt: (self pointIndex + self markIndex)//2.
- 	attrList _ paragraph text attributesAt: (self pointIndex + self markIndex)//2.
  	attrList do: [:attr |
  		(attr isKindOf: TextAction) ifTrue:
  			[^ self selection asString, '<', attr info, '>']].
  	"If none of the above"
  	attrList do: [:attr |
  		attr class == TextColor ifTrue:
  			[^ self selection asString, '<', attr color printString, '>']].
  	^ self selection asString, '[No hidden info]'!

Item was changed:
  ----- Method: TextEditor>>selectPrecedingIdentifier (in category 'new selection') -----
  selectPrecedingIdentifier
  	"Invisibly select the identifier that ends at the end of the selection, if any."
  
  	| string sep stop tok |
+ 	tok := false.
+ 	string := paragraph text string.
+ 	stop := self stopIndex - 1.
+ 	[stop > 0 and: [(string at: stop) isSeparator]] whileTrue: [stop := stop - 1].
+ 	sep := stop.
+ 	[sep > 0 and: [(string at: sep) tokenish]] whileTrue: [tok := true. sep := sep - 1].
- 	tok _ false.
- 	string _ paragraph text string.
- 	stop _ self stopIndex - 1.
- 	[stop > 0 and: [(string at: stop) isSeparator]] whileTrue: [stop _ stop - 1].
- 	sep _ stop.
- 	[sep > 0 and: [(string at: sep) tokenish]] whileTrue: [tok _ true. sep _ sep - 1].
  	tok ifTrue: [self selectInvisiblyFrom: sep + 1 to: stop]!

Item was changed:
  ----- Method: TextEditor>>fileItIn (in category 'menu messages') -----
  fileItIn
  	"Make a Stream on the text selection and fileIn it.
  	 1/24/96 sw: moved here from FileController; this function can be useful from any text window that shows stuff in chunk format"
  
  	| selection |
+ 	selection := self selection.
- 	selection _ self selection.
  	(ReadWriteStream on: selection string from: 1 to: selection size) fileIn
  !

Item was changed:
  ----- Method: TextEditor>>changeLfToCr: (in category 'editing keys') -----
  changeLfToCr: characterStream 
  	"Replace all LFs by CRs.
  	Triggered by Cmd-U -- useful when getting code from FTP sites
  	jmv- Modified to als change crlf by cr"
  	
  	| fixed |
  	sensor keyboard.		"flush the triggering cmd-key character"
  	
+ 	fixed := self selection string.
+ 	fixed := fixed copyReplaceAll: String crlf with: String cr.
+ 	fixed := fixed copyReplaceAll: String lf with: String cr. 
- 	fixed _ self selection string.
- 	fixed _ fixed copyReplaceAll: String crlf with: String cr.
- 	fixed _ fixed copyReplaceAll: String lf with: String cr. 
  	self replaceSelectionWith: (Text fromString: fixed).
  	^ true!

Item was changed:
  ----- Method: TextEditor>>correctFrom:to:with: (in category 'new selection') -----
  correctFrom: start to: stop with: aString
  	"Make a correction in the model that the user has authorised from somewhere else in the system (such as from the compilier).  The user's selection is not changed, only corrected."
  	| wasShowing userSelection delta loc |
  	aString = '#insert period' ifTrue:
+ 		[loc := start.
+ 		[(loc := loc-1)>0 and: [(paragraph text string at: loc) isSeparator]]
+ 			whileTrue: [loc := loc-1].
- 		[loc _ start.
- 		[(loc _ loc-1)>0 and: [(paragraph text string at: loc) isSeparator]]
- 			whileTrue: [loc _ loc-1].
  		^ self correctFrom: loc+1 to: loc with: '.'].
+ 	(wasShowing := selectionShowing) ifTrue: [ self reverseSelection ].
+ 	userSelection := self selectionInterval.
- 	(wasShowing _ selectionShowing) ifTrue: [ self reverseSelection ].
- 	userSelection _ self selectionInterval.
  
  	self selectInvisiblyFrom: start to: stop.
  	self replaceSelectionWith: aString asText.
  
+ 	delta := aString size - (stop - start + 1).
- 	delta _ aString size - (stop - start + 1).
  	self selectInvisiblyFrom:
  		userSelection first + (userSelection first > start ifFalse: [ 0 ] ifTrue: [ delta ])
  		to: userSelection last + (userSelection last > start ifFalse: [ 0 ] ifTrue: [ delta ]).
  	wasShowing ifTrue: [ self reverseSelection ].
  !

Item was changed:
  ----- Method: Morph>>openModal: (in category 'polymorph') -----
  openModal: aSystemWindow
  	"Open the given window locking the receiver until it is dismissed.
  	Answer the system window.
  	Restore the original keyboard focus when closed."
  
  	|area mySysWin keyboardFocus|
+ 	keyboardFocus := self activeHand keyboardFocus.
- 	keyboardFocus _ self activeHand keyboardFocus.
  	mySysWin := self isSystemWindow ifTrue: [self] ifFalse: [self ownerThatIsA: SystemWindow].
  	mySysWin ifNil: [mySysWin := self].
  	mySysWin modalLockTo: aSystemWindow.
  	( RealEstateAgent respondsTo: #reduceByFlaps: )
  		ifTrue:[
  			area := RealEstateAgent reduceByFlaps: RealEstateAgent maximumUsableArea]
  		ifFalse:[
  			area := RealEstateAgent maximumUsableArea].
  	aSystemWindow extent: aSystemWindow initialExtent.
  	aSystemWindow position = (0 at 0)
  		ifTrue: [aSystemWindow
  				position: self activeHand position - (aSystemWindow extent // 2)].
  	aSystemWindow
  		bounds: (aSystemWindow bounds translatedToBeWithin: area).
  	[ToolBuilder default runModal: aSystemWindow openAsIs]
  		ensure: [mySysWin modalUnlockFrom: aSystemWindow.
  				self activeHand newKeyboardFocus: keyboardFocus].
  	^aSystemWindow!

Item was changed:
  ----- Method: TextEditor>>againOnce: (in category 'private') -----
  againOnce: indices
  	"Find the next occurrence of FindText.  If none, answer false.
  	Append the start index of the occurrence to the stream indices, and, if
  	ChangeText is not the same object as FindText, replace the occurrence by it.
  	Note that the search is case-sensitive for replacements, otherwise not."
  
  	| where |
+ 	where := paragraph text findString: FindText startingAt: self stopIndex
- 	where _ paragraph text findString: FindText startingAt: self stopIndex
  				caseSensitive: ((ChangeText ~~ FindText) or: [Preferences caseSensitiveFinds]).
  	where = 0 ifTrue: [^ false].
  	self deselect; selectInvisiblyFrom: where to: where + FindText size - 1.
  	ChangeText ~~ FindText ifTrue: [self zapSelectionWith: ChangeText].
  	indices nextPut: where.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>pageHeight (in category 'private') -----
  pageHeight
  	| howManyLines visibleHeight totalHeight ratio |
+ 	howManyLines := paragraph numberOfLines.
+ 	visibleHeight := self visibleHeight.
+ 	totalHeight := self totalTextHeight.
+ 	ratio := visibleHeight / totalHeight.
- 	howManyLines _ paragraph numberOfLines.
- 	visibleHeight _ self visibleHeight.
- 	totalHeight _ self totalTextHeight.
- 	ratio _ visibleHeight / totalHeight.
  	^(ratio * howManyLines) rounded - 2!

Item was changed:
  ----- Method: TextEditor>>againOrSame:many: (in category 'private') -----
  againOrSame: useOldKeys many: many
  	"Subroutine of search: and again.  If useOldKeys, use same FindText and ChangeText as before.  If many is true, do it repeatedly.  Created 1/26/96 sw by adding the many argument to #againOrSame."
  
  	|  home indices wasTypedKey |
  
+ 	home := self selectionInterval.  "what was selected when 'again' was invoked"
- 	home _ self selectionInterval.  "what was selected when 'again' was invoked"
  
  	"If new keys are to be picked..."
  	useOldKeys ifFalse: "Choose as FindText..."
+ 		[FindText := UndoSelection.  "... the last thing replaced."
- 		[FindText _ UndoSelection.  "... the last thing replaced."
  		"If the last command was in another paragraph, ChangeText is set..."
  		paragraph == UndoParagraph ifTrue: "... else set it now as follows."
  			[UndoInterval ~= home ifTrue: [self selectInterval: UndoInterval]. "blink"
+ 			ChangeText := ((UndoMessage sends: #undoCutCopy:) and: [self hasSelection])
- 			ChangeText _ ((UndoMessage sends: #undoCutCopy:) and: [self hasSelection])
  				ifTrue: [FindText] "== objects signal no model-locking by 'undo copy'"
  				ifFalse: [self selection]]]. "otherwise, change text is last-replaced text"
  
+ 	(wasTypedKey := FindText size = 0)
- 	(wasTypedKey _ FindText size = 0)
  		ifTrue: "just inserted at a caret"
+ 			[home := self selectionInterval.
- 			[home _ self selectionInterval.
  			self replaceSelectionWith: self nullText.  "delete search key..."
+ 			FindText := ChangeText] "... and search for it, without replacing"
- 			FindText _ ChangeText] "... and search for it, without replacing"
  		ifFalse: "Show where the search will start"
  			[home last = self selectionInterval last ifFalse:
  				[self selectInterval: home]].
  
  	"Find and Change, recording start indices in the array"
+ 	indices := WriteStream on: (Array new: 20). "an array to store change locs"
- 	indices _ WriteStream on: (Array new: 20). "an array to store change locs"
  	[(self againOnce: indices) & many] whileTrue. "<-- this does the work"
  	indices isEmpty ifTrue:  "none found"
  		[self flash.
  		wasTypedKey ifFalse: [^self]].
  
  	(many | wasTypedKey) ifFalse: "after undo, select this replacement"
+ 		[home := self startIndex to:
- 		[home _ self startIndex to:
  			self startIndex + UndoSelection size - 1].
  
  	self undoer: #undoAgain:andReselect:typedKey: with: indices contents with: home with: wasTypedKey!

Item was changed:
  ----- Method: Editor>>previousWord: (in category 'private') -----
  previousWord: position
  	| string index |
+ 	string := self string.
+ 	index := position.
- 	string _ self string.
- 	index _ position.
  	[(index between: 1 and: string size) and: [(string at: index) isAlphaNumeric not]]
+ 		whileTrue: [index := index - 1].
- 		whileTrue: [index _ index - 1].
  	[(index between: 1 and: string size) and: [(string at: index) isAlphaNumeric]]
+ 		whileTrue: [index := index - 1].
- 		whileTrue: [index _ index - 1].
  	^ index + 1!

Item was changed:
  ----- Method: TextEditor>>replaceSelectionWith: (in category 'accessing') -----
  replaceSelectionWith: aText
  	"Remember the selection text in UndoSelection.
  	 Deselect, and replace the selection text by aText.
  	 Remember the resulting selectionInterval in UndoInterval and PriorInterval.
  	 Set up undo to use UndoReplace."
  
  	beginTypeInBlock ~~ nil ifTrue: [^self zapSelectionWith: aText]. "called from old code"
+ 	UndoSelection := self selection.
- 	UndoSelection _ self selection.
  	self zapSelectionWith: aText.
  	self undoer: #undoReplace!

Item was changed:
  ----- Method: TextEditor>>changeEmphasis: (in category 'editing keys') -----
  changeEmphasis: characterStream 
  	"Change the emphasis of the current selection or prepare to accept characters with the change in emphasis. Emphasis change amounts to a font change.  Keeps typeahead."
  
  	"control 0..9 -> 0..9"
  
  	| keyCode attribute oldAttributes index thisSel colors extras |
  	keyCode := ('0123456789-=' indexOf: sensor keyboard ifAbsent: [1]) - 1.
  	oldAttributes := paragraph text attributesAt: self pointIndex.
  	thisSel := self selection.
  
  	"Decipher keyCodes for Command 0-9..."
  	(keyCode between: 1 and: 5) 
  		ifTrue: [attribute := TextFontChange fontNumber: keyCode].
  
  	keyCode = 6 
  		ifTrue: [
  			colors := #(#black #magenta #red #yellow #green #blue #cyan #white).
  			extras := self emphasisExtras.
  			index := UIManager default chooseFrom:colors , #('choose color...' ), extras
  						lines: (Array with: colors size + 1).
  			index = 0 ifTrue: [^true].
  			index <= colors size 
  				ifTrue: [attribute := TextColor color: (Color perform: (colors at: index))]
  				ifFalse: [
  					index := index - colors size - 1.	"Re-number!!!!!!"
  					index = 0 
  						ifTrue: [attribute := self chooseColor]
  						ifFalse:[^self handleEmphasisExtra: index with: characterStream]	"handle an extra"]].
  	(keyCode between: 7 and: 11) 
  		ifTrue: [
  			sensor leftShiftDown 
  				ifTrue: [
  					keyCode = 10 ifTrue: [attribute := TextKern kern: -1].
  					keyCode = 11 ifTrue: [attribute := TextKern kern: 1]]
  				ifFalse: [
  					attribute := TextEmphasis 
  								perform: (#(#bold #italic #narrow #underlined #struckOut) at: keyCode - 6).
  					oldAttributes 
  						do: [:att | (att dominates: attribute) ifTrue: [attribute turnOff]]]].
  	keyCode = 0 ifTrue: [attribute := TextEmphasis normal].
  	attribute ifNotNil: [
  		thisSel size = 0
  			ifTrue: [
  				"only change emphasisHere while typing"
  				self insertTypeAhead: characterStream.
+ 				emphasisHere := Text addAttribute: attribute toArray: oldAttributes ]
- 				emphasisHere _ Text addAttribute: attribute toArray: oldAttributes ]
  			ifFalse: [
  				self replaceSelectionWith: (thisSel asText addAttribute: attribute) ]].
  	^true!

Item was changed:
  ----- Method: TextEditor>>cursorEnd: (in category 'nonediting/nontyping keys') -----
  cursorEnd: characterStream 
  
  	"Private - Move cursor end of current line."
  	| string |
  	self closeTypeIn: characterStream.
+ 	string := paragraph text string.
- 	string _ paragraph text string.
  	self
  		moveCursor:
  			[:position | Preferences wordStyleCursorMovement
  				ifTrue:[| targetLine |
+ 					targetLine := paragraph lines at:(paragraph lineIndexOfCharacterIndex: position).
- 					targetLine _ paragraph lines at:(paragraph lineIndexOfCharacterIndex: position).
  					targetLine = paragraph lastLine
  						ifTrue:[targetLine last + 1]
  						ifFalse:[targetLine last]]
  				ifFalse:[
  					string
  						indexOf: Character cr
  						startingAt: position
  						ifAbsent:[string size + 1]]]
  		forward: true
  		specialBlock:[:dummy | string size + 1].
  	^true!

Item was changed:
  ----- Method: TextEditor>>undo (in category 'menu messages') -----
  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."
  
  	sensor flushKeyboard. "a way to flush stuck keys"
  	self closeTypeIn.
  
  	UndoParagraph == paragraph ifFalse: "Can't undo another paragraph's edit"
+ 		[UndoMessage := Message selector: #undoReplace.
+ 		UndoInterval := 1 to: 0.
+ 		Undone := true].
- 		[UndoMessage _ Message selector: #undoReplace.
- 		UndoInterval _ 1 to: 0.
- 		Undone _ true].
  	UndoInterval ~= self selectionInterval ifTrue: "blink the actual target"
  		[self selectInterval: UndoInterval; deselect].
  
  	"Leave a signal of which phase is in progress"
+ 	UndoParagraph := Undone ifTrue: [#redoing] ifFalse: [#undoing].
- 	UndoParagraph _ Undone ifTrue: [#redoing] ifFalse: [#undoing].
  	UndoMessage sentTo: self.
+ 	UndoParagraph := paragraph!
- 	UndoParagraph _ paragraph!

Item was changed:
  ----- Method: TextEditor>>undoMessage:forRedo: (in category 'undo support') -----
  undoMessage: aMessage forRedo: aBoolean
  	"Call this from an undoer/redoer to set up UndoMessage as the
  	 corresponding redoer/undoer.  Also set up UndoParagraph, as well
  	 as the state variable Undone.  It is assumed that UndoInterval has been
  	 established (generally by zapSelectionWith:) and that UndoSelection has been
  	 saved (generally by replaceSelectionWith: or replace:With:and:)."
  
+ 	self isDoing ifTrue: [UndoParagraph := paragraph].
+ 	UndoMessage := aMessage.
+ 	Undone := aBoolean!
- 	self isDoing ifTrue: [UndoParagraph _ paragraph].
- 	UndoMessage _ aMessage.
- 	Undone _ aBoolean!

Item was changed:
  ----- Method: TextEditor>>inspectIt (in category 'do-its') -----
  inspectIt
  	"1/13/96 sw: minor fixup"
  	| result |
+ 	result := self evaluateSelection.
- 	result _ self evaluateSelection.
  	((result isKindOf: FakeClassPool) or: [result == #failedDoit])
  			ifTrue: [morph flash]
  			ifFalse: [result inspect]!

Item was changed:
  ----- Method: Editor>>initialize (in category 'initialize-release') -----
  initialize
  	"Initialize the state of the receiver. Subclasses should include 'super 
  	initialize' when redefining this message to insure proper initialization."
  
+ 	sensor := InputSensor default!
- 	sensor _ InputSensor default!

Item was changed:
  ----- Method: TextEditor>>replace:with:and: (in category 'accessing') -----
  replace: xoldInterval with: newText and: selectingBlock 
  	"Replace the text in oldInterval with newText and execute selectingBlock to establish the new selection.  Create an undoAndReselect:redoAndReselect: undoer to allow perfect undoing."
  
  	| undoInterval |
+ 	undoInterval := self selectionInterval.
- 	undoInterval _ self selectionInterval.
  	undoInterval = xoldInterval ifFalse: [self selectInterval: xoldInterval].
+ 	UndoSelection := self selection.
- 	UndoSelection _ self selection.
  	self zapSelectionWith: newText.
  	selectingBlock value.
+ 	otherInterval := self selectionInterval.
- 	otherInterval _ self selectionInterval.
  	self undoer: #undoAndReselect:redoAndReselect: with: undoInterval with: otherInterval!

Item was changed:
  ----- Method: TextEditor>>stateArrayPut: (in category 'initialize-release') -----
  stateArrayPut: stateArray
  	| sel |
+ 	ChangeText := stateArray at: 1.
+ 	FindText := stateArray at: 2.
+ 	UndoInterval := stateArray at: 3.
+ 	UndoMessage := stateArray at: 4.
+ 	UndoParagraph := stateArray at: 5.
+ 	UndoSelection := stateArray at: 6.
+ 	Undone := stateArray at: 7.
+ 	sel := stateArray at: 8.
- 	ChangeText _ stateArray at: 1.
- 	FindText _ stateArray at: 2.
- 	UndoInterval _ stateArray at: 3.
- 	UndoMessage _ stateArray at: 4.
- 	UndoParagraph _ stateArray at: 5.
- 	UndoSelection _ stateArray at: 6.
- 	Undone _ stateArray at: 7.
- 	sel _ stateArray at: 8.
  	self selectFrom: sel first to: sel last.
+ 	beginTypeInBlock := stateArray at: 9.
+ 	emphasisHere := stateArray at: 10!
- 	beginTypeInBlock _ stateArray at: 9.
- 	emphasisHere _ stateArray at: 10!

Item was changed:
  ----- Method: TextEditor>>copySelection (in category 'menu messages') -----
  copySelection
  	"Copy the current selection and store it in the paste buffer, unless a caret.  Undoer & Redoer: undoCutCopy"
  
  	self lineSelectAndEmptyCheck: [^ self].
  
  	"Simulate 'substitute: self selection' without locking the controller"
+ 	UndoSelection := self selection.
- 	UndoSelection _ self selection.
  	self undoer: #undoCutCopy: with: self clipboardText.
+ 	UndoInterval := self selectionInterval.
- 	UndoInterval _ self selectionInterval.
  	self clipboardTextPut: UndoSelection!

Item was added:
+ ----- 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, 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:
+ 				[str := string allButFirst.
+ 				(self explainTemp: str) ~~ nil ifTrue:
+ 					[^'"An argument to this block will be bound to the temporary variable ',
+ 						str, '."']]].
+ 	^ nil!

Item was changed:
  ----- Method: TextEditor>>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].
- 		[otherInterval _ oldInterval].
  	self storeSelectionInParagraph!

Item was changed:
  ----- Method: TextEditor>>enclose: (in category 'editing keys') -----
  enclose: characterStream
  	"Insert or remove bracket characters around the current selection.
  	 Flushes typeahead."
  
  	| char left right startIndex stopIndex oldSelection which text |
+ 	char := sensor keyboard.
- 	char _ sensor keyboard.
  	self closeTypeIn.
+ 	startIndex := self startIndex.
+ 	stopIndex := self stopIndex.
+ 	oldSelection := self selection.
+ 	which := '([<{"''' indexOf: char ifAbsent: [ ^true ].
+ 	left := '([<{"''' at: which.
+ 	right := ')]>}"''' at: which.
+ 	text := paragraph text.
- 	startIndex _ self startIndex.
- 	stopIndex _ self stopIndex.
- 	oldSelection _ self selection.
- 	which _ '([<{"''' indexOf: char ifAbsent: [ ^true ].
- 	left _ '([<{"''' at: which.
- 	right _ ')]>}"''' at: which.
- 	text _ paragraph text.
  	((startIndex > 1 and: [stopIndex <= text size])
  			and: [ (text at: startIndex-1) = left and: [(text at: stopIndex) = right]])
  		ifTrue: [
  			"already enclosed; strip off brackets"
  			self selectFrom: startIndex-1 to: stopIndex.
  			self replaceSelectionWith: oldSelection]
  		ifFalse: [
  			"not enclosed; enclose by matching brackets"
  			self replaceSelectionWith:
  				(Text string: (String with: left), oldSelection string, (String with: right) attributes: emphasisHere).
  			self selectFrom: startIndex+1 to: stopIndex].
  	^true!

Item was changed:
  ----- Method: TextEditor>>debugIt (in category 'do-its') -----
  debugIt
  
  	| method receiver context |
  	(model respondsTo: #doItReceiver) 
  		ifTrue: 
  			[FakeClassPool adopt: model selectedClass.
+ 			receiver := model doItReceiver.
+ 			context := model doItContext]
- 			receiver _ model doItReceiver.
- 			context _ model doItContext]
  		ifFalse:
+ 			[receiver := context := nil].
- 			[receiver _ context _ nil].
  	self lineSelectAndEmptyCheck: [^self].
+ 	method := self compileSelectionFor: receiver in: context.
- 	method _ self compileSelectionFor: receiver in: context.
  	method notNil ifTrue:
  		[self debug: method receiver: receiver in: context].
  	FakeClassPool adopt: nil!

Item was changed:
  ----- Method: TextEditor>>setAlignment: (in category 'menu messages') -----
  setAlignment: aSymbol
  	| attr interval |
+ 	attr := TextAlignment perform: aSymbol.
+ 	interval := self encompassLine: self selectionInterval.
- 	attr _ TextAlignment perform: aSymbol.
- 	interval _ self encompassLine: self selectionInterval.
  	paragraph 
  		replaceFrom: interval first 
  		to: interval last 
  		with: ((paragraph text copyFrom: interval first to: interval last) addAttribute: attr)!

Item was changed:
  ----- Method: TextEditor>>setSearchString: (in category 'nonediting/nontyping keys') -----
  setSearchString: characterStream
  	"Establish the current selection as the current search string."
  
  	| aString |
  	self closeTypeIn: characterStream.
  	sensor keyboard.
  	self lineSelectAndEmptyCheck: [^ true].
+ 	aString :=  self selection string.
- 	aString _  self selection string.
  	aString size = 0
  		ifTrue:
  			[self flash]
  		ifFalse:
  			[self setSearch: aString].
  	^ true!

Item was changed:
  ----- Method: TextEditor>>resetState (in category 'initialize-release') -----
  resetState 
  	"Establish the initial conditions for editing the paragraph: place caret 
  	before first character, set the emphasis to that of the first character,
  	and save the paragraph for purposes of canceling."
  
+ 	markBlock := paragraph defaultCharacterBlock.
- 	markBlock _ paragraph defaultCharacterBlock.
  	self pointBlock: markBlock copy.
+ 	beginTypeInBlock := nil.
+ 	UndoInterval := otherInterval := 1 to: 0.
- 	beginTypeInBlock _ nil.
- 	UndoInterval _ otherInterval _ 1 to: 0.
  	self setEmphasisHere.
+ 	selectionShowing := false!
- 	selectionShowing _ false!

Item was changed:
  ----- Method: TextEditor>>backTo: (in category 'typing support') -----
  backTo: startIndex
  	"During typing, backspace to startIndex.  Deleted characters fall into three
  	 clusters, from left to right in the text: (1) preexisting characters that were
  	 backed over; (2) newly typed characters that were backed over (excluding
  	 typeahead, which never even appears); (3) preexisting characters that
  	 were highlighted before typing began.  If typing has not yet been opened,
  	 open it and watch for the first and third cluster.  If typing has been opened,
  	 watch for the first and second cluster.  Save characters from the first and third
  	 cluster in UndoSelection.  Tally characters from the first cluster in UndoMessage's parameter.
  	 Delete all the clusters.  Do not alter Undoer or UndoInterval (except via
  	 openTypeIn).  The code is shorter than the comment."
  
  	| saveLimit newBackovers |
+ 	saveLimit := beginTypeInBlock
+ 		ifNil: [self openTypeIn. UndoSelection := self nullText. self stopIndex]
- 	saveLimit _ beginTypeInBlock
- 		ifNil: [self openTypeIn. UndoSelection _ self nullText. self stopIndex]
  		ifNotNil: [self startOfTyping].
  	self markIndex: startIndex.
  	startIndex < saveLimit ifTrue: [
+ 		newBackovers := self startOfTyping - startIndex.
+ 		beginTypeInBlock := self startIndex.
- 		newBackovers _ self startOfTyping - startIndex.
- 		beginTypeInBlock _ self startIndex.
  		UndoSelection replaceFrom: 1 to: 0 with:
  			(paragraph text copyFrom: startIndex to: saveLimit - 1).
  		UndoMessage argument: (UndoMessage argument ifNil: [1]) + newBackovers].
  	self zapSelectionWith: self nullText.
  	self unselect!

Item was changed:
  ----- Method: Editor>>sensor: (in category 'private') -----
  sensor: aSensor
  	"Set the receiver's sensor to aSensor."
  
+ 	sensor := aSensor!
- 	sensor _ aSensor!

Item was changed:
  ----- Method: PasteUpMorph>>modalLockTo: (in category 'polymorph') -----
  modalLockTo: aSystemWindow
  	"Don't lock the world!! Lock the submorphs.
  	The modal window gets opened afterwards so is OK."
  	
  	|lockStates|
+ 	lockStates := IdentityDictionary new.
- 	lockStates _ IdentityDictionary new.
  	self submorphsDo: [:m |
  		lockStates at: m put: m isLocked.
  		m lock].
  	self
  		setProperty: #submorphLockStates
  		toValue: lockStates!

Item was changed:
  ----- Method: TextEditor>>noUndoer (in category 'undo support') -----
  noUndoer
  	"The Undoer to use when the command can not be undone.  Checked for
  	 specially by readKeyboard."
  
+ 	UndoMessage := Message selector: #noUndoer!
- 	UndoMessage _ Message selector: #noUndoer!

Item was changed:
  ----- Method: TextEditor>>explainNumber: (in category 'explain') -----
  explainNumber: string 
  	"Is string a Number?"
  
  	| strm c |
+ 	(c := string at: 1) isDigit ifFalse: [(c = $- and: [string size > 1 and: [(string at: 2) isDigit]])
- 	(c _ string at: 1) isDigit ifFalse: [(c = $- and: [string size > 1 and: [(string at: 2) isDigit]])
  			ifFalse: [^nil]].
+ 	strm := ReadStream on: string.
+ 	c := Number readFrom: strm.
- 	strm _ ReadStream on: string.
- 	c _ Number readFrom: strm.
  	strm atEnd ifFalse: [^nil].
  	c printString = string
  		ifTrue: [^'"' , string , ' is a ' , c class name , '"']
  		ifFalse: [^'"' , string , ' (= ' , c printString , ') is a ' , c class name , '"']!

Item was changed:
  ----- Method: TextEditor>>sameColumn:newLine:forward: (in category 'private') -----
  sameColumn: start newLine: lineBlock forward: isForward
  	"Private - Compute the index in my text
  	with the line number derived from lineBlock,"
  	" a one argument block accepting the old line number.
  	The position inside the line will be preserved as good as possible"
  	"The boolean isForward is used in the border case to determine if
  	we should move to the beginning or the end of the line."
  	| wordStyle column currentLine offsetAtTargetLine targetEOL lines numberOfLines currentLineNumber targetLineNumber |
+ 	wordStyle := Preferences wordStyleCursorMovement.
- 	wordStyle _ Preferences wordStyleCursorMovement.
  	wordStyle
  		ifTrue: [
+ 			lines := paragraph lines.
- 			lines _ paragraph lines.
  			numberOfLines := paragraph numberOfLines.
+ 			currentLineNumber  := paragraph lineIndexOfCharacterIndex: start.
+ 			currentLine := lines at: currentLineNumber]
- 			currentLineNumber  _ paragraph lineIndexOfCharacterIndex: start.
- 			currentLine _ lines at: currentLineNumber]
  		ifFalse: [
+ 			lines := self lines.
- 			lines _ self lines.
  			numberOfLines := lines size.
+ 			currentLine := lines
- 			currentLine _ lines
  				detect:[:lineInterval | lineInterval last >= start]
  				ifNone:[lines last].
+ 			currentLineNumber := currentLine second].
+ 	column := start - currentLine first.
+ 	targetLineNumber := ((lineBlock value: currentLineNumber) max: 1) min: numberOfLines.
+ 	offsetAtTargetLine := (lines at: targetLineNumber) first.
+ 	targetEOL := (lines at: targetLineNumber) last + (targetLineNumber = numberOfLines ifTrue:[1]ifFalse:[0]).
- 			currentLineNumber _ currentLine second].
- 	column _ start - currentLine first.
- 	targetLineNumber _ ((lineBlock value: currentLineNumber) max: 1) min: numberOfLines.
- 	offsetAtTargetLine _ (lines at: targetLineNumber) first.
- 	targetEOL _ (lines at: targetLineNumber) last + (targetLineNumber = numberOfLines ifTrue:[1]ifFalse:[0]).
  	targetLineNumber = currentLineNumber
  	"No movement or movement failed. Move to beginning or end of line."
  		ifTrue:[^isForward
  			ifTrue:[targetEOL]
  			ifFalse:[offsetAtTargetLine]].
  	^offsetAtTargetLine + column min: targetEOL.!

Item was changed:
  ----- Method: Editor>>moveCursor:forward:specialBlock: (in category 'private') -----
  moveCursor: directionBlock forward: forward specialBlock: specialBlock
  	"Private - Move cursor.
  	directionBlock is a one argument Block that computes the new Position from a given one.
  	specialBlock is a one argumentBlock that computes the new position from a given one under the alternate semantics.
  	Note that directionBlock always is evaluated first."
  	| shift indices newPosition |
+ 	shift := sensor leftShiftDown.
+ 	indices := self setIndices: shift forward: forward.
+ 	newPosition := directionBlock value: (indices at: #moving).
- 	shift _ sensor leftShiftDown.
- 	indices _ self setIndices: shift forward: forward.
- 	newPosition _ directionBlock value: (indices at: #moving).
  	(sensor commandKeyPressed or:[sensor controlKeyPressed])
+ 		ifTrue: [newPosition := specialBlock value: newPosition].
- 		ifTrue: [newPosition _ specialBlock value: newPosition].
  	sensor keyboard.
  	shift
  		ifTrue: [self selectMark: (indices at: #fixed) point: newPosition - 1]
  		ifFalse: [self selectAt: newPosition]!

Item was changed:
  ----- Method: TextEditor>>explainCtxt: (in category 'explain') -----
  explainCtxt: symbol 
  	"Is symbol a context variable?"
  
  	| reply classes text cls |
+ 	symbol = #nil ifTrue: [reply := '"is a constant.  It is the only instance of class UndefinedObject.  nil is the initial value of all variables."'].
+ 	symbol = #true ifTrue: [reply := '"is a constant.  It is the only instance of class True and is the receiver of many control messages."'].
+ 	symbol = #false ifTrue: [reply := '"is a constant.  It is the only instance of class False and is the receiver of many control messages."'].
+ 	symbol = #thisContext ifTrue: [reply := '"is a context variable.  Its value is always the MethodContext which is executing this method."'].
- 	symbol = #nil ifTrue: [reply _ '"is a constant.  It is the only instance of class UndefinedObject.  nil is the initial value of all variables."'].
- 	symbol = #true ifTrue: [reply _ '"is a constant.  It is the only instance of class True and is the receiver of many control messages."'].
- 	symbol = #false ifTrue: [reply _ '"is a constant.  It is the only instance of class False and is the receiver of many control messages."'].
- 	symbol = #thisContext ifTrue: [reply _ '"is a context variable.  Its value is always the MethodContext which is executing this method."'].
  	(model respondsTo: #selectedClassOrMetaClass) ifTrue: [
+ 		cls := model selectedClassOrMetaClass].
- 		cls _ model selectedClassOrMetaClass].
  	cls ifNil: [^ reply].	  "no class known"
  	symbol = #self ifTrue: 
+ 			[classes := cls withAllSubclasses.
- 			[classes _ cls withAllSubclasses.
  			classes size > 12
+ 				ifTrue: [text := cls printString , ' or a subclass']
- 				ifTrue: [text _ cls printString , ' or a subclass']
  				ifFalse: 
+ 					[classes := classes printString.
+ 					text := 'one of these classes' , (classes copyFrom: 4 to: classes size)].
+ 			reply := '"is the receiver of this message; an instance of ' , text , '"'].
+ 	symbol = #super ifTrue: [reply := '"is just like self.  Messages to super are looked up in the superclass (' , cls superclass printString , ')"'].
- 					[classes _ classes printString.
- 					text _ 'one of these classes' , (classes copyFrom: 4 to: classes size)].
- 			reply _ '"is the receiver of this message; an instance of ' , text , '"'].
- 	symbol = #super ifTrue: [reply _ '"is just like self.  Messages to super are looked up in the superclass (' , cls superclass printString , ')"'].
  	^reply!

Item was changed:
  ----- Method: TextEditor>>encompassLine: (in category 'new selection') -----
  encompassLine: anInterval
  	"Return an interval that encompasses the entire line"
  	| string left right |
+ 	string := paragraph text string.
+ 	left := (string lastIndexOf: Character cr startingAt: anInterval first - 1 ifAbsent:[0]) + 1.
+ 	right := (string indexOf: Character cr startingAt: anInterval last + 1 ifAbsent: [string size + 1]) - 1.
- 	string _ paragraph text string.
- 	left _ (string lastIndexOf: Character cr startingAt: anInterval first - 1 ifAbsent:[0]) + 1.
- 	right _ (string indexOf: Character cr startingAt: anInterval last + 1 ifAbsent: [string size + 1]) - 1.
  	^left to: right!

Item was changed:
  ----- Method: TextEditor>>browseClassFromIt (in category 'menu messages') -----
  browseClassFromIt
  	"Launch a hierarchy browser for the class indicated by the current selection.  If multiple classes matching the selection exist, let the user choose among them."
  
  	| aClass |
  	self lineSelectAndEmptyCheck: [^ self].
  
+ 	aClass := Utilities classFromPattern: (self selection string copyWithout: Character cr) withCaption: 'choose a class to browse...'.
- 	aClass _ Utilities classFromPattern: (self selection string copyWithout: Character cr) withCaption: 'choose a class to browse...'.
  	aClass ifNil: [^ morph flash].
  
  	Utilities spawnHierarchyForClass: aClass selector: nil!

Item was changed:
  ----- Method: Editor>>backspace: (in category 'typing/selecting keys') -----
  backspace: characterStream 
  	"Backspace over the last character."
  
  	| startIndex |
  	sensor leftShiftDown ifTrue: [^ self backWord: characterStream].
  	characterStream isEmpty
  		ifTrue:
+ 			[startIndex := self markIndex +
- 			[startIndex _ self markIndex +
  				(self hasCaret ifTrue: [0] ifFalse: [1]).
  			[sensor keyboardPressed and:
  			 [sensor keyboardPeek asciiValue = 8]] whileTrue: [
  				"process multiple backspaces"
  				sensor keyboard.
+ 				startIndex := 1 max: startIndex - 1.
- 				startIndex _ 1 max: startIndex - 1.
  			].
  			self backTo: startIndex]
  		ifFalse:
  			[sensor keyboard.
  			characterStream skip: -1].
  	^false!

Item was changed:
  ----- Method: TextEditor>>selectCurrentTypeIn: (in category 'nonediting/nontyping keys') -----
  selectCurrentTypeIn: characterStream 
  	"Select what would be replaced by an undo (e.g., the last typeIn)."
  
  	| prior |
  
  	self closeTypeIn: characterStream.
+ 	prior := otherInterval.
- 	prior _ otherInterval.
  	sensor keyboard.		"flush character"
  	self closeTypeIn: characterStream.
  	self selectInterval: UndoInterval.
+ 	otherInterval := prior.
- 	otherInterval _ prior.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>closeTypeIn (in category 'typing support') -----
  closeTypeIn
  	"See comment in openTypeIn.  It is important to call closeTypeIn before executing
  	 any non-typing key, making a new selection, etc.  It is called automatically for
  	 menu commands.
  	 Typing commands can call 'closeTypeIn: aCharacterStream' instead of this to
  	 save typeahead.  Undoer & Redoer: undoAndReselect:redoAndReselect:."
  
  	| begin stop |
  	beginTypeInBlock == nil ifFalse: [
  		(UndoMessage sends: #noUndoer) ifTrue: "should always be true, but just in case..."
+ 			[begin := self startOfTyping.
+ 			stop := self stopIndex.
- 			[begin _ self startOfTyping.
- 			stop _ self stopIndex.
  			self undoer: #undoAndReselect:redoAndReselect:
  				with: (begin + UndoMessage argument to: begin + UndoSelection size - 1)
  				with: (stop to: stop - 1).
+ 			UndoInterval := begin to: stop - 1].
+ 		beginTypeInBlock := nil]!
- 			UndoInterval _ begin to: stop - 1].
- 		beginTypeInBlock _ nil]!

Item was changed:
  ----- Method: TextEditor>>model: (in category 'model access') -----
  model: aModel 
  	"Controller|model: and Controller|view: are sent by View|controller: in 
  	order to coordinate the links between the model, view, and controller. In 
  	ordinary usage, the receiver is created and passed as the parameter to 
  	View|controller: so that the receiver's model and view links can be set 
  	up by the view."
  
+ 	model := aModel!
- 	model _ aModel!

Item was changed:
  ----- Method: TextEditor>>cursorHome: (in category 'nonediting/nontyping keys') -----
  cursorHome: characterStream 
  
  	"Private - Move cursor from position in current line to beginning of
  	current line. If control key is pressed put cursor at beginning of text"
  
  	| string |
  
+ 	string := paragraph text string.
- 	string _ paragraph text string.
  	self
  		moveCursor: [ :position | Preferences wordStyleCursorMovement
  				ifTrue:[
  					(paragraph lines at:(paragraph lineIndexOfCharacterIndex: position)) first]
  				ifFalse:[
  					(string
  						lastIndexOf: Character cr
  						startingAt: position - 1
  						ifAbsent:[0]) + 1]]
  		forward: false
  		specialBlock: [:dummy | 1].
  	^true!

Item was changed:
  ----- Method: TextEditor>>forwardDelete: (in category 'typing/selecting keys') -----
  forwardDelete: characterStream
  	"Delete forward over the next character.
  	  Make Undo work on the whole type-in, not just the one char.
  	wod 11/3/1998: If there was a selection use #zapSelectionWith: rather than #backspace: which was 'one off' in deleting the selection. Handling of things like undo or typeIn area were not fully considered."
  	| startIndex usel upara uinterval ind stopIndex |
+ 	startIndex := self markIndex.
- 	startIndex _ self markIndex.
  	startIndex > paragraph text size ifTrue:
  		[sensor keyboard.
  		^ false].
  	self hasSelection ifTrue:
  		["there was a selection"
  		sensor keyboard.
  		self zapSelectionWith: self nullText.
  		^ false].
  	"Null selection - do the delete forward"
  	beginTypeInBlock == nil	"no previous typing.  openTypeIn"
+ 		ifTrue: [self openTypeIn. UndoSelection := self nullText].
+ 	uinterval := UndoInterval deepCopy.
+ 	upara := UndoParagraph deepCopy.
- 		ifTrue: [self openTypeIn. UndoSelection _ self nullText].
- 	uinterval _ UndoInterval deepCopy.
- 	upara _ UndoParagraph deepCopy.
  	stopIndex := startIndex.
  	(sensor keyboard asciiValue = 127 and: [sensor leftShiftDown])
  		ifTrue: [stopIndex := (self nextWord: stopIndex) - 1].
  	self selectFrom: startIndex to: stopIndex.
  	self replaceSelectionWith: self nullText.
  	self selectFrom: startIndex to: startIndex-1.
+ 	UndoParagraph := upara.  UndoInterval := uinterval.
- 	UndoParagraph _ upara.  UndoInterval _ uinterval.
  	UndoMessage selector == #noUndoer ifTrue: [
  		(UndoSelection isText) ifTrue: [
+ 			usel := UndoSelection.
+ 			ind := startIndex. "UndoInterval startIndex"
- 			usel _ UndoSelection.
- 			ind _ startIndex. "UndoInterval startIndex"
  			usel replaceFrom: usel size + 1 to: usel size with:
  				(UndoParagraph text copyFrom: ind to: ind).
  			UndoParagraph text replaceFrom: ind to: ind with:
  self nullText]].
  	^false!

Item was changed:
  ----- Method: Editor>>nextWord: (in category 'private') -----
  nextWord: position
  	| string index |
+ 	string := self string.
+ 	index := position.
- 	string _ self string.
- 	index _ position.
  	[(index between: 1 and: string size) and: [(string at: index) isAlphaNumeric]]
+ 		whileTrue: [index := index + 1].
- 		whileTrue: [index _ index + 1].
  	[(index between: 1 and: string size) and: [(string at: index) isAlphaNumeric not]]
+ 		whileTrue: [index := index + 1].
- 		whileTrue: [index _ index + 1].
  	^ index!

Item was changed:
  ----- Method: Editor>>setIndices:forward: (in category 'private') -----
  setIndices: shiftPressed forward: forward
  	"Little helper method that sets the moving and fixed indices according to some flags."
  	| indices |
+ 	indices := Dictionary new.
- 	indices _ Dictionary new.
  	(shiftPressed and:[self class selectionsMayShrink])
  		ifTrue: [
  			indices at: #moving put: self pointIndex.
  			indices at: #fixed put: self markIndex
  		] ifFalse: [
  			forward
  				ifTrue:[
  					indices at: #moving put: self stopIndex.
  					indices at: #fixed put: self startIndex.
  				] ifFalse: [
  					indices at: #moving put: self startIndex.
  					indices at: #fixed put: self stopIndex.
  				]
  		].
  	^indices!

Item was changed:
  ----- Method: TextEditor>>argAdvance: (in category 'typing/selecting keys') -----
  argAdvance: characterStream
  	"Invoked by Ctrl-a.  Useful after Ctrl-q.
  	 Search forward from the end of the selection for a colon followed by
  		a space.  Place the caret after the space.  If none are found, place the
  		caret at the end of the text.  Does not affect the undoability of the 
  	 	previous command."
  
  	| start |
  	sensor keyboard.		"flush character"
  	self closeTypeIn: characterStream.
+ 	start := paragraph text findString: ': ' startingAt: self stopIndex.
+ 	start = 0 ifTrue: [start := paragraph text size + 1].
- 	start _ paragraph text findString: ': ' startingAt: self stopIndex.
- 	start = 0 ifTrue: [start _ paragraph text size + 1].
  	self selectAt: start + 2.
  	^true!

Item was changed:
  ----- Method: TextEditor class>>initializeShiftedYellowButtonMenu (in category 'keyboard shortcut tables') -----
  initializeShiftedYellowButtonMenu
  	"Initialize the yellow button pop-up menu and corresponding messages."
  
  	"TextEditor initialize"
  	"
  	shiftedYellowButtonMenu := {
  		{'set font... (k)' translated.					#offerFontMenu}.
  		{'set style... (K)' translated.				#changeStyle}.
  		{'set alignment...' translated.				#chooseAlignment}.
  		#-.
  		{'more...' translated.						#yellowButtonActivity}.
  	}
  	"
+ 	shiftedYellowButtonMenu := yellowButtonMenu!
- 	shiftedYellowButtonMenu _ yellowButtonMenu!

Item was changed:
  ----- Method: SmalltalkEditor>>handleEmphasisExtra:with: (in category 'editing keys') -----
  handleEmphasisExtra: index with: characterStream
  	"Handle an extra emphasis menu item"
  	| action attribute thisSel |
  	action := {
  		[attribute := TextDoIt new.
  		thisSel := attribute analyze: self selection asString].
  		[attribute := TextPrintIt new.
  		thisSel := attribute analyze: self selection asString].
  		[attribute := TextLink new.
  		thisSel := attribute analyze: self selection asString with: 'Comment'].
  		[attribute := TextLink new.
  		thisSel := attribute analyze: self selection asString with: 'Definition'].
  		[attribute := TextLink new.
  		thisSel := attribute analyze: self selection asString with: 'Hierarchy'].
  		[attribute := TextLink new.
  		thisSel := attribute analyze: self selection asString].
  		[attribute := TextURL new.
  		thisSel := attribute analyze: self selection asString].
  		["Edit hidden info"
  		thisSel := self hiddenInfo.	"includes selection"
  		attribute := TextEmphasis normal].
  		["Copy hidden info"
  		self copyHiddenInfo.
  		^true].	"no other action"
  	} at: index.
  	action value.
  
  	thisSel ifNil: [^true].	"Could not figure out what to link to"
  
  	attribute ifNotNil: [
  		thisSel ifEmpty:[ | oldAttributes |
  			"only change emphasisHere while typing"
  			oldAttributes := paragraph text attributesAt: self pointIndex.
  			self insertTypeAhead: characterStream.
+ 			emphasisHere := Text addAttribute: attribute toArray: oldAttributes.
- 			emphasisHere _ Text addAttribute: attribute toArray: oldAttributes.
  		] ifNotEmpty: [
  			self replaceSelectionWith: (thisSel asText addAttribute: attribute).
  		]
  	].
  	^true!

Item was changed:
  ----- Method: TextEditor>>nextTokenFrom:direction: (in category 'new selection') -----
  nextTokenFrom: start direction: dir
  	"simple token-finder for compiler automated corrections"
  	| loc str |
+ 	loc := start + dir.
+ 	str := paragraph text string.
- 	loc _ start + dir.
- 	str _ paragraph text string.
  	[(loc between: 1 and: str size) and: [(str at: loc) isSeparator]]
+ 		whileTrue: [loc := loc + dir].
- 		whileTrue: [loc _ loc + dir].
  	^ loc!

Item was changed:
  ----- Method: TextEditor>>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."
  
  	| honorCommandKeys |
  	((char == Character cr) and: [morph acceptOnCR])
  		ifTrue: [
  			sensor keyboard.  "Gobble cr -- probably unnecessary."
  			self closeTypeIn.
  			^ true].
  
  	self clearParens.
    
  	char asciiValue = 13 ifTrue: [
  		sensor controlKeyPressed ifTrue: [
  			^ self normalCharacter: typeAheadStream ].
  		sensor leftShiftDown ifTrue: [
  			^ self lf: typeAheadStream ].
  		sensor commandKeyPressed ifTrue: [
  			^ self crlf: typeAheadStream ].
  		^ self crWithIndent: typeAheadStream ].
  
+ 	((honorCommandKeys := Preferences cmdKeysInText) and: [char = Character enter])
- 	((honorCommandKeys _ Preferences cmdKeysInText) and: [char = Character enter])
  		ifTrue: [^ self dispatchOnEnterWith: typeAheadStream].
  
  	"Special keys overwrite crtl+key combinations - at least on Windows. To resolve this
  	conflict, assume that keys other than cursor keys aren't used together with Crtl." 
  	((self class specialShiftCmdKeys includes: char asciiValue) and: [char asciiValue < 27])
  		ifTrue: [^ sensor controlKeyPressed
  			ifTrue: [self perform: (self class shiftCmdActions at: char asciiValue + 1) with: typeAheadStream]
  			ifFalse: [self perform: (self class cmdActions at: char asciiValue + 1) with: typeAheadStream]].
  
  	"backspace, and escape keys (ascii 8 and 27) are command keys"
  	((honorCommandKeys and: [sensor commandKeyPressed]) or: [self class specialShiftCmdKeys includes: char asciiValue]) ifTrue:
  		[^ sensor leftShiftDown
  			ifTrue: [
  				self perform: (self class shiftCmdActions at: char asciiValue + 1) with: typeAheadStream]
  			ifFalse: [
  				self perform: (self class cmdActions at: char asciiValue + 1) with: typeAheadStream]].
  
  	"the control key can be used to invoke shift-cmd shortcuts"
  	(honorCommandKeys and: [sensor controlKeyPressed])
  		ifTrue: [
  			^ self perform: (self class shiftCmdActions at: char asciiValue + 1) with: typeAheadStream].
  
  	(')]}' includes: char)
  		ifTrue: [self blinkPrevParen].
  
  	^ self normalCharacter: typeAheadStream!

Item was changed:
  ----- Method: TextEditor>>debug:receiver:in: (in category 'do-its') -----
  debug: aCompiledMethod receiver: anObject in: evalContext
  
  	| selector guineaPig debugger context |
+ 	selector := evalContext isNil ifTrue: [#DoIt] ifFalse: [#DoItIn:].
- 	selector _ evalContext isNil ifTrue: [#DoIt] ifFalse: [#DoItIn:].
  	anObject class addSelectorSilently: selector withMethod: aCompiledMethod.
+ 	guineaPig := evalContext isNil
- 	guineaPig _ evalContext isNil
  		ifTrue: [[anObject DoIt] newProcess]
  		ifFalse: [[anObject DoItIn: evalContext] newProcess].
+ 	context := guineaPig suspendedContext.
+ 	debugger := Debugger new
- 	context _ guineaPig suspendedContext.
- 	debugger _ Debugger new
  		process: guineaPig
  		controller: nil
  		context: context.
  	debugger openFullNoSuspendLabel: 'Debug it'.
  	[debugger interruptedContext method == aCompiledMethod]
  		whileFalse: [debugger send].
  	anObject class basicRemoveSelector: selector!

Item was changed:
  ----- Method: TextEditor>>blinkParenAt: (in category 'parenblinking') -----
  blinkParenAt: parenLocation 
  	self text
  		addAttribute: TextEmphasis bold
  		from: parenLocation
  		to: parenLocation.
+ 	lastParenLocation := parenLocation.!
- 	lastParenLocation _ parenLocation.!

Item was changed:
  ----- Method: TextEditor>>setSearch: (in category 'accessing') -----
  setSearch: aString
  	"Set the FindText and ChangeText to seek aString; except if already seeking aString, leave ChangeText alone so again will repeat last replacement."
  
  	FindText string = aString
+ 		ifFalse: [FindText := ChangeText := aString asText]!
- 		ifFalse: [FindText _ ChangeText _ aString asText]!

Item was changed:
  ----- Method: TextEditor>>browseChangeSetsWithSelector (in category 'menu messages') -----
  browseChangeSetsWithSelector
  	"Determine which, if any, change sets have at least one change for the selected selector, independent of class"
  
  	| aSelector |
  	self lineSelectAndEmptyCheck: [^ self].
+ 	(aSelector := self selectedSelector) == nil ifTrue: [^ morph flash].
- 	(aSelector _ self selectedSelector) == nil ifTrue: [^ morph flash].
  	ChangeSorter browseChangeSetsWithSelector: aSelector!

Item was changed:
  ----- Method: TextEditor>>zapSelectionWith: (in category 'mvc compatibility') -----
  zapSelectionWith: aText
  
  	| start stop |
  	self deselect.
+ 	start := self startIndex.
+ 	stop := self stopIndex.
- 	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) select: [:att | att mayBeExtended]].
- 		emphasisHere _ (paragraph text attributesAt: start) select: [:att | att mayBeExtended]].
  	(start = stop and: [ aText size = 0 ]) ifFalse: [
  		paragraph replaceFrom: start to: stop - 1 with: aText.
  		self markIndex: start; pointIndex: start + aText size.
+ 		UndoInterval := otherInterval := self selectionInterval].
- 		UndoInterval _ otherInterval _ self selectionInterval].
  
  	self userHasEdited  " -- note text now dirty"!

Item was changed:
  ----- Method: TextEditor>>pointBlock: (in category 'accessing-selection') -----
  pointBlock: aCharacterBlock
+ 	pointBlock := aCharacterBlock.
- 	pointBlock _ aCharacterBlock.
  !

Item was changed:
  ----- Method: FileList>>askServerInfo (in category 'server list') -----
  askServerInfo
  	"Get the user to create a ServerDirectory for a new server.  Fill in and say Accept."
  	| template |
+ 	template := '"Please fill in the following info, then select all text and choose DoIt."
- 	template _ '"Please fill in the following info, then select all text and choose DoIt."
  
  	| aa | 
  	self flag: #ViolateNonReferenceToOtherClasses.
+ 	aa := ServerDirectory new.
- 	aa _ ServerDirectory new.
  	aa server: ''st.cs.uiuc.edu''.    "host"
  	aa user: ''anonymous''.
  	aa password: ''yourEmail at school.edu''.
  	aa directory: ''/Smalltalk/Squeak/Goodies''.
  	aa url: ''''.    "<- this is optional.  Only used when *writing* update files."
  	ServerDirectory addServer: aa named: ''UIUCArchive''.  "<- known by this name in Squeak"'.
  
  	(StringHolder new contents: template) openLabel: 'FTP Server Form'
  	!

Item was changed:
  ----- Method: TextEditor class>>initializeShiftCmdKeyShortcuts (in category 'keyboard shortcut tables') -----
  initializeShiftCmdKeyShortcuts 
  	"Initialize the shift-command-key (or control-key) shortcut table."
  	"NOTE: if you don't know what your keyboard generates, use Sensor kbdTest"
  	"wod 11/3/1998: Fix setting of cmdMap for shifted keys to actually use the 
  	capitalized versions of the letters.
  	TPR 2/18/99: add the plain ascii values back in for those VMs that don't return the shifted values."
  
  	"TextEditor initialize"
  	
  	| cmdMap cmds |
  
  	"shift-command and control shortcuts"
+ 	cmdMap := Array new: 256 withAll: #noop:.  		"use temp in case of a crash"
- 	cmdMap _ Array new: 256 withAll: #noop:.  		"use temp in case of a crash"
  	cmdMap at: ( 1 + 1) put: #cursorHome:.			"home key"
  	cmdMap at: ( 4 + 1) put: #cursorEnd:.				"end key"
  	cmdMap at: ( 8 + 1) put: #forwardDelete:.			"ctrl-H or delete key"
  	cmdMap at: (11 + 1) put: #cursorPageUp:.			"page up key"
  	cmdMap at: (12 + 1) put: #cursorPageDown:.		"page down key"
  	cmdMap at: (13 + 1) put: #crWithIndent:.			"ctrl-Return"
  	cmdMap at: (27 + 1) put: #offerMenuFromEsc:.	"escape key"
  	cmdMap at: (28 + 1) put: #cursorLeft:.			"left arrow key"
  	cmdMap at: (29 + 1) put: #cursorRight:.			"right arrow key"
  	cmdMap at: (30 + 1) put: #cursorUp:.				"up arrow key"
  	cmdMap at: (31 + 1) put: #cursorDown:.			"down arrow key"
  	cmdMap at: (32 + 1) put: #selectWord:.			"space bar key"
  	cmdMap at: (45 + 1) put: #changeEmphasis:.		"cmd-sh-minus"
  	cmdMap at: (61 + 1) put: #changeEmphasis:.		"cmd-sh-plus"
  	cmdMap at: (127 + 1) put: #forwardDelete:.		"del key"
  
  	"Note: Command key overrides shift key, so, for example, cmd-shift-9 produces $9 not $("
  	'9[,''' do: [ :char | cmdMap at: (char asciiValue + 1) put: #shiftEnclose: ].	"({< and double-quote"
  	"Note: Must use cmd-9 or ctrl-9 to get '()' since cmd-shift-9 is a Mac FKey command."
  
  	"NB: sw 12/9/2001 commented out the idiosyncratic line just below, which was grabbing shift-esc in the text editor and hence which argued with the wish to have shift-esc be a universal gesture for escaping the local context and calling up the desktop menu."  
  	"cmdMap at: (27 + 1) put: #shiftEnclose:." 	"ctrl-["
  
  	"'""''(' do: [ :char | cmdMap at: (char asciiValue + 1) put: #enclose:]."
  
+ 	cmds := #(
- 	cmds _ #(
  		$c	compareToClipboard:
  		$d	duplicate:
  		$h	cursorTopHome:
  		$j	doAgainMany:
  		$k	changeStyle:
  		$l	outdent:
  		$m	selectCurrentTypeIn:
  		$r	indent:
  		$s	search:
  		$u	changeLfToCr:
  		$x	makeLowercase:
  		$y	makeUppercase:
  		$z	makeCapitalized:
  	).
  	1 to: cmds size by: 2 do: [ :i |
  		cmdMap at: ((cmds at: i) asciiValue + 1) put: (cmds at: i + 1).			"plain keys"
  		cmdMap at: ((cmds at: i) asciiValue - 32 + 1) put: (cmds at: i + 1).		"shifted keys"
  		cmdMap at: ((cmds at: i) asciiValue - 96 + 1) put: (cmds at: i + 1).		"ctrl keys"
  	].
+ 	shiftCmdActions := cmdMap!
- 	shiftCmdActions _ cmdMap!

Item was changed:
  ----- Method: TextEditor>>spawn (in category 'menu messages') -----
  spawn
  	"Create and schedule a message browser for the code of the model's 
  	selected message. Retain any edits that have not yet been accepted."
  	| code |
+ 	code := paragraph text string.
- 	code _ paragraph text string.
  	self cancel.
  	model spawn: code.!

Item was changed:
  ----- Method: TextEditor>>changeSelectionFontTo: (in category 'attributes') -----
  changeSelectionFontTo: aFont
  	| attr |
  	aFont ifNil:[^self].
+ 	attr := TextFontReference toFont: aFont.
- 	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 changed:
  ----- Method: TextEditor>>browseItHere (in category 'menu messages') -----
  browseItHere
  	"Retarget the receiver's window to look at the selected class, if appropriate.  3/1/96 sw"
  	| aSymbol foundClass b |
+ 	(((b := model) isKindOf: Browser) and: [b couldBrowseAnyClass])
- 	(((b _ model) isKindOf: Browser) and: [b couldBrowseAnyClass])
  		ifFalse: [^ morph flash].
  	model okToChange ifFalse: [^ morph flash].
  	self selectionInterval isEmpty ifTrue: [self selectWord].
+ 	(aSymbol := self selectedSymbol) isNil ifTrue: [^ morph flash].
- 	(aSymbol _ self selectedSymbol) isNil ifTrue: [^ morph flash].
  
+ 	foundClass := (Smalltalk at: aSymbol ifAbsent: [nil]).
- 	foundClass _ (Smalltalk at: aSymbol ifAbsent: [nil]).
  		foundClass isNil ifTrue: [^ morph flash].
  		(foundClass isKindOf: Class)
  			ifTrue:
  				[model systemCategoryListIndex: 
  					(model systemCategoryList indexOf: foundClass category).
  	model classListIndex: (model classList indexOf: foundClass name)]!

Item was changed:
  ----- Method: TextEditor>>changeParagraph: (in category 'initialize-release') -----
  changeParagraph: aParagraph 
  	"Install aParagraph as the one to be edited by the receiver."
  
+ 	UndoParagraph == paragraph ifTrue: [UndoParagraph := nil].
+ 	paragraph := aParagraph.
- 	UndoParagraph == paragraph ifTrue: [UndoParagraph _ nil].
- 	paragraph _ aParagraph.
  	self resetState!

Item was changed:
  ----- Method: TextEditor class>>abandonChangeText (in category 'class initialization') -----
  abandonChangeText
  	"Call this to get out of the maddening situation in which the system keeps aggressively trying to do a replacement that you no longer wish to make, every time you make choose a new method in a list."
+ 	ChangeText := FindText
- 	ChangeText _ FindText
  
  	"
  	TextEditor abandonChangeText
  	"!

Item was changed:
  ----- Method: TextEditor>>openTypeIn (in category 'typing support') -----
  openTypeIn
  	"Set up UndoSelection to null text (to be added to by readKeyboard and backTo:),
  	 beginTypeInBlock to keep track of the leftmost backspace, and UndoParameter to tally
  	 how many deleted characters were backspaced over rather than 'cut'.
  	 You can't undo typing until after closeTypeIn."
  
  	beginTypeInBlock ifNil: [
+ 		UndoSelection := self nullText.
- 		UndoSelection _ self nullText.
  		self undoer: #noUndoer with: 0.
+ 		beginTypeInBlock := self startIndex]!
- 		beginTypeInBlock _ self startIndex]!

Item was changed:
  ----- Method: TextEditor>>compareToClipboard (in category 'menu messages') -----
  compareToClipboard
  	"Check to see if whether the receiver's text is the same as the text currently on the clipboard, and inform the user."
  	| s1 s2 |
+ 	s1 := self clipboardText string.
+ 	s2 := paragraph text string.
- 	s1 _ self clipboardText string.
- 	s2 _ paragraph text string.
  	s1 = s2 ifTrue: [^ self inform: 'Exact match'].
  
  	(StringHolder new textContents:
  		(TextDiffBuilder buildDisplayPatchFrom: s1 to: s2))
  		openLabel: 'Comparison to Clipboard Text'!

Item was changed:
  ----- Method: TextEditor>>evaluateSelection (in category 'do-its') -----
  evaluateSelection
  	"Treat the current selection as an expression; evaluate it and return the result"
  	| result rcvr ctxt |
  	self lineSelectAndEmptyCheck: [^ ''].
  
  	(model respondsTo: #doItReceiver) 
  		ifTrue: [FakeClassPool adopt: model selectedClass.  "Include model pool vars if any"
+ 				rcvr := model doItReceiver.
+ 				ctxt := model doItContext]
+ 		ifFalse: [rcvr := ctxt := nil].
+ 	result := [
- 				rcvr _ model doItReceiver.
- 				ctxt _ model doItContext]
- 		ifFalse: [rcvr _ ctxt _ nil].
- 	result _ [
  		rcvr class evaluatorClass new 
  			evaluate: self selectionAsStream
  			in: ctxt
  			to: rcvr
  			notifying: self
  			ifFail: [FakeClassPool adopt: nil. ^ #failedDoit]
  			logged: true.
  	] 
  		on: OutOfScopeNotification 
  		do: [ :ex | ex resume: true].
  	FakeClassPool adopt: nil.
  	^ result!

Item was changed:
  ----- Method: TextEditor>>markBlock: (in category 'accessing-selection') -----
  markBlock: aCharacterBlock
+ 	markBlock := aCharacterBlock!
- 	markBlock _ aCharacterBlock!

Item was changed:
  ----- Method: TextEditor>>isDisjointFrom: (in category 'private') -----
  isDisjointFrom: anInterval
  	"Answer true if anInterval is a caret not touching or within the current
  	 interval, or if anInterval is a non-caret that does not overlap the current
  	 selection."
  
  	| fudge |
+ 	fudge := anInterval size = 0 ifTrue: [1] ifFalse: [0].
- 	fudge _ anInterval size = 0 ifTrue: [1] ifFalse: [0].
  	^(anInterval last + fudge < self startIndex or:
  			[anInterval first - fudge >= self stopIndex])
  !

Item was changed:
  ----- Method: TextEditor>>exploreIt (in category 'do-its') -----
  exploreIt
  	| result |
+ 	result := self evaluateSelection.
- 	result _ self evaluateSelection.
  	((result isKindOf: FakeClassPool) or: [result == #failedDoit])
  			ifTrue: [morph flash]
  			ifFalse: [result explore]!

Item was changed:
  ----- Method: TextEditor>>readKeyboard (in category 'typing support') -----
  readKeyboard
  	"Key struck on the keyboard. Find out which one and, if special, carry 
  	out the associated special action. Otherwise, add the character to the 
  	stream of characters.  Undoer & Redoer: see closeTypeIn."
  
  	| typeAhead char |
+ 	typeAhead := WriteStream on: (String new: 128).
- 	typeAhead _ WriteStream on: (String new: 128).
  	[ sensor keyboardPressed ] whileTrue: [
  		self deselect.
  		[ sensor keyboardPressed ] whileTrue: [
+ 			char := sensor keyboardPeek.
- 			char _ sensor keyboardPeek.
  			(self dispatchOnCharacter: char with: typeAhead) ifTrue: [
  				self doneTyping.
  				self storeSelectionInParagraph.
  				^self].
  			self openTypeIn].
  		self hasSelection ifTrue: [ "save highlighted characters"
+ 			UndoSelection := self selection].
- 			UndoSelection _ self selection].
  		self zapSelectionWith: 
  			(Text string: typeAhead contents attributes: emphasisHere).
  		typeAhead reset.
  		self unselect].
  	self storeSelectionInParagraph!

Item was changed:
  ----- Method: TextEditor>>pasteRecent (in category 'menu messages') -----
  pasteRecent
  	"Paste an item chose from RecentClippings."
  
  	| clipping |
+ 	(clipping := Clipboard chooseRecentClipping) ifNil: [^ self].
- 	(clipping _ Clipboard chooseRecentClipping) ifNil: [^ self].
  	Clipboard clipboardText: clipping.
  	^ self paste!

Item was changed:
  ----- Method: TextEditor>>swapChars: (in category 'editing keys') -----
  swapChars: characterStream 
  	"Triggered byCmd-Y;.  Swap two characters, either those straddling the insertion point, or the two that comprise the selection.  Suggested by Ted Kaehler.  "
  
  	| currentSelection aString chars |
  	sensor keyboard.		"flush the triggering cmd-key character"
+ 	(chars := self selection) size = 0
- 	(chars _ self selection) size = 0
  		ifTrue:
+ 			[currentSelection := self pointIndex.
- 			[currentSelection _ self pointIndex.
  			self selectMark: currentSelection - 1 point: currentSelection]
  		ifFalse:
  			[chars size = 2
  				ifFalse:
  					[morph flash. ^ true]
  				ifTrue:
+ 					[currentSelection := self pointIndex - 1]].
+ 	aString := self selection string.
- 					[currentSelection _ self pointIndex - 1]].
- 	aString _ self selection string.
  	self replaceSelectionWith: (Text string: aString reversed attributes: emphasisHere).
  	self selectAt: currentSelection + 1.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>explainScan: (in category 'explain') -----
  explainScan: string 
  	"Remove beginning and trailing space, tab, cr.
  	 1/15/96 sw: copied intact from BrowserCodeController"
  
  	| c beg end |
+ 	beg := 1.
+ 	end := string size.
- 	beg _ 1.
- 	end _ string size.
  	
  	[beg = end ifTrue: [^string copyFrom: 1 to: 1].
  	"if all blank, tell about the first"
+ 	c := string at: beg.
- 	c _ string at: beg.
  	c = Character space or: [c = Character tab or: [c = Character cr]]]
+ 		whileTrue: [beg := beg + 1].
- 		whileTrue: [beg _ beg + 1].
  	
+ 	[c := string at: end.
- 	[c _ string at: end.
  	c = Character space or: [c = Character tab or: [c = Character cr]]]
+ 		whileTrue: [end := end - 1].
- 		whileTrue: [end _ end - 1].
  	^string copyFrom: beg to: end	"Return purely visible characters"!

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."
  
  	| pos |
+ 	pos := self selectionInterval notEmpty
- 	pos _ self selectionInterval notEmpty
  		ifTrue: [
  			self startIndex + anInteger - 1 ]
  		ifFalse: [anInteger].
  	self insertAndSelect: aString at: (pos max: 1)!

Item was changed:
  ----- Method: TextMorphEditor>>changeSelectionFontTo: (in category 'attributes') -----
  changeSelectionFontTo: aFont
  	| attr |
  	aFont ifNil:[^self].
+ 	attr := TextFontReference toFont: aFont.
- 	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 changed:
  ----- Method: TextEditor>>printIt (in category 'do-its') -----
  printIt
  	"Treat the current text selection as an expression; evaluate it. Insert the 
  	description of the result of evaluation after the selection and then make 
  	this description the new text selection."
  	| result |
+ 	result := self evaluateSelection.
- 	result _ self evaluateSelection.
  	((result isKindOf: FakeClassPool) or: [result == #failedDoit])
  			ifTrue: [morph flash]
  			ifFalse: [self afterSelectionInsertAndSelect: result printString]!

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

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

Item was changed:
  ----- Method: TextMorph>>keyStroke: (in category 'event handling') -----
  keyStroke: evt
  	"Handle a keystroke event."
  	| action |
  	self resetBlinkCursor. "don't blink during type-in"
  	evt keyValue = 13 ifTrue:["CR - check for special action"
+ 		action := self crAction.
- 		action _ self crAction.
  		action ifNotNil:[
  			"Note: Code below assumes that this was some
  			input field reacting on CR. Break the keyboard
  			focus so that the receiver can be safely deleted."
  			evt hand newKeyboardFocus: nil.
  			^action value]].
  	self handleInteraction: [editor readKeyboard] fromEvent: evt.
  	"self updateFromParagraph."
  	super keyStroke: evt  "sends to keyStroke event handler, if any"!

Item was changed:
  ----- Method: TextEditor>>setEmphasis: (in category 'editing keys') -----
  setEmphasis: emphasisSymbol
  	"Change the emphasis of the current selection."
  
  	| oldAttributes attribute |
+ 	oldAttributes := paragraph text attributesAt: self selectionInterval first.
- 	oldAttributes _ paragraph text attributesAt: self selectionInterval first.
  
+ 	attribute := TextEmphasis perform: emphasisSymbol.
- 	attribute _ TextEmphasis perform: emphasisSymbol.
  	(emphasisSymbol == #normal) 
  		ifFalse:	[oldAttributes do:	
  			[:att | (att dominates: attribute) ifTrue: [attribute turnOff]]].
  	self replaceSelectionWith: (self selection addAttribute: attribute)!




More information about the Squeak-dev mailing list