[Pkg] The Trunk: Morphic-nice.559.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Aug 3 22:01:08 UTC 2011


Nicolas Cellier uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-nice.559.mcz

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

Name: Morphic-nice.559
Author: nice
Time: 3 August 2011, 11:47:38.397 pm
UUID: 2d464aec-2c88-4ad0-9f51-6c208b5cdf82
Ancestors: Morphic-nice.558

Let TextEditor be event driven and let us ban sensor usage from it.

Details:

I tried to apply Cuis 3.3 methods where possible and kept Squeakism where necessary.

There are unused methods that crept into the Editor classes, but we'll see later about further convergence with Cuis or not...

Like Cuis, I renamed ivar beginTypeInBlock -> beginTypeInIndex because this is an Integer index, not a CharacterBlock.
Code is already long enough to avoid such traps.
I also removed sensor and the structure of the TextEditor did change a lot. So it's hard to say if code is reloadable... The inbox will be a test place.

Like Cuis I removed the typeAheadStream which was useless already since we recompose after each key stroke.
Instead of such stream, the keyboard event is passed as argument to editing methods.

Some small divergences:

I did not define TextEditor>>#processKeyboardEvent: but TextEditor>>#keyStroke:
My rationale was that mouseUp: mouseDown: and mouseMove: were not renamed, so why renaming keyStroke: ?
On the other hand, it would be easier to follow code with different selectors, and maybe also good for a VM to reduce unecessary polymorphism.

I did not define TextEditor>>#dispathOn: but TextEditor>>#dispatchOnKeyboardEvent:
I felt this was more clear... less unecessary polymorphism. My mood was changing ;)

These above two behaviours have not been unified (Cuis only deal with 256 characters and can offer a dispatch table for all characters, we can't).

Unlike Cuis I did not implement multi selection (?).
I also kept the oldInterval and otherInterval ivars because I don't know if I can touch them.
I also kept selectionShowing because I'm totally unaware of these details.

I did not yet imported the SimpleEditor.
Thanks to Juan for leading the process, and cross the fingers to see if update is possible or require intermediate stages.

=============== Diff against Morphic-nice.558 ===============

Item was changed:
  Object subclass: #Editor
+ 	instanceVariableNames: 'morph selectionShowing'
+ 	classVariableNames: 'BlinkingCursor DestructiveBackWord DumbbellCursor KeystrokeActions SelectionsMayShrink'
- 	instanceVariableNames: 'sensor morph selectionShowing'
- 	classVariableNames: 'BlinkingCursor DestructiveBackWord DumbbellCursor SelectionsMayShrink'
  	poolDictionaries: ''
  	category: 'Morphic-Text Support'!
  
  !Editor commentStamp: '<historical>' prior: 0!
  New text editors.
+ TextEditor provides most of the functionality that used to be in TextMorphEditor.
- TextEditor provides most of the functionality that used to be in TextMorphEditor. This class is no longer a Controller!!
  SmalltalkEditor is has Smalltalk code specific features.
  SimpleEditor provides basic functionality for single line text editing. It does not handle fonts and styles, aligning and Smalltalk utilities. It handles one single line.
+ CellStyleEditor allows entering alphabetic characters using only number keys, like many cell phones do.!
- CellStyleEditor allows entering alphabetic characters using only number keys, like most cell phones do.!

Item was changed:
  ----- Method: Editor class>>initialize (in category 'class initialization') -----
  initialize
  	"
  	Editor initialize
  	"
+ 	self initializeKeystrokeActions.
  	self allSubclassesDo: [ :c | c initialize ]!

Item was added:
+ ----- Method: Editor class>>initializeKeystrokeActions (in category 'class initialization') -----
+ initializeKeystrokeActions
+ 	"Initialize the table for regular (i.e. non-command) keystroke dispatch"
+ 	"
+ 	self initializeKeystrokeActions
+ 	"
+ 	| actions |
+ 	actions := Array new: 256 withAll: #normalCharacter:.
+ 	0 to: 31 do: [ :i | actions at: i+1 put: #noop: ].
+ 	actions at: 1 + 1 put: #cursorHome:.				"home key"
+ 	actions at: 3 + 1 put: #enter:.						"enter / return key"
+ 	actions at: 4 + 1 put: #cursorEnd:.				"end key"
+ 	actions at: 5 + 1 put: #noop:.						"insert key"
+ 	actions at: 8 + 1 put: #backspace:.				"macDelete winBackspace key"
+ 	actions at: 9 + 1 put: #normalCharacter:.		"tab"
+ 	actions at: 11 + 1 put: #cursorPageUp:.			"page up key"
+ 	actions at: 12 + 1 put: #cursorPageDown:.		"page down key"
+ 	actions at: 13 + 1 put: #enter:.					"enter / return key"
+ 	actions at: 27 + 1 put: #offerMenuFromEsc:.	"escape key"
+ 	actions at: 28 + 1 put: #cursorLeft:.				"left arrow key"
+ 	actions at: 29 + 1 put: #cursorRight:.				"right arrow key"
+ 	actions at: 30 + 1 put: #cursorUp:.				"up arrow key"
+ 	actions at: 31 + 1 put: #cursorDown:.			"down arrow key"
+ 	actions at: 127 + 1 put: #forwardDelete:.		"winDelete key"
+ 	KeystrokeActions := actions!

Item was changed:
  ----- Method: Editor>>backWord: (in category 'typing/selecting keys') -----
+ backWord: aKeyboardEvent 
- backWord: characterStream 
  	^ self class destructiveBackWord 
+ 		ifTrue: [ self destructiveBackWord: aKeyboardEvent ]
+ 		ifFalse: [ self nonDestructiveBackWord: aKeyboardEvent ]!
- 		ifTrue: [ self destructiveBackWord: characterStream ]
- 		ifFalse: [ self nonDestructiveBackWord: characterStream ]!

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

Item was added:
+ ----- Method: Editor>>beginningOfLine: (in category 'private') -----
+ beginningOfLine: position
+ 	"Redefined in subclasses using Paragraph support"
+ 	^ self beginningOfParagraph: position!

Item was added:
+ ----- Method: Editor>>beginningOfNextParagraph: (in category 'private') -----
+ beginningOfNextParagraph: position
+ 	| s |
+ 	s := self string.
+ 	^ (s
+ 		indexOf: Character cr
+ 		startingAt: position
+ 		ifAbsent: [ s size ]) + 1!

Item was added:
+ ----- Method: Editor>>beginningOfParagraph: (in category 'private') -----
+ beginningOfParagraph: position
+ 	^ (self string
+ 		lastIndexOf: Character cr
+ 		startingAt: position
+ 		ifAbsent: [ 0 ]) + 1.!

Item was added:
+ ----- Method: Editor>>beginningOfText (in category 'private') -----
+ beginningOfText
+ 	^1!

Item was added:
+ ----- Method: Editor>>clearSelection (in category 'typing/selecting keys') -----
+ clearSelection
+ 
+ 	self selectFrom: 1 to: 0!

Item was removed:
- ----- Method: Editor>>closeTypeIn: (in category 'typing support') -----
- closeTypeIn: characterStream
- 	"Call instead of closeTypeIn when you want typeahead to be inserted before the
- 	 control character is executed, e.g., from Ctrl-V."
- 
- 	self insertTypeAhead: characterStream.
- 	self closeTypeIn!

Item was changed:
  ----- Method: Editor>>copySelection: (in category 'editing keys') -----
+ copySelection: aKeyboardEvent
+ 	"Copy the current text selection."
- copySelection: characterStream 
- 	"Copy the current text selection.  Flushes typeahead."
  
- 	sensor keyboard.		"flush character"
  	self copySelection.
  	^true!

Item was added:
+ ----- Method: Editor>>cr: (in category 'typing/selecting keys') -----
+ cr: aKeyboardEvent
+ 	"Append a carriage return character to the stream of characters."
+ 
+ 	self addString: Character cr asString.
+ 	^false!

Item was added:
+ ----- Method: Editor>>crWithIndent: (in category 'typing/selecting keys') -----
+ crWithIndent: aKeyboardEvent
+ 
+ 	"Only for SmalltalkEditor. Regular editors don't indent"
+ 	^ self cr: aKeyboardEvent!

Item was changed:
  ----- Method: Editor>>crlf: (in category 'typing/selecting keys') -----
+ crlf: aKeyboardEvent
- crlf: characterStream 
  	"Append a line feed character to the stream of characters."
  
+ 	self addString: String crlf.
- 	sensor keyboard.
- 	characterStream
- 		nextPut: Character cr;
- 		nextPut: Character lf.
  	^false!

Item was changed:
  ----- Method: Editor>>cursorDown: (in category 'nonediting/nontyping keys') -----
+ cursorDown: aKeyboardEvent
- cursorDown: characterStream 
- 
  	"Private - Move cursor from position in current line to same position in
  	next line. If next line too short, put at end. If shift key down,
  	select."
+ 	self closeTypeIn.
- 	self closeTypeIn: characterStream.
  	self 
+ 		moveCursor: [:position | self
- 		moveCursor:[:position | self
  				sameColumn: position
+ 				newLine: [:line | line + 1]
- 				newLine:[:line | line + 1]
  				forward: true]
  		forward: true
+ 		event: aKeyboardEvent
+ 		specialBlock: [:dummy | dummy].
- 		specialBlock:[:dummy | dummy].
  	^true!

Item was changed:
  ----- Method: Editor>>cursorLeft: (in category 'nonediting/nontyping keys') -----
+ cursorLeft: aKeyboardEvent
- cursorLeft: characterStream 
  	"Private - Move cursor left one character if nothing selected, otherwise 
  	move cursor to beginning of selection. If the shift key is down, start 
  	selecting or extending current selection. Don't allow cursor past 
  	beginning of text"
  
+ 	self closeTypeIn.
- 	self closeTypeIn: characterStream.
  	self
  		moveCursor:[:position | position - 1 max: 1]
  		forward: false
+ 		event: aKeyboardEvent
  		specialBlock:[:position | self previousWord: position].
  	^ true!

Item was changed:
  ----- Method: Editor>>cursorPageDown: (in category 'nonediting/nontyping keys') -----
+ cursorPageDown: aKeyboardEvent
- cursorPageDown: characterStream 
  
+ 	self closeTypeIn.
- 	self closeTypeIn: characterStream.
  	self 
  		moveCursor: [:position |
  			self
  				sameColumn: position
  				newLine: [:lineNo | lineNo + self pageHeight]
  				forward: true]
  		forward: true
+ 		event: aKeyboardEvent
  		specialBlock:[:dummy | dummy].
  	^true!

Item was changed:
  ----- Method: Editor>>cursorPageUp: (in category 'nonediting/nontyping keys') -----
+ cursorPageUp: aKeyboardEvent 
- cursorPageUp: characterStream 
  
+ 	self closeTypeIn.
- 	self closeTypeIn: characterStream.
  	self 
  		moveCursor: [:position |
  			self
  				sameColumn: position
  				newLine: [:lineNo | lineNo - self pageHeight]
  				forward: false]
  		forward: false
+ 		event: aKeyboardEvent
  		specialBlock:[:dummy | dummy].
  	^true!

Item was changed:
  ----- Method: Editor>>cursorRight: (in category 'nonediting/nontyping keys') -----
+ cursorRight: aKeyboardEvent 
- cursorRight: characterStream 
  	"Private - Move cursor right one character if nothing selected, 
  	otherwise move cursor to end of selection. If the shift key is down, 
  	start selecting characters or extending already selected characters. 
  	Don't allow cursor past end of text"
  
+ 	self closeTypeIn.
- 	self closeTypeIn: characterStream.
  	self
  		moveCursor: [:position | position + 1]
  		forward: true
+ 		event: aKeyboardEvent
  		specialBlock:[:position | self nextWord: position].
  	^ true!

Item was changed:
  ----- Method: Editor>>cursorTopHome: (in category 'typing/selecting keys') -----
+ cursorTopHome: aKeyboardEvent
- cursorTopHome: characterStream 
  	"Put cursor at beginning of text -- invoked from cmd-H shortcut, useful for keyboards that have no home key."
+ 
- 	
- 	sensor keyboard.
  	self selectAt: 1.
  	^ true!

Item was changed:
  ----- Method: Editor>>cursorUp: (in category 'nonediting/nontyping keys') -----
+ cursorUp: aKeyboardEvent 
+ 	"Private - Move cursor from position in current line to same position in
+ 	prior line. If prior line too short, put at end"
- cursorUp: characterStream 
  
+ 	self closeTypeIn.
- "Private - Move cursor from position in current line to same position in
- prior line. If prior line too short, put at end"
- 
- 	self closeTypeIn: characterStream.
  	self
  		moveCursor: [:position | self
  				sameColumn: position
  				newLine:[:line | line - 1]
  				forward: false]
  		forward: false
+ 		event: aKeyboardEvent
  		specialBlock:[:dummy | dummy].
  	^true!

Item was changed:
  ----- Method: Editor>>cut: (in category 'editing keys') -----
+ cut: aKeyboardEvent 
+ 	"Cut out the current text selection."
- cut: characterStream 
- 	"Cut out the current text selection.  Flushes typeahead."
  
- 	sensor keyboard.		"flush character"
  	self cut.
  	^true!

Item was changed:
  ----- Method: Editor>>destructiveBackWord: (in category 'typing/selecting keys') -----
+ destructiveBackWord: aKeyboardEvent 
- destructiveBackWord: 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 |
+ 	self hasCaret
+ 		ifTrue: "a caret, delete at least one character"
+ 			[startIndex := 1 max: self markIndex - 1.
+ 			[startIndex > 1 and:
+ 				[(self string at: startIndex - 1) tokenish]]
+ 				whileTrue:
+ 					[startIndex := startIndex - 1]]
+ 		ifFalse: "a non-caret, just delete it"
+ 			[startIndex := self markIndex].
+ 	self backTo: startIndex.
- 	sensor keyboard.
- 	characterStream isEmpty
- 		ifTrue:
- 			[self hasCaret
- 				ifTrue: "a caret, delete at least one character"
- 					[startIndex := 1 max: self markIndex - 1.
- 					[startIndex > 1 and:
- 						[(self string at: startIndex - 1) tokenish]]
- 						whileTrue:
- 							[startIndex := startIndex - 1]]
- 				ifFalse: "a non-caret, just delete it"
- 					[startIndex := self markIndex].
- 			self backTo: startIndex]
- 		ifFalse:
- 			[characterStream reset].
  	^false!

Item was added:
+ ----- Method: Editor>>endOfLine: (in category 'private') -----
+ endOfLine: position
+ 	"Redefined in subclasses using Paragraph support"
+ 	^self endOfParagraph: position!

Item was added:
+ ----- Method: Editor>>endOfParagraph: (in category 'private') -----
+ endOfParagraph: position
+ 	| s |
+ 	s := self string.
+ 	^ s
+ 		indexOf: Character cr
+ 		startingAt: position
+ 		ifAbsent: [ s size + 1 ].!

Item was added:
+ ----- Method: Editor>>endOfText (in category 'private') -----
+ endOfText
+ 	^self string size + 1!

Item was added:
+ ----- Method: Editor>>enter: (in category 'typing/selecting keys') -----
+ enter: aKeyboardEvent
+ 	"Enter / return key was pressed"
+ 	"Process the various Enter / Return keystrokes"
+ 	
+ 	morph acceptOnCR ifTrue: [
+ 		self closeTypeIn.
+ 		^ true].
+ 
+ 	aKeyboardEvent controlKeyPressed ifTrue: [
+ 		^ self cr: aKeyboardEvent ].
+ 	aKeyboardEvent shiftPressed ifTrue: [
+ 		^ self lf: aKeyboardEvent ].
+ 	aKeyboardEvent commandAltKeyPressed ifTrue: [
+ 		^ self crlf: aKeyboardEvent ].
+ 	^ self crWithIndent: aKeyboardEvent!

Item was removed:
- ----- 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!

Item was changed:
  ----- Method: Editor>>lf: (in category 'typing/selecting keys') -----
+ lf: aKeyboardEvent 
- lf: characterStream 
  	"Append a line feed character to the stream of characters."
  
+ 	self addString: Character lf asString.
- 	sensor keyboard.
- 	characterStream nextPut: Character lf.
  	^false!

Item was added:
+ ----- Method: Editor>>moveCursor:forward:event:specialBlock: (in category 'private') -----
+ moveCursor: directionBlock forward: forward event: aKeyboardEvent 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."
+ 	| indices newPosition shouldSelect |
+ 	shouldSelect := aKeyboardEvent shiftPressed.
+ 	indices := self setIndices: shouldSelect forward: forward.
+ 	newPosition := directionBlock value: (indices at: #moving).
+ 	(aKeyboardEvent commandKeyPressed or: [aKeyboardEvent controlKeyPressed])
+ 		ifTrue: [newPosition := specialBlock value: newPosition].
+ 	shouldSelect
+ 		ifTrue: [self selectMark: (indices at: #fixed) point: newPosition - 1]
+ 		ifFalse: [self selectAt: newPosition]!

Item was added:
+ ----- Method: Editor>>moveCursor:forward:select: (in category 'private') -----
+ moveCursor: directionBlock forward: forward select: shouldSelect
+ 	"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."
+ 	| indices newPosition |
+ 	indices := self setIndices: shouldSelect forward: forward.
+ 	newPosition := directionBlock value: (indices at: #moving).
+ 	shouldSelect
+ 		ifTrue: [self selectMark: (indices at: #fixed) point: newPosition - 1]
+ 		ifFalse: [self selectAt: newPosition]!

Item was removed:
- ----- 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."
- 	^ self
- 		moveCursor: directionBlock
- 		forward: forward
- 		specialBlock: specialBlock
- 		select: sensor leftShiftDown!

Item was removed:
- ----- Method: Editor>>moveCursor:forward:specialBlock:select: (in category 'private') -----
- moveCursor: directionBlock forward: forward specialBlock: specialBlock select: shouldSelect
- 	"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."
- 	| indices newPosition |
- 	indices := self setIndices: shouldSelect forward: forward.
- 	newPosition := directionBlock value: (indices at: #moving).
- 	(sensor commandKeyPressed or:[sensor controlKeyPressed])
- 		ifTrue: [newPosition := specialBlock value: newPosition].
- 	sensor keyboard.
- 	shouldSelect
- 		ifTrue: [self selectMark: (indices at: #fixed) point: newPosition - 1]
- 		ifFalse: [self selectAt: newPosition]!

Item was changed:
  ----- Method: Editor>>nonDestructiveBackWord: (in category 'typing/selecting keys') -----
+ nonDestructiveBackWord: aKeyboardEvent 
- nonDestructiveBackWord: characterStream 
  	"Select the prior word."
  	| indices newPosition |
+ 	self closeTypeIn.
- 	self closeTypeIn: characterStream.
  	indices := self 
  		setIndices: true
  		forward: false.
+ 	newPosition := 1 max: (indices at: #moving) - 1.
- 	newPosition := 1 max: (indices at: #moving)-1.
  	newPosition :=  self previousWord: newPosition.
- 	sensor keyboard.
  	self selectMark: (indices at: #fixed) point: newPosition - 1.
  	^ true!

Item was changed:
  ----- Method: Editor>>noop: (in category 'editing keys') -----
+ noop: aKeyboardEvent 
- noop: characterStream 
  	"Unimplemented keyboard command; just ignore it."
  
- 	sensor keyboard.	  "flush character"
  	^ true!

Item was changed:
  ----- Method: Editor>>normalCharacter: (in category 'typing/selecting keys') -----
+ normalCharacter: aKeyboardEvent 
- normalCharacter: characterStream 
  	"A nonspecial character is to be added to the stream of characters."
  
+ 	self addString: aKeyboardEvent keyCharacter asString.
- 	characterStream nextPut: sensor keyboard.
  	^false!

Item was changed:
  ----- Method: Editor>>paste: (in category 'editing keys') -----
+ paste: aKeyboardEvent 
+ 	"Replace the current text selection by the text in the shared buffer."
- paste: characterStream 
- 	"Replace the current text selection by the text in the shared buffer.
- 	 Keeps typeahead."
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self paste.
  	^true!

Item was changed:
  ----- Method: Editor>>selectAll: (in category 'typing/selecting keys') -----
+ selectAll: aKeyboardEvent 
- selectAll: characterStream 
  	"select everything, invoked by cmd-a.  1/17/96 sw"
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self selectFrom: 1 to: self string size.
  	^ true!

Item was changed:
  ----- Method: Editor>>selectInvisiblyFrom:to: (in category 'new selection') -----
  selectInvisiblyFrom: start to: stop
  	"Select the designated characters, inclusive.  Make no visual changes."
  
+ 	self markIndex: start pointIndex: stop + 1!
- 	self markIndex: start; pointIndex: stop + 1!

Item was changed:
  ----- Method: Editor>>selectInvisiblyMark:point: (in category 'new selection') -----
  selectInvisiblyMark: mark point: point
  	"Select the designated characters, inclusive.  Make no visual changes."
  
+ 	self markIndex: mark pointIndex: point + 1!
- 	self markIndex: mark; pointIndex: point + 1!

Item was changed:
  ----- Method: Editor>>selectMark:point: (in category 'new selection') -----
  selectMark: mark point: point
  	"Deselect, then select the specified characters inclusive.
  	 Be sure the selection is in view."
  
+ 	(mark =  self markIndex and: [point + 1 = self pointIndex]) ifFalse: [
+ 		self selectInvisiblyMark: mark point: point ]!
- 	(mark =  self markIndex and: [point + 1 = self pointIndex]) ifFalse:
- 		[self deselect.
- 		self selectInvisiblyMark: mark point: point]!

Item was changed:
  ----- Method: Editor>>selectWord (in category 'new selection') -----
  selectWord
  	"Select delimited text or word--the result of double-clicking."
  
+ 	^self selectWordLeftDelimiters: String cr rightDelimiters: String cr!
- 	| openDelimiter closeDelimiter direction match level leftDelimiters rightDelimiters
- 	string here hereChar start stop |
- 	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 := '([{<''"
- '.
- 	rightDelimiters := ')]}>''"
- '.
- 	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]
- 		ifFalse: 
- 			[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]
- 				ifFalse: ["no delimiters -- select a token"
- 					direction := -1]].
- 	level := 1.
- 	[level > 0 and: [direction > 0
- 			ifTrue: [here < string size]
- 			ifFalse: [here > 1]]]
- 		whileTrue: 
- 			[hereChar := string at: (here := here + direction).
- 			match = 0
- 				ifTrue: ["token scan goes left, then right"
- 					hereChar tokenish
- 						ifTrue: [here = 1
- 								ifTrue: 
- 									[start := 1.
- 									"go right if hit string start"
- 									direction := 1]]
- 						ifFalse: [direction < 0
- 								ifTrue: 
- 									[start := here + 1.
- 									"go right if hit non-token"
- 									direction := 1]
- 								ifFalse: [level := 0]]]
- 				ifFalse: ["bracket match just counts nesting level"
- 					hereChar = closeDelimiter
- 						ifTrue: [level := level - 1"leaving nest"]
- 						ifFalse: [hereChar = openDelimiter 
- 									ifTrue: [level := level + 1"entering deeper nest"]]]].
- 
- 	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: Editor>>selectWord: (in category 'nonediting/nontyping keys') -----
+ selectWord: aKeyboardEvent
+ 
+ 	self closeTypeIn.
- selectWord: characterStream
- 	sensor keyboard.
- 	self closeTypeIn: characterStream.
  	self selectWord.
  	^ true!

Item was added:
+ ----- Method: Editor>>selectWordLeftDelimiters:rightDelimiters: (in category 'new selection') -----
+ selectWordLeftDelimiters: leftDelimiters rightDelimiters: rightDelimiters
+ 	"Select delimited text or word--the result of double-clicking."
+ 
+ 	| openDelimiter closeDelimiter direction match level
+ 	string here hereChar start stop |
+ 	string := self string.
+ 	here := self pointIndex min: string size max: 2.
+ 	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]
+ 		ifFalse: [
+ 			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]
+ 				ifFalse: [
+ 					"no delimiters -- select a token"
+ 					direction := -1]].
+ 	level := 1.
+ 	[level > 0 and: [direction > 0
+ 			ifTrue: [here < string size]
+ 			ifFalse: [here > 1]]]
+ 		whileTrue: [
+ 			hereChar := string at: (here := here + direction).
+ 			match = 0
+ 				ifTrue: ["token scan goes left, then right"
+ 					hereChar tokenish
+ 						ifTrue: [here = 1
+ 								ifTrue: [
+ 									start := 1.
+ 									"go right if hit string start"
+ 									direction := 1]]
+ 						ifFalse: [
+ 							direction < 0
+ 								ifTrue: [
+ 									start := here + 1.
+ 									"go right if hit non-token"
+ 									direction := 1]
+ 								ifFalse: [level := 0]]]
+ 				ifFalse: ["bracket match just counts nesting level"
+ 					hereChar = closeDelimiter
+ 						ifTrue: [level := level - 1"leaving nest"]
+ 						ifFalse: [hereChar = openDelimiter 
+ 									ifTrue: [level := level + 1"entering deeper nest"]]]].
+ 
+ 	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 removed:
- ----- Method: Editor>>sensor: (in category 'private') -----
- sensor: aSensor
- 	"Set the receiver's sensor to aSensor."
- 
- 	sensor := aSensor!

Item was removed:
- ----- Method: Editor>>unselect (in category 'accessing-selection') -----
- unselect
- 	self markIndex: self pointIndex!

Item was added:
+ ----- Method: Editor>>wordSelectAndEmptyCheck: (in category 'menu messages') -----
+ wordSelectAndEmptyCheck: returnBlock
+ 	"Ensure selecting the entire current word; if after that's done the selection is still empty, then evaluate the returnBlock, which will typically consist of '[^ self]' in the caller -- check senders of this method to understand this."
+ 
+ 	self selectWord.  "Select exactly a whole word"
+ 	self hasSelection ifFalse: [morph flash.  ^ returnBlock value]!

Item was changed:
  ----- Method: SmalltalkEditor>>blinkPrevParen: (in category 'parenblinking') -----
+ blinkPrevParen: aKeyboardEvent
- blinkPrevParen: aCharacter
  	"Same as super, but tries to follow the Smalltalk syntax."
  
  	| openDelimiter closeDelimiter level string here inside |
  	string := paragraph text string.
  	here := pointBlock stringIndex.
+ 	openDelimiter := aKeyboardEvent keyCharacter.
- 	openDelimiter := aCharacter.
  	closeDelimiter := '([{' at: (')]}' indexOf: openDelimiter).
  	level := 1.
  	inside := nil. "Tricky."
  	(here > 1 and: [ (string at: here - 1) = $$ ]) ifTrue: [ ^self ]. "Just a character literal."
  	[ level > 0 and: [ here > 1 ] ] whileTrue: [
  		| hereChar |
  		hereChar := string at: (here := here - 1).
  		inside "Are we inside a comment or string literal?"
  			ifNotNil: [ "Yes."
  				hereChar = inside ifTrue: [
  					(here > 1 and: [ (string at: here - 1) ~= inside ])
  						ifTrue: [ inside := nil ]
  						ifFalse: [ here := here - 1 ] ] ]
  			ifNil: [
  				(here > 1 and: [ (string at: here - 1) = $$ ]) "Just a character literal."
  					ifTrue: [ here := here - 1 ]
  					ifFalse: [
  						hereChar
  							caseOf: {
  								[ closeDelimiter ] -> [
  									(level := level - 1) = 0 ifTrue: [
  										^self blinkParenAt: here ] ].
  								[ openDelimiter ] -> [  level := level + 1 ].
  								[ $" ] -> [ inside := $" ].
  								[ $' ] -> [ inside := $' ] }
  							otherwise: [] ] ] ]!

Item was changed:
  ----- Method: SmalltalkEditor>>handleEmphasisExtra:with: (in category 'editing keys') -----
+ handleEmphasisExtra: index with: aKeyboardEvent
- 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.
  		] ifNotEmpty: [
  			self replaceSelectionWith: (thisSel asText addAttribute: attribute).
  		]
  	].
  	^true!

Item was changed:
  ----- Method: SmalltalkEditor>>typeMethodArgument: (in category 'private') -----
+ typeMethodArgument: aKeyboardEvent 
- typeMethodArgument: characterStream 
  	"Replace the current text selection with the name of the method argument represented by the keyCode."
  	| keyCode |
  	keyCode := ('1234' 
+ 		indexOf: aKeyboardEvent keyCharacter
- 		indexOf: sensor keyboard 
  		ifAbsent: [1]).
+ 	self  addString: (self methodArgument: keyCode).
- 	characterStream nextPutAll: (self methodArgument: keyCode).
  	^ false!

Item was changed:
  Editor subclass: #TextEditor
+ 	instanceVariableNames: 'model paragraph markBlock pointBlock beginTypeInIndex emphasisHere lastParenLocation otherInterval oldInterval'
- 	instanceVariableNames: 'model paragraph pointBlock markBlock beginTypeInBlock emphasisHere otherInterval lastParenLocation oldInterval'
  	classVariableNames: 'AutoEnclose AutoIndent ChangeText FindText UndoInterval UndoMessage UndoParagraph UndoSelection Undone'
  	poolDictionaries: ''
  	category: 'Morphic-Text Support'!
  TextEditor class
  	instanceVariableNames: 'cmdActions shiftCmdActions yellowButtonMenu shiftedYellowButtonMenu'!
  
  !TextEditor commentStamp: '<historical>' prior: 0!
  See comment in Editor.
  
  My instances edit Text, this is, they support multiple lines and TextAttributes.
  They have no specific facilities for editing Smalltalk code. Those are found in SmalltalkEditor.!
  TextEditor class
  	instanceVariableNames: 'cmdActions shiftCmdActions yellowButtonMenu shiftedYellowButtonMenu'!

Item was added:
+ ----- Method: TextEditor>>addString: (in category 'typing support') -----
+ addString: aString
+ 	"Think of a better name"
+ 
+ 	self zapSelectionWith: aString!

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 := self 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 selectInvisiblyFrom: where to: where + FindText size - 1.	"Repeat it here. Senders beware: only one of these should last"
+ 
+ 	ChangeText ~~ FindText ifTrue: [ self zapSelectionWith: ChangeText ].
- 	self deselect; selectInvisiblyFrom: where to: where + FindText size - 1.
- 	ChangeText ~~ FindText ifTrue: [self zapSelectionWith: ChangeText].
  	indices nextPut: where.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>againOrSame: (in category 'private') -----
  againOrSame: useOldKeys
  	"Subroutine of search: and again.  If useOldKeys, use same FindText and ChangeText as before.
  	 1/26/96 sw: real worked moved to againOrSame:many:"
  
+ 	self againOrSame: useOldKeys many: false.
- 	self againOrSame: useOldKeys many: sensor leftShiftDown.
  
  	(morph respondsTo: #editView) 
  		ifTrue: [morph editView selectionInterval: self selectionInterval]!

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"
  
  	"If new keys are to be picked..."
+ 	useOldKeys ifFalse: [ "Choose as FindText..."
+ 		FindText := UndoSelection.  "... the last thing replaced."
- 	useOldKeys ifFalse: "Choose as FindText..."
- 		[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"
- 		paragraph == UndoParagraph ifTrue: "... else set it now as follows."
- 			[UndoInterval ~= home ifTrue: [self selectInterval: UndoInterval]. "blink"
  			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)
+ 		ifTrue: [ "just inserted at a caret"
+ 			home := self selectionInterval.
- 		ifTrue: "just inserted at a caret"
- 			[home := self selectionInterval.
  			self replaceSelectionWith: self nullText.  "delete search key..."
  			FindText := ChangeText] "... and search for it, without replacing"
+ 		ifFalse: [ "Show where the search will start"
+ 			home last = self selectionInterval last ifFalse: [
+ 				self selectInterval: home]].
- 		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"
  	[(self againOnce: indices) & many] whileTrue. "<-- this does the work"
+ 	"Last find was also stored in markBlock / pointBlock"
+ 	indices isEmpty ifTrue: [  "none found"
+ 		self flash.
- 	indices isEmpty ifTrue:  "none found"
- 		[self flash.
  		wasTypedKey ifFalse: [^self]].
  
+ 	(many | wasTypedKey) ifFalse: [ "after undo, select this replacement"
+ 		home := self startIndex to:
- 	(many | wasTypedKey) ifFalse: "after undo, select this replacement"
- 		[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: TextEditor>>align (in category 'menu messages') -----
  align
  	"Align text according to the next greater alignment value,
  	cycling among leftFlush, rightFlush, center, and justified."
  	self changeAlignment.
+ 	self recomputeSelection!
- 	self recomputeInterval!

Item was changed:
  ----- Method: TextEditor>>align: (in category 'editing keys') -----
+ align: aKeyboardEvent
- align: characterStream 
  	"Triggered by Cmd-u;  cycle through alignment alternatives.  8/11/96 sw"
  
- 	sensor keyboard.		"flush character"
  	self align.
  	^ true!

Item was added:
+ ----- Method: TextEditor>>applyAttribute: (in category 'private') -----
+ applyAttribute: aTextAttribute
+ 	"The user selected aTextAttribute via shortcut, menu or other means.
+ 	If there is a selection, apply the attribute to the selection.
+ 	In any case use the attribute for the user input (emphasisHere)"
+ 	| interval |
+ 
+ 	emphasisHere := Text addAttribute: aTextAttribute toArray: emphasisHere.
+ 	
+ 	interval := self selectionInterval.
+ 	(interval isEmpty and: [ aTextAttribute isParagraphAttribute not ])
+ 		ifTrue: [ ^self ].
+ 	
+ 	self text addAttribute: aTextAttribute from: interval first to: interval last.
+ 	paragraph recomposeFrom: interval first to: interval last delta: 0.
+ 	self recomputeSelection.	"Needed so visible selection is updated to reflect new visual extent of selection"
+ 	morph changed!

Item was changed:
  ----- Method: TextEditor>>argAdvance: (in category 'typing/selecting keys') -----
+ argAdvance: aKeyboardEvent
- 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 |
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	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>>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;
+ 	(3) preexisting characters that
- 	 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 := beginTypeInIndex
+ 		ifNil: [self openTypeIn. UndoSelection := self nullText. self stopIndex].
+ 	markBlock := paragraph characterBlockForIndex: startIndex.
- 	saveLimit := beginTypeInBlock
- 		ifNil: [self openTypeIn. UndoSelection := self nullText. self stopIndex]
- 		ifNotNil: [self startOfTyping].
- 	self markIndex: startIndex.
  	startIndex < saveLimit ifTrue: [
+ 		newBackovers := beginTypeInIndex - startIndex.
+ 		beginTypeInIndex := self startIndex.
- 		newBackovers := self startOfTyping - startIndex.
- 		beginTypeInBlock := self startIndex.
  		UndoSelection replaceFrom: 1 to: 0 with:
+ 			(self text copyFrom: startIndex to: saveLimit - 1).
- 			(paragraph text copyFrom: startIndex to: saveLimit - 1).
  		UndoMessage arguments size > 0 ifTrue: [
+ 			UndoMessage argument: (UndoMessage argument ifNil: [1]) + newBackovers]].
- 			UndoMessage argument: (UndoMessage argument ifNil: [1]) + newBackovers] ].
  	self zapSelectionWith: self nullText.
+ 	markBlock := pointBlock!
- 	self unselect!

Item was added:
+ ----- Method: TextEditor>>beginningOfLine: (in category 'private') -----
+ beginningOfLine: position
+ 	"Redefined in subclasses using Paragraph support"
+ 	^ (paragraph lines at:(paragraph lineIndexFor: position)) first!

Item was changed:
  ----- Method: TextEditor>>blinkParen (in category 'parenblinking') -----
  blinkParen
+ 	"Used if Shout"
+ 	lastParenLocation ifNotNil: [
+ 		self text string size >= lastParenLocation ifTrue: [
- 	"Highlight the last parenthesis in the text"
- 	lastParenLocation ifNotNil:
- 		[self text string size >= lastParenLocation ifTrue: [
  			self text
  				addAttribute: TextEmphasis bold
  				from: lastParenLocation
+ 				to: lastParenLocation]]!
- 				to: lastParenLocation]]
- !

Item was removed:
- ----- Method: TextEditor>>blinkPrevParen (in category 'parenblinking') -----
- blinkPrevParen
- 	
- 	self deprecated: 'Use #blinkPrevParen:'.
- 	self blinkPrevParen: sensor keyboardPeek!

Item was changed:
  ----- Method: TextEditor>>blinkPrevParen: (in category 'parenblinking') -----
+ blinkPrevParen: aKeyboardEvent
+ 	"Used if not Shout"
- blinkPrevParen: aCharacter
- 
  	| openDelimiter closeDelimiter level string here hereChar |
+ 	string := paragraph string.
- 	string := paragraph text string.
  	here := pointBlock stringIndex.
+ 	openDelimiter := aKeyboardEvent keyCharacter.
- 	openDelimiter := aCharacter.
  	closeDelimiter := '([{' at: (')]}' indexOf: openDelimiter).
  	level := 1.
  	[level > 0 and: [here > 1]]
  		whileTrue:
  			[hereChar := string at: (here := here - 1).
  			hereChar = closeDelimiter
  				ifTrue:
  					[level := level - 1.
  					level = 0
  						ifTrue: [^ self blinkParenAt: here]]
  				ifFalse:
  					[hereChar = openDelimiter
  						ifTrue: [level := level + 1]]]!

Item was changed:
  ----- Method: TextEditor>>browseIt (in category 'menu messages') -----
  browseIt
  	"Launch a browser for the current selection, if appropriate"
  
  	| aSymbol anEntry brow |
  
  	Preferences alternativeBrowseIt ifTrue: [^ self browseClassFromIt].
  
  	self lineSelectAndEmptyCheck: [^ self].
  	(aSymbol := self selectedSymbol) isNil ifTrue: [^ morph flash].
  
  	aSymbol first isUppercase
  		ifTrue:
  			[anEntry := (Smalltalk
  				at: aSymbol
  				ifAbsent:
  					[ self systemNavigation browseAllImplementorsOf: aSymbol.
  					^ nil]).
+ 			anEntry ifNil: [^ morph flash].
- 			anEntry isNil ifTrue: [^ morph flash].
  			(anEntry isKindOf: Class)
  				ifFalse:	[anEntry := anEntry class].
  			brow := Preferences browseToolClass new.
  			brow setClass: anEntry selector: nil.
  			brow class
  				openBrowserView: (brow openEditString: nil)
  				label: 'System Browser']
  		ifFalse:
  			[self systemNavigation browseAllImplementorsOf: aSymbol]!

Item was changed:
  ----- Method: TextEditor>>browseIt: (in category 'editing keys') -----
+ browseIt: aKeyboardEvent
- browseIt: characterStream 
  	"Triggered by Cmd-B; browse the thing represented by the current selection, if plausible.  1/18/96 sw"
  
- 	sensor keyboard.		"flush character"
  	self browseIt.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>browseItHere: (in category 'editing keys') -----
+ browseItHere: aKeyboardEvent 
- browseItHere: characterStream 
  	"Triggered by Cmd-shift-B; browse the thing represented by the current selection, if plausible, in the receiver's own window.  3/1/96 sw"
  
- 	sensor keyboard.		"flush character"
  	self browseItHere.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>cancel: (in category 'editing keys') -----
+ cancel: aKeyboardEvent
+ 	"Cancel unsubmitted changes."
- cancel: characterStream 
- 	"Cancel unsubmitted changes.  Flushes typeahead.  1/12/96 sw"
  
- 	sensor keyboard.
  	self cancel.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>changeEmphasis: (in category 'editing keys') -----
+ changeEmphasis: aKeyboardEvent 
- 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: aKeyboardEvent keyCharacter ifAbsent: [1]) - 1.
- 	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: aKeyboardEvent]	"handle an extra"]].
- 						ifFalse:[^self handleEmphasisExtra: index with: characterStream]	"handle an extra"]].
  	(keyCode between: 7 and: 11) 
  		ifTrue: [
+ 			aKeyboardEvent shiftPressed 
- 			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 ]
  			ifFalse: [
  				self replaceSelectionWith: (thisSel asText addAttribute: attribute) ]].
  	^true!

Item was changed:
  ----- Method: TextEditor>>changeEmphasisOrAlignment (in category 'attributes') -----
  changeEmphasisOrAlignment
  	| aList reply  code align menuList startIndex |
  	startIndex := self startIndex.
  	aList := #(normal bold italic narrow underlined struckOut leftFlush centered rightFlush justified).	
  	align := paragraph text alignmentAt: startIndex 
  		ifAbsent: [ paragraph textStyle alignment ].
  	code := paragraph text emphasisAt: startIndex.
  	menuList := WriteStream on: Array new.
  	menuList nextPut: (code isZero ifTrue:['<on>'] ifFalse:['<off>']), 'normal' translated.
  	menuList nextPutAll: (#(bold italic underlined struckOut) collect:[:emph|
  		(code anyMask: (TextEmphasis perform: emph) emphasisCode)
  			ifTrue: [ '<on>', emph asString translated ]
  			ifFalse: [ '<off>',emph asString translated ]]).
  	((paragraph text attributesAt: startIndex)
  		anySatisfy: [ :attr | attr isKern and: [attr kern < 0 ]]) 
  			ifTrue: [ menuList nextPut:'<on>', 'narrow' translated ]
  			ifFalse: [ menuList nextPut:'<off>', 'narrow' translated ].
  	menuList nextPutAll: (#(leftFlush centered rightFlush justified) collectWithIndex: [ :type :i |
  		align = (i-1)
  			ifTrue: [ '<on>',type asString translated ]
  			ifFalse: [ '<off>',type asString translated ]]).
  	aList := #(normal bold italic underlined struckOut narrow leftFlush centered rightFlush justified).
  	reply := UIManager default chooseFrom: menuList contents values: aList lines: #(1 6).
  	reply notNil ifTrue: [
  		(#(leftFlush centered rightFlush justified) includes: reply)
  			ifTrue: [
  				self setAlignment: reply.
  				paragraph composeAll.
+ 				self recomputeSelection]
- 				self recomputeInterval]
  			ifFalse: [
  				self setEmphasis: reply.
  				paragraph composeAll.
  				self recomputeSelection]].
  	^ true!

Item was changed:
  ----- Method: TextEditor>>changeLfToCr: (in category 'editing keys') -----
+ changeLfToCr: aKeyboardEvent 
- 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 withSqueakLineEndings. 
  	self replaceSelectionWith: (Text fromString: fixed).
  	^ true!

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

Item was changed:
  ----- Method: TextEditor>>changeStyle: (in category 'typing/selecting keys') -----
+ changeStyle: aKeyboardEvent 
- changeStyle: characterStream 
  	"Put up the style-change menu"
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self changeStyle.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>clearParens (in category 'parenblinking') -----
  clearParens
+ 	lastParenLocation ifNotNil: [
+ 		self text string size >= lastParenLocation ifTrue: [
- 	"Clear parenthesis highlight"
- 	lastParenLocation ifNotNil:
- 		[self text string size >= lastParenLocation ifTrue: [
  			self text
  				removeAttribute: TextEmphasis bold
  				from: lastParenLocation
  				to: lastParenLocation]].
+ 	lastParenLocation := nil!
- 	lastParenLocation := nil.!

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.
+ 	 Undoer & Redoer: undoAndReselect:redoAndReselect:."
- 	 Typing commands can call 'closeTypeIn: aCharacterStream' instead of this to
- 	 save typeahead.  Undoer & Redoer: undoAndReselect:redoAndReselect:."
  
  	| begin stop |
+ 	beginTypeInIndex ifNotNil: [
+ 		(UndoMessage sends: #noUndoer) ifTrue: [ "should always be true, but just in case..."
+ 			begin := beginTypeInIndex.
- 	beginTypeInBlock == nil ifFalse: [
- 		(UndoMessage sends: #noUndoer) ifTrue: "should always be true, but just in case..."
- 			[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].
+ 		beginTypeInIndex := nil]!
- 		beginTypeInBlock := nil]!

Item was changed:
  ----- Method: TextEditor>>compareToClipboard: (in category 'editing keys') -----
+ compareToClipboard: aKeyboardEvent
+ 	"Compare the receiver to the text on the clipboard."
- compareToClipboard: characterStream 
- 	"Compare the receiver to the text on the clipboard.  Flushes typeahead.  5/1/96 sw"
  
- 	sensor keyboard.	
  	self compareToClipboard.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>copyHiddenInfo (in category 'editing keys') -----
  copyHiddenInfo
  	"In TextLinks, TextDoits, TextColor, and TextURLs, there is hidden
  info.  Copy that to the clipboard.  You can paste it and see what it is.
  Usually enclosed in <>."
  
+ 	^ self clipboardTextPut: self hiddenInfo!
- 	^ self clipboardTextPut: self hiddenInfo asText!

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."
+ 	| userSelection delta loc wasShowing |
+ 	aString = '#insert period' ifTrue: [
+ 		loc := start.
+ 		[(loc := loc-1)>0 and: [(paragraph string at: loc) isSeparator]]
- 	| 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].
  		^ self correctFrom: loc+1 to: loc with: '.'].
  	(wasShowing := selectionShowing) ifTrue: [ self reverseSelection ].
  	userSelection := self selectionInterval.
  
  	self selectInvisiblyFrom: start to: stop.
+ 	self replaceSelectionWith: aString.
- 	self replaceSelectionWith: aString asText.
  
  	delta := aString size - (stop - start + 1).
+ 	self
+ 		selectInvisiblyFrom: userSelection first + (userSelection first > start ifFalse: [ 0 ] ifTrue: [ delta ])
- 	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: TextEditor>>crWithIndent: (in category 'typing/selecting keys') -----
+ crWithIndent: aKeyboardEvent 
- 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."
+ 	self addString: (String streamContents: [:characterStream | characterStream crtab: self tabCount]).  "Now inject CR with tabCount tabs"
- 	sensor keyboard.		"flush character"
- 	characterStream crtab: self tabCount.  "Now inject CR with tabCount tabs"
  	^ false!

Item was changed:
  ----- Method: TextEditor>>cursorDown: (in category 'nonediting/nontyping keys') -----
+ cursorDown: aKeyboardEvent 
- cursorDown: characterStream 
  
  	"Private - Move cursor from position in current line to same position in
  	next line. If next line too short, put at end. If shift key down,
  	select."
+ 	self closeTypeIn.
- 	self closeTypeIn: characterStream.
  	self 
  		moveCursor:[:position | self
  				sameColumn: position
  				newLine:[:line | line + 1]
  				forward: true]
  		forward: true
+ 		event: aKeyboardEvent
  		specialBlock:[:dummy | dummy].
  	^true!

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

Item was changed:
  ----- Method: TextEditor>>cursorHome: (in category 'nonediting/nontyping keys') -----
+ cursorHome: aKeyboardEvent 
- 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.
  	self
  		moveCursor: [ :position | Preferences wordStyleCursorMovement
  				ifTrue:[
  					(paragraph lines at:(paragraph lineIndexOfCharacterIndex: position)) first]
  				ifFalse:[
  					(string
  						lastIndexOfAnyOf: CharacterSet crlf
  						startingAt: position - 1
  						ifAbsent:[0]) + 1]]
  		forward: false
+ 		event: aKeyboardEvent
  		specialBlock: [:dummy | 1].
  	^true!

Item was removed:
- ----- 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 openers closers result |
- 	((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])
- 		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].
- 
- 	openers := '([{'.  closers := ')]}'.
- 
- 	result := self normalCharacter: typeAheadStream.
- 	(closers includes: char) ifTrue: [self blinkPrevParen: char].
- 
- 	(self class autoEnclose and: [ openers includes: char ])
- 		ifTrue: 
- 			[ typeAheadStream nextPut: (closers at: (openers indexOf: char)).
- 			self insertTypeAhead: typeAheadStream.
- 			self moveCursor: [ : position | position-1 ] forward: false specialBlock: [ : pos | "no special behavior" ] select: false ].
- 
- 	^ result!

Item was changed:
  ----- Method: TextEditor>>dispatchOnEnterWith: (in category 'typing support') -----
+ dispatchOnEnterWith: aKeyboardEvent
- dispatchOnEnterWith: typeAheadStream
  	"Enter key hit.  Treat is as an 'accept', viz a synonym for cmd-s.  If cmd key is down, treat is as a synonym for print-it. "
  
+ 	aKeyboardEvent commandKeyPressed
- 	sensor keyboard.  "consume enter key"
- 	sensor commandKeyPressed
  		ifTrue:
  			[self printIt.]
  		ifFalse: 
+ 			[self closeTypeIn.
- 			[self closeTypeIn: typeAheadStream.
  			self accept].
  	^ true!

Item was added:
+ ----- Method: TextEditor>>dispatchOnKeyboardEvent: (in category 'typing support') -----
+ dispatchOnKeyboardEvent: aKeyboardEvent
+ 	"Carry out the action associated with this character, if any.
+ 	Type-ahead is passed so some routines can flush or use it."
+ 
+ 	| honorCommandKeys openers closers result |
+ 	(aKeyboardEvent keyCharacter == Character cr and: [ morph acceptOnCR ])
+ 		ifTrue: [ 
+ 			self closeTypeIn.
+ 			^ true ].
+ 	self clearParens.
+ 	aKeyboardEvent keyValue = 13
+ 		ifTrue: [ 
+ 			aKeyboardEvent controlKeyPressed
+ 				ifTrue: [ ^ self normalCharacter: aKeyboardEvent ].
+ 			aKeyboardEvent shiftPressed
+ 				ifTrue: [ ^ self lf: aKeyboardEvent ].
+ 			aKeyboardEvent commandKeyPressed
+ 				ifTrue: [ ^ self crlf: aKeyboardEvent ].
+ 			^ self crWithIndent: aKeyboardEvent ].
+ 	((honorCommandKeys := Preferences cmdKeysInText) and: [ aKeyboardEvent keyCharacter = Character enter ])
+ 		ifTrue: [ ^ self dispatchOnEnterWith: aKeyboardEvent ].	"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: aKeyboardEvent keyValue) and: [ aKeyboardEvent keyValue < 27 ])
+ 		ifTrue: [ 
+ 			^ aKeyboardEvent controlKeyPressed
+ 				ifTrue: [ self perform: (self class shiftCmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent ]
+ 				ifFalse: [ self perform: (self class cmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent ] ].	"backspace, and escape keys (ascii 8 and 27) are command keys"
+ 	((honorCommandKeys and: [ aKeyboardEvent commandKeyPressed ])
+ 		or: [ self class specialShiftCmdKeys includes: aKeyboardEvent keyValue ])
+ 		ifTrue: [ 
+ 			^ aKeyboardEvent shiftPressed
+ 				ifTrue: [ self perform: (self class shiftCmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent ]
+ 				ifFalse: [ self perform: (self class cmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent ] ].	"the control key can be used to invoke shift-cmd shortcuts"
+ 	(honorCommandKeys and: [ aKeyboardEvent controlKeyPressed ])
+ 		ifTrue: [ ^ self perform: (self class shiftCmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent ].
+ 	openers := '([{'.
+ 	closers := ')]}'.
+ 	result := self normalCharacter: aKeyboardEvent.
+ 	(closers includes: aKeyboardEvent keyCharacter)
+ 		ifTrue: [ self blinkPrevParen: aKeyboardEvent ].
+ 	(self class autoEnclose and: [ openers includes: aKeyboardEvent keyCharacter ])
+ 		ifTrue: [ 
+ 			self addString: (closers at: (openers indexOf: aKeyboardEvent keyCharacter)) asString.
+ 			self moveCursor: [ :position | position - 1 ] forward: false select: false	"no special behavior" ].
+ 	^ result!

Item was changed:
  ----- Method: TextEditor>>displayIfFalse: (in category 'typing/selecting keys') -----
+ displayIfFalse: aKeyboardEvent
- displayIfFalse: characterStream 
  	"Replace the current text selection with the text 'ifFalse:'--initiated by 
  	ctrl-f."
  
+ 	self addString: 'ifFalse:'.
- 	sensor keyboard.		"flush character"
- 	characterStream nextPutAll: 'ifFalse:'.
  	^false!

Item was changed:
  ----- Method: TextEditor>>displayIfTrue: (in category 'typing/selecting keys') -----
+ displayIfTrue: aKeyboardEvent
- displayIfTrue: characterStream 
  	"Replace the current text selection with the text 'ifTrue:'--initiated by 
  	ctrl-t."
  
+ 	self addString: 'ifTrue:'.
- 	sensor keyboard.		"flush character"
- 	characterStream nextPutAll: 'ifTrue:'.
  	^false!

Item was changed:
  ----- Method: TextEditor>>doAgainMany: (in category 'typing/selecting keys') -----
+ doAgainMany: aKeyboardEvent 
- doAgainMany: characterStream 
  	"Do the previous thing again repeatedly. 1/26/96 sw"
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self againOrSame: (UndoMessage sends: #undoAgain:andReselect:typedKey:) many: true.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>doAgainOnce: (in category 'typing/selecting keys') -----
+ doAgainOnce: aKeyboardEvent 
- doAgainOnce: characterStream 
  	"Do the previous thing again once. 1/26/96 sw"
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self again.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>doIt: (in category 'editing keys') -----
+ doIt: aKeyboardEvent
- doIt: characterStream 
  	"Called when user hits cmd-d.  Select the current line, if relevant, then evaluate and execute.  2/1/96 sw.
  	2/29/96 sw: don't call selectLine; it's done by doIt now"
  
- 	sensor keyboard.	
  	self doIt.
  	^ true!

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

Item was changed:
  ----- Method: TextEditor>>duplicate: (in category 'editing keys') -----
+ duplicate: aKeyboardEvent
- duplicate: characterStream
  	"Paste the current selection over the prior selection, if it is non-overlapping and
  	 legal.  Flushes typeahead.  Undoer & Redoer: undoAndReselect."
  
- 	sensor keyboard.
  	self closeTypeIn.
  	(self hasSelection and: [self isDisjointFrom: otherInterval])
  		ifTrue: "Something to duplicate"
  			[self replace: otherInterval with: self selection and:
  				[self selectAt: self pointIndex]]
  		ifFalse:
  			[morph flash].
  	^true!

Item was changed:
  ----- Method: TextEditor>>enclose: (in category 'editing keys') -----
+ enclose: aKeyboardEvent
+ 	"Insert or remove bracket characters around the current selection."
- enclose: characterStream
- 	"Insert or remove bracket characters around the current selection.
- 	 Flushes typeahead."
  
+ 	| left right startIndex stopIndex oldSelection which t |
- 	| char left right startIndex stopIndex oldSelection which text |
- 	char := sensor keyboard.
  	self closeTypeIn.
  	startIndex := self startIndex.
  	stopIndex := self stopIndex.
  	oldSelection := self selection.
+ 	which := '([<{"''' indexOf: aKeyboardEvent keyCharacter ifAbsent: [ ^true ].
+ 	left := '([<{"''' at: which.
+ 	right := ')]>}"''' at: which.
+ 	t := self text.
+ 	((startIndex > 1 and: [stopIndex <= t size])
+ 			and: [ (t at: startIndex-1) = left and: [(t at: stopIndex) = right]])
- 	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 added:
+ ----- Method: TextEditor>>endOfLine: (in category 'private') -----
+ endOfLine: position
+ 	"Redefined in subclasses using Paragraph support"
+ 	| targetLine |
+ 	targetLine := paragraph lines at: (paragraph lineIndexFor: position).
+ 	^ targetLine = paragraph lastLine
+ 		ifFalse: [ targetLine last ]
+ 		ifTrue: [ targetLine last + 1 ]!

Item was changed:
  ----- Method: TextEditor>>exchange: (in category 'editing keys') -----
+ exchange: eKeyboardEvent
- exchange: characterStream
  	"Exchange the current and prior selections.  Keeps typeahead."
  
+ 	self closeTypeIn.
- 	sensor keyboard.	 "Flush character"
- 	self closeTypeIn: characterStream.
  	self exchange.
  	^true!

Item was changed:
  ----- Method: TextEditor>>explainDelimitor: (in category 'explain') -----
  explainDelimitor: string
  	"Is string enclosed in delimitors?"
  
  	| str |
  	(string at: 1) isLetter ifTrue: [^nil].  "only special chars"
  	(string first = string last) ifTrue:
  			[^ self explainChar: (String with: string first)]
  		ifFalse:
  			[(string first = $( and: [string last = $)]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = $[ and: [string last = $]]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = ${ and: [string last = $}]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = $< and: [string last = $>]) ifTrue:
  				[^ self explainChar: (String with: string first)].
  			(string first = $# and: [string last = $)]) ifTrue:
  				[^'"An instance of class Array.  The Numbers, Characters, 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) ifNotNil: [
+ 					^'"An argument to this block will be bound to the temporary variable ',
- 				(self explainTemp: str) ~~ nil ifTrue:
- 					[^'"An argument to this block will be bound to the temporary variable ',
  						str, '."']]].
  	^ nil!

Item was changed:
  ----- Method: TextEditor>>exploreIt: (in category 'editing keys') -----
+ exploreIt: aKeyboardEvent
- exploreIt: characterStream 
  	"Explore the selection -- invoked via cmd-shift-I.  If there is no current selection, use the current line."
  
- 	sensor keyboard.		"flush character"
  	self exploreIt.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>fileItIn: (in category 'editing keys') -----
+ fileItIn: aKeyboardEvent
- fileItIn: characterStream 
  	"File in the selection; invoked via a keyboard shortcut, -- for now, cmd-shift-G."
  
- 	sensor keyboard.		"flush character"
  	self fileItIn.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>find: (in category 'typing/selecting keys') -----
+ find: aKeyboardEvent
- find: characterStream
  	"Prompt the user for what to find, then find it, searching from the current selection onward.  1/24/96 sw"
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self find.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>findAgain: (in category 'typing/selecting keys') -----
+ findAgain: aKeyboardEvent 
- findAgain: characterStream 
  	"Find the desired text again.  1/24/96 sw"
  
+ 	self closeTypeIn.
+ 	self againOrSame: true many: aKeyboardEvent shiftPressed.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
- 	self findAgain.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>forwardDelete: (in category 'typing/selecting keys') -----
+ forwardDelete: aKeyboardEvent
- 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 text size ifTrue: [
- 	startIndex > paragraph text size ifTrue:
- 		[sensor keyboard.
  		^ false].
+ 	self hasSelection ifTrue: [
+ 		"there was a selection"
- 	self hasSelection ifTrue:
- 		["there was a selection"
- 		sensor keyboard.
  		self zapSelectionWith: self nullText.
  		^ false].
  	"Null selection - do the delete forward"
+ 	beginTypeInIndex ifNil: [	"no previous typing.  openTypeIn"
+ 		self openTypeIn. UndoSelection := self nullText].
+ 	uinterval := UndoInterval copy.
+ 	upara := UndoParagraph copy.
- 	beginTypeInBlock == nil	"no previous typing.  openTypeIn"
- 		ifTrue: [self openTypeIn. UndoSelection := self nullText].
- 	uinterval := UndoInterval deepCopy.
- 	upara := UndoParagraph deepCopy.
  	stopIndex := startIndex.
+ 	(aKeyboardEvent keyValue = 127 and: [ aKeyboardEvent shiftPressed ])
+ 		ifTrue: [stopIndex := (self nextWordStart: stopIndex) - 1].
- 	(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.
  	UndoMessage selector == #noUndoer ifTrue: [
  		(UndoSelection isText) ifTrue: [
  			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]].
- 			UndoParagraph text replaceFrom: ind to: ind with:
- self nullText]].
  	^false!

Item was changed:
  ----- Method: TextEditor>>handleEmphasisExtra:with: (in category 'editing keys') -----
+ handleEmphasisExtra: index with: aKeyboardEvent
- handleEmphasisExtra: index with: characterStream
  	"Handle an emphasis extra choice"
  	^true!

Item was changed:
  ----- Method: TextEditor>>hasCaret (in category 'accessing-selection') -----
  hasCaret
+ 	^ markBlock = pointBlock!
- 	^self markBlock = self pointBlock!

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 := self 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>>implementorsOfIt: (in category 'editing keys') -----
+ implementorsOfIt: aKeyboardEvent
- implementorsOfIt: characterStream 
  	"Triggered by Cmd-m; browse implementors of the selector represented by the current selection, if plausible. 2/1/96 sw"
  
- 	sensor keyboard.		"flush character"
  	self implementorsOfIt.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>inOutdent:delta: (in category 'editing keys') -----
+ inOutdent: aKeyboardEvent delta: delta
- inOutdent: characterStream delta: delta
  	"Add/remove a tab at the front of every line occupied by the selection. Flushes typeahead.  Derived from work by Larry Tesler back in December 1985.  Now triggered by Cmd-L and Cmd-R.  2/29/96 sw"
  
  	| realStart realStop lines startLine stopLine start stop adjustStart indentation numLines oldString newString newSize |
- 	sensor keyboard.  "Flush typeahead"
  
  	"Operate on entire lines, but remember the real selection for re-highlighting later"
  	realStart := self startIndex.
  	realStop := self stopIndex - 1.
  
  	"Special case a caret on a line of its own, including weird case at end of paragraph"
  	(realStart > realStop and:
  				[realStart < 2 or: [(paragraph string at: realStart - 1) == Character cr or: [(paragraph string at: realStart - 1) == Character lf]]])
  		ifTrue:
  			[delta < 0
  				ifTrue:
  					[morph flash]
  				ifFalse:
  					[self replaceSelectionWith: Character tab asSymbol asText.
  					self selectAt: realStart + 1].
  			^true].
  
  	lines := paragraph lines.
  	startLine := paragraph lineIndexOfCharacterIndex: realStart.
  	"start on a real line, not a wrapped line"
  	[startLine = 1 or: [CharacterSet crlf includes: (paragraph string at: (lines at: startLine-1) last)]] whileFalse: [startLine := startLine - 1].
  	stopLine := paragraph lineIndexOfCharacterIndex: (realStart max: realStop).
  	start := (lines at: startLine) first.
  	stop := (lines at: stopLine) last.
  	
  	"Pin the start of highlighting unless the selection starts a line"
  	adjustStart := realStart > start.
  
  	"Find the indentation of the least-indented non-blank line; never outdent more"
  	indentation := (startLine to: stopLine) inject: 1000 into:
  		[:m :l |
  		m min: (paragraph indentationOfLineIndex: l ifBlank: [:tabs | 1000])].
  	indentation + delta <= 0 ifTrue: ["^false"].
  
  	numLines := stopLine + 1 - startLine.
  	oldString := paragraph string copyFrom: start to: stop.
  	newString := oldString species new: oldString size + ((numLines * delta) max: 0).
  
  	"Do the actual work"
  	newSize := 0.
  	delta > 0
  		ifTrue: [| tabs |
  			tabs := oldString species new: delta withAll: Character tab.
  			oldString lineIndicesDo: [:startL :endWithoutDelimiters :endL |
  				startL < endWithoutDelimiters ifTrue: [newString replaceFrom: 1 + newSize to: (newSize := newSize + delta) with: tabs startingAt: 1].
  				newString replaceFrom: 1 + newSize to: (newSize := 1 + newSize + endL - startL) with: oldString startingAt: startL]]
  		ifFalse: [| tab |
  			tab := Character tab.
  			oldString lineIndicesDo: [:startL :endWithoutDelimiters :endL |
  				| i |
  				i := 0.
  				[i + delta < 0 and: [ i + startL <= endWithoutDelimiters and: [(oldString at: i + startL) == tab]]] whileTrue: [i := i + 1].
  				newString replaceFrom: 1 + newSize to: (newSize := 1 + newSize + endL - (i + startL)) with: oldString startingAt: i + startL]].
  	newSize < newString size ifTrue: [newString := newString copyFrom: 1 to: newSize].
  
  	"Adjust the range that will be highlighted later"
  	adjustStart ifTrue: [realStart := (realStart + delta) max: start].
  	realStop := realStop + newSize - oldString size.
  
  	"Replace selection"
  	self selectInvisiblyFrom: start to: stop.
  	self replaceSelectionWith: newString asText.
  	self selectFrom: realStart to: realStop. 	"highlight only the original range"
  	^ true!

Item was changed:
  ----- Method: TextEditor>>indent: (in category 'editing keys') -----
+ indent: aKeyboardEvent
+ 	"Add a tab at the front of every line occupied by the selection. Invoked from keyboard via cmd-shift-R.  2/29/96 sw"
- indent: characterStream
- 	"Add a tab at the front of every line occupied by the selection. Flushes typeahead.  Invoked from keyboard via cmd-shift-R.  2/29/96 sw"
  
+ 	^ self inOutdent: aKeyboardEvent delta: 1!
- 	^ self inOutdent: characterStream delta: 1!

Item was added:
+ ----- 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.
+ 	delta > 0
+ 		ifTrue: "shift right"
+ 			[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]]
+ 		ifFalse: "shift left"
+ 			[skip := delta. "a negative number"
+ 			 [inStream atEnd] whileFalse:
+ 				[((ch := inStream next) == tab and: [skip < 0]) ifFalse:
+ 					[outStream nextPut: ch].
+ 				skip := ch == cr ifTrue: [delta] ifFalse: [skip + 1]]]!

Item was removed:
- ----- Method: TextEditor>>insertTypeAhead: (in category 'typing support') -----
- insertTypeAhead: typeAhead
- 	typeAhead position = 0 ifFalse: [
- 		self zapSelectionWith: (Text string: typeAhead contents attributes: emphasisHere).
- 		typeAhead reset.
- 		self unselect]!

Item was changed:
  ----- Method: TextEditor>>inspectIt: (in category 'editing keys') -----
+ inspectIt: aKeyboardEvent
- inspectIt: characterStream 
  	"Inspect the selection -- invoked via cmd-i.  If there is no current selection, use the current line.  1/17/96 sw
  	 2/29/96 sw: don't call selectLine; it's done by inspectIt now"
  
- 	sensor keyboard.		"flush character"
  	self inspectIt.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>keyStroke: (in category 'events') -----
  keyStroke: anEvent
+  	self deselect.
+ 	(self dispatchOnKeyboardEvent: anEvent) 
+ 		ifTrue:
+ 			[self doneTyping.
+ 			self storeSelectionInParagraph.
+ 			^self].
+ 	self openTypeIn.
+ 	self hasSelection ifTrue: [ "save highlighted characters"
+ 		UndoSelection := self selection].
+ 	markBlock := pointBlock.
+ 	self storeSelectionInParagraph!
- 	"Temporary hack to handle keyboard events thru sensor"
- 	
- 	self sensor: (KeyboardBuffer new startingEvent: anEvent).
- 	self readKeyboard!

Item was added:
+ ----- Method: TextEditor>>lineSelectAndEmptyCheck: (in category 'new selection') -----
+ lineSelectAndEmptyCheck: returnBlock
+ 	"If the current selection is an insertion point, expand it to be the entire current line; if after that's done the selection is still empty, then evaluate the returnBlock, which will typically consist of '[^ self]' in the caller -- check senders of this method to understand this."
+ 
+ 	self selectLine.  "if current selection is an insertion point, then first select the entire line in which occurs before proceeding"
+ 	self hasSelection ifFalse: [morph flash.  ^ returnBlock value]!

Item was changed:
  ----- Method: TextEditor>>makeCapitalized: (in category 'editing keys') -----
+ makeCapitalized: aKeyboardEvent
- 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"
+ 	self replaceSelectionWith: 
+ 		(self selection string collect:
+ 			[:c | prev := prev isLetter ifTrue: [c asLowercase] ifFalse: [c asUppercase]]).
- 	self replaceSelectionWith: (Text fromString:
- 			(self selection string collect:
- 				[:c | prev := prev isLetter ifTrue: [c asLowercase] ifFalse: [c asUppercase]])).
  	^ true!

Item was changed:
  ----- Method: TextEditor>>makeLowercase: (in category 'editing keys') -----
+ makeLowercase: aKeyboardEvent
- makeLowercase: characterStream 
  	"Force the current selection to lowercase.  Triggered by Cmd-X."
  
+ 	self replaceSelectionWith: (self selection string asLowercase).
- 	sensor keyboard.		"flush the triggering cmd-key character"
- 	self replaceSelectionWith: (Text fromString: (self selection string asLowercase)).
  	^ true!

Item was changed:
  ----- Method: TextEditor>>makeUppercase: (in category 'editing keys') -----
+ makeUppercase: aKeyboardEvent
- makeUppercase: characterStream 
  	"Force the current selection to uppercase.  Triggered by Cmd-Y."
  
+ 	self replaceSelectionWith: (self selection string asUppercase).
- 	sensor keyboard.		"flush the triggering cmd-key character"
- 	self replaceSelectionWith: (Text fromString: (self selection string asUppercase)).
  	^ true!

Item was removed:
- ----- Method: TextEditor>>markBlock (in category 'accessing-selection') -----
- markBlock
- 	^ markBlock!

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

Item was changed:
  ----- Method: TextEditor>>markIndex (in category 'accessing-selection') -----
  markIndex
+ 	^ markBlock stringIndex!
- 	^ self markBlock stringIndex!

Item was removed:
- ----- Method: TextEditor>>markIndex: (in category 'accessing-selection') -----
- markIndex: anIndex
- 	self markBlock: (paragraph characterBlockForIndex: anIndex)
- !

Item was added:
+ ----- Method: TextEditor>>markIndex:pointIndex: (in category 'accessing-selection') -----
+ markIndex: anIndex pointIndex: anotherIndex
+ 	"Called, for example, when selecting text with shift+arrow keys"
+ 	markBlock := paragraph characterBlockForIndex: anIndex.
+ 	pointBlock := paragraph characterBlockForIndex: anotherIndex!

Item was changed:
  ----- Method: TextEditor>>methodNamesContainingIt: (in category 'editing keys') -----
+ methodNamesContainingIt: aKeyboardEvent 
- methodNamesContainingIt: characterStream 
  	"Browse methods whose selectors containing the selection in their names"
  
- 	sensor keyboard.		"flush character"
  	self methodNamesContainingIt.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>methodStringsContainingIt: (in category 'editing keys') -----
+ methodStringsContainingIt: aKeyboardEvent 
- methodStringsContainingIt: characterStream 
  	"Invoked from cmd-E -- open a browser on all methods holding string constants containing it.  Flushes typeahead. "
  
- 	sensor keyboard.	
  	self methodStringsContainingit.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>model: (in category 'model access') -----
+ model: aModel
- 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!

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.
  
  	(paragraph clickAt: clickPoint for: model controller: self) ifTrue: [
+ 		markBlock := b.
+ 		pointBlock := b.
- 		self markBlock: b.
- 		self pointBlock: b.
  		evt hand releaseKeyboardFocus: self.
  		^ self ].
  	
  	evt shiftPressed
  		ifFalse: [
  			self closeTypeIn.
+ 			markBlock := b.
+ 			pointBlock := b ]
- 			self markBlock: b.
- 			self pointBlock: b ]
  		 ifTrue: [
  			self closeTypeIn.
  			self mouseMove: evt ].
         self storeSelectionInParagraph!

Item was changed:
  ----- Method: TextEditor>>mouseMove: (in category 'events') -----
+ mouseMove: evt
- mouseMove: evt 
  	"Change the selection in response to mouse-down drag"
  
+ 	pointBlock := paragraph characterBlockAtPoint: evt position.
- 	self pointBlock: (paragraph characterBlockAtPoint: (evt cursorPoint)).
  	self storeSelectionInParagraph!

Item was added:
+ ----- Method: TextEditor>>moveCursor:forward:event:specialBlock: (in category 'private') -----
+ moveCursor: directionBlock forward: forward event: aKeyboardEvent specialBlock: specialBlock 
+ 	super moveCursor: directionBlock forward: forward event: aKeyboardEvent specialBlock: specialBlock.
+ 	self setEmphasisHere!

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 string.
- 	str := paragraph text string.
  	[(loc between: 1 and: str size) and: [(str at: loc) isSeparator]]
  		whileTrue: [loc := loc + dir].
  	^ loc!

Item was changed:
  ----- Method: TextEditor>>offerFontMenu: (in category 'editing keys') -----
+ offerFontMenu: aKeyboardEvent 
+ 	"The user typed the command key that requests a font change; Offer the font menu.  5/27/96 sw"
- offerFontMenu: characterStream 
- 	"The user typed the command key that requests a font change; Offer the font menu.  5/27/96 sw
- 	 Keeps typeahead.  (?? should flush?)"
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self offerFontMenu.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>offerMenuFromEsc: (in category 'menu commands') -----
+ offerMenuFromEsc: aKeyboardEvent 
- offerMenuFromEsc: characterStream 
  	"The escape key was hit while the receiver has the keyboard focus; take action"
  
  	ActiveEvent shiftPressed ifFalse: [
+ 		self raiseContextMenu: aKeyboardEvent ].
- 		self raiseContextMenu: characterStream ].
  	^true!

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."
  
+ 	beginTypeInIndex ifNil: [
- 	beginTypeInBlock ifNil: [
  		UndoSelection := self nullText.
  		self undoer: #noUndoer with: 0.
+ 		beginTypeInIndex := self startIndex]!
- 		beginTypeInBlock := self startIndex]!

Item was changed:
  ----- Method: TextEditor>>outdent: (in category 'editing keys') -----
+ outdent: aKeyboardEvent
+ 	"Remove a tab from the front of every line occupied by the selection.
+ 	Invoked from keyboard via cmd-shift-L.  2/29/96 sw"
- outdent: characterStream
- 	"Remove a tab from the front of every line occupied by the selection. Flushes typeahead.  Invoked from keyboard via cmd-shift-L.  2/29/96 sw"
  
+ 	^ self inOutdent: aKeyboardEvent delta: -1!
- 	^ self inOutdent: characterStream delta: -1!

Item was changed:
  ----- Method: TextEditor>>pasteInitials: (in category 'editing keys') -----
+ pasteInitials: aKeyboardEvent 
+ 	"Replace the current text selection by an authorship name/date stamp; invoked by cmd-shift-v, easy way to put an authorship stamp in the comments of an editor."
- pasteInitials: characterStream 
- 	"Replace the current text selection by an authorship name/date stamp; invoked by cmd-shift-v, easy way to put an authorship stamp in the comments of an editor.
- 	 Keeps typeahead."
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self replace: self selectionInterval with: (Text fromString: Utilities changeStamp) and: [self selectAt: self stopIndex].
  	^ true!

Item was removed:
- ----- Method: TextEditor>>pointBlock (in category 'accessing-selection') -----
- pointBlock
- 	^ pointBlock!

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

Item was changed:
  ----- Method: TextEditor>>pointIndex (in category 'accessing-selection') -----
  pointIndex
+ 	^ pointBlock stringIndex!
- 	^ self pointBlock stringIndex!

Item was removed:
- ----- Method: TextEditor>>pointIndex: (in category 'accessing-selection') -----
- pointIndex: anIndex
- 	self pointBlock: (paragraph characterBlockForIndex: anIndex)
- !

Item was changed:
  ----- Method: TextEditor>>printIt: (in category 'editing keys') -----
+ printIt: aKeyboardEvent
- printIt: characterStream 
  	"Print the results of evaluting the selection -- invoked via cmd-p.  If there is no current selection, use the current line.  1/17/96 sw
  	 2/29/96 sw: don't call selectLine now, since it's called by doIt"
  
- 	sensor keyboard.		"flush character"
  	self printIt.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>querySymbol: (in category 'typing/selecting keys') -----
+ querySymbol: aKeyboardEvent
- querySymbol: characterStream
  	"Invoked by Ctrl-q to query the Symbol table and display alternate symbols.
  	 See comment in completeSymbol:lastOffering: for details."
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.	"keep typeahead"
  	self hasCaret
  		ifTrue: "Ctrl-q typed when a caret"
  			[self perform: #completeSymbol:lastOffering: withArguments:
  				((UndoParagraph == paragraph and: [UndoMessage sends: #undoQuery:lastOffering:])
  					ifTrue: [UndoMessage arguments] "repeated Ctrl-q"
  					ifFalse: [Array with: nil with: nil])] "initial Ctrl-q"
  		ifFalse: "Ctrl-q typed when statements were highlighted"
  			[morph flash].
  	^true!

Item was changed:
  ----- Method: TextEditor>>raiseContextMenu: (in category 'nonediting/nontyping keys') -----
+ raiseContextMenu: aKeyboardEvent 
- raiseContextMenu: characterStream 
  	(morph respondsTo: #editView)
+ 		ifTrue: [morph editView yellowButtonActivity: false].
- 		ifTrue: [morph editView yellowButtonActivity: ActiveEvent shiftPressed].
  	^ true!

Item was removed:
- ----- 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).
- 	[ sensor keyboardPressed ] whileTrue: [
- 		self deselect.
- 		[ sensor keyboardPressed ] whileTrue: [
- 			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].
- 		self zapSelectionWith: 
- 			(Text string: typeAhead contents attributes: emphasisHere).
- 		typeAhead reset.
- 		self unselect].
- 	self storeSelectionInParagraph!

Item was removed:
- ----- Method: TextEditor>>recomputeInterval (in category 'current selection') -----
- recomputeInterval
- 	"The same characters are selected but their coordinates may have changed."
- 
- 	self markIndex: self markIndex; pointIndex: self pointIndex!

Item was changed:
  ----- Method: TextEditor>>recomputeSelection (in category 'current selection') -----
  recomputeSelection
+ 	"The same characters are selected but their coordinates may have changed."
- 	"Redetermine the selection according to the start and stop block indices; 
- 	do not highlight."
  
+ 	self markIndex: self markIndex pointIndex: self pointIndex!
- 	self deselect; recomputeInterval!

Item was changed:
  ----- Method: TextEditor>>referencesToIt: (in category 'editing keys') -----
+ referencesToIt: aKeyboardEvent
- referencesToIt: characterStream 
  	"Triggered by Cmd-N; browse references to the current selection"
  
- 	sensor keyboard.		"flush character"
  	self referencesToIt.
  	^ true!

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."
  
+ 	beginTypeInIndex ifNotNil: [^self zapSelectionWith: aText]. "called from old code"
- 	beginTypeInBlock ifNotNil: [^self zapSelectionWith: aText]. "called from old code"
  	UndoSelection := self selection.
  	self zapSelectionWith: aText.
  	self undoer: #undoReplace!

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."
  
+ 	pointBlock := markBlock := paragraph defaultCharacterBlock.
+ 	beginTypeInIndex := nil.
- 	markBlock := paragraph defaultCharacterBlock.
- 	self pointBlock: markBlock copy.
- 	beginTypeInBlock := nil.
  	UndoInterval := otherInterval := 1 to: 0.
  	self setEmphasisHere.
  	selectionShowing := false!

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

Item was changed:
  ----- Method: TextEditor>>save: (in category 'editing keys') -----
+ save: aKeyboardEvent
+ 	"Submit the current text.  Equivalent to 'accept' 1/18/96 sw"
- save: characterStream
- 	"Submit the current text.  Equivalent to 'accept' 1/18/96 sw
- 	 Keeps typeahead."
  
+ 	self closeTypeIn.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
  	self accept.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>search: (in category 'typing/selecting keys') -----
+ search: aKeyboardEvent
- search: characterStream
  	"Invoked by Ctrl-S.  Same as 'again', but always uses the existing FindText
  	 and ChangeText regardless of the last edit."
  
+ 	self closeTypeIn.
+ 	self
+ 		againOrSame: true "true means use same keys"
+ 		many: aKeyboardEvent shiftPressed.
- 	sensor keyboard.		"flush character"
- 	self closeTypeIn: characterStream.
- 	self againOrSame: true. "true means use same keys"
  	^true!

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

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 string.
- 	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>>selectionAsStream (in category 'accessing-selection') -----
  selectionAsStream
+ 	"Answer a ReadStream on the text in the paragraph that is currently  selected."
- 	"Answer a ReadStream on the text in the paragraph that is currently 
- 	selected."
  
  	^ReadWriteStream
  		on: paragraph string
  		from: self startIndex
  		to: self stopIndex - 1!

Item was changed:
  ----- Method: TextEditor>>sendersOfIt: (in category 'editing keys') -----
+ sendersOfIt: aKeyboardEvent
- sendersOfIt: characterStream 
  	"Triggered by Cmd-n; browse implementors of the selector represented by the current selection, if plausible. 2/1/96 sw"
  
- 	sensor keyboard.		"flush character"
  	self sendersOfIt.
  	^ true!

Item was added:
+ ----- Method: TextEditor>>setEmphasisHereFromText (in category 'typing support') -----
+ setEmphasisHereFromText
+ 
+ 	self setEmphasisHereFromTextForward: true!

Item was added:
+ ----- Method: TextEditor>>setEmphasisHereFromTextForward: (in category 'typing support') -----
+ setEmphasisHereFromTextForward: f
+ 
+ 	| i t forward delta prevIsSeparator nextIsSeparator |
+ 	i := self pointIndex.
+ 	t := self text.
+ 	"Try to set emphasisHere correctly after whitespace.
+ 	Most important after a cr, i.e. at the start of a new line"
+ 	prevIsSeparator :=  i > 1 and: [ (t at: i-1) isSeparator ].
+ 	nextIsSeparator := i <= t size and: [ (t at: i) isSeparator ].
+ 	forward := prevIsSeparator = nextIsSeparator
+ 		ifTrue: [ f ]
+ 		ifFalse: [ nextIsSeparator ].
+ 	delta := forward ifTrue: [ 1 ] ifFalse: [ 0 ].
+ 	emphasisHere := (t attributesAt: (i - delta max: 1))
+ 					select: [:att | att mayBeExtended].!

Item was changed:
  ----- Method: TextEditor>>setSearch: (in category 'accessing') -----
+ setSearch: aStringOrText
- 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 = aStringOrText
+ 		ifFalse: [FindText := ChangeText := aStringOrText]!
- 	FindText string = aString
- 		ifFalse: [FindText := ChangeText := aString asText]!

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

Item was changed:
  ----- Method: TextEditor>>shiftEnclose: (in category 'editing keys') -----
+ shiftEnclose: aKeyboardEvent
- shiftEnclose: characterStream
  	"Insert or remove bracket characters around the current selection.
  	 Flushes typeahead."
  
  	| char left right startIndex stopIndex oldSelection which text |
+ 	char := aKeyboardEvent keyCharacter.
- 	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 > 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>>spawnIt: (in category 'editing keys') -----
+ spawnIt: aKeyboardEvent
- spawnIt: characterStream
  	"Triggered by Cmd-o; spawn a new code window, if it makes sense."
  
- 	sensor keyboard.
  	self spawn.
  	^ true!

Item was changed:
  ----- Method: TextEditor>>startBlock (in category 'accessing-selection') -----
  startBlock
+ 	^ pointBlock min: markBlock!
- 	^ self pointBlock min: self markBlock!

Item was changed:
  ----- Method: TextEditor>>startOfTyping (in category 'typing support') -----
  startOfTyping
  	"Compatibility during change from characterBlock to integer"
+ 	beginTypeInIndex == nil ifTrue: [^ nil].
+ 	beginTypeInIndex isNumber ifTrue: [^ beginTypeInIndex].
- 	beginTypeInBlock == nil ifTrue: [^ nil].
- 	beginTypeInBlock isNumber ifTrue: [^ beginTypeInBlock].
  	"Last line for compatibility during change from CharacterBlock to Integer."
+ 	^ beginTypeInIndex stringIndex!
- 	^ beginTypeInBlock stringIndex!

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.
  	self selectFrom: sel first to: sel last.
+ 	beginTypeInIndex := stateArray at: 9.
- 	beginTypeInBlock := stateArray at: 9.
  	emphasisHere := stateArray at: 10!

Item was changed:
  ----- Method: TextEditor>>stopBlock (in category 'accessing-selection') -----
  stopBlock
+ 	^ pointBlock max: markBlock!
- 	^ self pointBlock max: self markBlock!

Item was changed:
  ----- Method: TextEditor>>swapChars: (in category 'editing keys') -----
+ swapChars: aKeyboardEvent 
- 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
  		ifTrue:
  			[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.
  	self replaceSelectionWith: (Text string: aString reversed attributes: emphasisHere).
  	self selectAt: currentSelection + 1.
  	^ true!

Item was added:
+ ----- Method: TextEditor>>unapplyAttribute: (in category 'private') -----
+ unapplyAttribute: aTextAttribute
+ 	"The user selected aTextAttribute to be removed.
+ 	If there is a selection, unapply the attribute to the selection.
+ 	In any case do not use the attribute for the user input (emphasisHere)"
+ 
+ 	| interval |
+ 
+ 	emphasisHere := emphasisHere copyWithout: aTextAttribute.
+ 
+ 	interval := self selectionInterval.
+ 	(interval isEmpty and: [ aTextAttribute isParagraphAttribute not ])
+ 		ifTrue: [ ^self ].
+ 	
+ 	self text removeAttribute: aTextAttribute from: interval first to: interval last.
+ 	paragraph recomposeFrom: interval first to: interval last delta: 0.
+ 	self recomputeSelection.	"Needed so visible selection is updated to reflect new visual extent of selection"
+ 	morph changed!

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.
- 	UndoParagraph == paragraph ifFalse: "Can't undo another paragraph's edit"
- 		[UndoMessage := Message selector: #undoReplace.
  		UndoInterval := 1 to: 0.
  		Undone := true].
+ 	UndoInterval ~= self selectionInterval ifTrue: [ "blink the actual target"
+ 		self selectInterval: UndoInterval].
- 	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].
  	UndoMessage sentTo: self.
  	UndoParagraph := paragraph!

Item was changed:
  ----- Method: TextEditor>>undo: (in category 'editing keys') -----
+ undo: aKeyboardEvent 
+ 	"Undo the last edit."
- undo: characterStream 
- 	"Undo the last edit.  Keeps typeahead, so undo twice is a full redo."
  
+ 	self closeTypeIn.
- 	sensor keyboard. 	"flush character"
- 	self closeTypeIn: characterStream.
  	self undo.
  	^true!

Item was removed:
- ----- Method: TextEditor>>unselect (in category 'accessing-selection') -----
- unselect
- 	self markBlock: self pointBlock copy!

Item was changed:
  ----- Method: TextEditor>>zapSelectionWith: (in category 'mvc compatibility') -----
+ zapSelectionWith: replacement
- zapSelectionWith: aText
  
+ 	| start stop rep |
- 	| start stop |
  	self deselect.
  	start := self startIndex.
  	stop := self stopIndex.
+ 	(replacement isEmpty and: [stop > start]) ifTrue: [
- 	(aText isEmpty and: [stop > start]) ifTrue: [
  		"If deleting, then set emphasisHere from 1st character of the deletion"
+ 		emphasisHere := (self text attributesAt: start) select: [:att | att mayBeExtended]].
+ 	(start = stop and: [ replacement isEmpty ]) ifFalse: [
+ 		replacement isText
+ 			ifTrue: [ rep := replacement]
+ 			ifFalse: [ rep := Text string: replacement attributes: emphasisHere ].
+ 		self text replaceFrom: start to: stop - 1 with: rep.
+ 		paragraph
+ 			recomposeFrom: start
+ 			to:  start + rep size - 1
+ 			delta: rep size - (stop-start).
+ 		self markIndex: start pointIndex: start + rep size.
- 		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].
  
  	self userHasEdited  " -- note text now dirty"!

Item was changed:
  ----- Method: TextMorph>>mouseMove: (in category 'event handling') -----
  mouseMove: evt
  	evt redButtonPressed ifFalse: [^ self enterClickableRegion: evt].
+ 	self handleInteraction: [self editor mouseMove: evt] fromEvent: evt!
- 	self handleInteraction: [editor mouseMove: evt] fromEvent: evt!

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



More information about the Packages mailing list