[squeak-dev] The Trunk: Morphic-mt.1035.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 13 09:13:24 UTC 2015


Marcel Taeumel uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-mt.1035.mcz

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

Name: Morphic-mt.1035
Author: mt
Time: 13 November 2015, 10:12:46.795 am
UUID: 926c3239-11f3-4ae5-930a-3de5de1a8d7e
Ancestors: Morphic-mt.1034

Adds multiple text undo/redo functionality. Preference allows to specify the maximum history depth. Each text editor has its own history. All histories will be purged when building a Squeak release.

CMD+Z ... Undo
CMD+SHIFT+Z ... Redo

Note: The function #makeCapitalized: cannot be invoked via CMD+SHIFT+Z anymore. CMD+Y is undo primarily on Windows machines and already assigned to #swapChars:. Also, CMD+SHIFT+Z is more convenient for US-like keyboard layouts.

=============== Diff against Morphic-mt.1034 ===============

Item was removed:
- Object subclass: #EditCommand
- 	instanceVariableNames: 'textMorph phase replacedText replacedTextInterval newText newTextInterval lastSelectionInterval'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Text Support'!
- 
- !EditCommand commentStamp: '<historical>' prior: 0!
- This class handles all paragraph surgery in VI. In general, subclasses of EditCommand should be able to rely on the super class' undo/redo machinery -- only the repeat command needs to be overridden in most cases. This assumes, of course, that the newText, replacedText, newTextInterval, and replacedTextInterval have been set correctly.
- 
- When setting the interval, use normal mode style selections, not insert mode selections (see class comment of VIMorphEditor).
- 
- Possible useful expressions for doIt or printIt.
- 
- Structure:
-  instVar1		type -- comment about the purpose of instVar1
-  instVar2		type -- comment about the purpose of instVar2
- 
- Any further useful comments about the general approach of this implementation.!

Item was removed:
- ----- Method: EditCommand class>>textMorph:replacedText:replacedTextInterval:newText:newTextInterval: (in category 'instance creation') -----
- textMorph: tm
- replacedText: replacedText 
- replacedTextInterval: replacedTextInterval
- newText: newText 
- newTextInterval: newTextInterval
- 
- 
- 	^(self new)
- 			textMorph: tm
- 			replacedText: replacedText 
- 			replacedTextInterval: replacedTextInterval
- 			newText: newText 
- 			newTextInterval: newTextInterval;
- 			yourself
- 
- !

Item was removed:
- ----- Method: EditCommand>>doCommand (in category 'command execution') -----
- doCommand
- 
- 	^self redoCommand
- 
- 	!

Item was removed:
- ----- Method: EditCommand>>doSelectionInterval (in category 'selection') -----
- doSelectionInterval
- 	^self redoSelectionInterval!

Item was removed:
- ----- Method: EditCommand>>iEditCommand (in category 'accessors') -----
- iEditCommand
- 	^true!

Item was removed:
- ----- Method: EditCommand>>lastSelectionInterval (in category 'accessors') -----
- lastSelectionInterval
- 	^lastSelectionInterval!

Item was removed:
- ----- Method: EditCommand>>newText (in category 'accessors') -----
- newText
- 	^newText!

Item was removed:
- ----- Method: EditCommand>>newText: (in category 'accessors') -----
- newText: aText
- 	^newText := aText!

Item was removed:
- ----- Method: EditCommand>>newTextInterval (in category 'accessors') -----
- newTextInterval
- 	^newTextInterval!

Item was removed:
- ----- Method: EditCommand>>newTextInterval: (in category 'accessors') -----
- newTextInterval: anInterval
- 	^newText := anInterval!

Item was removed:
- ----- Method: EditCommand>>pEditor (in category 'accessors') -----
- pEditor
- 	^textMorph editor
- !

Item was removed:
- ----- Method: EditCommand>>phase (in category 'accessors') -----
- phase
- 	^phase 
- !

Item was removed:
- ----- Method: EditCommand>>phase: (in category 'accessors') -----
- phase: aSymbol
- 	^phase := aSymbol
- !

Item was removed:
- ----- Method: EditCommand>>printOn: (in category 'accessors') -----
- printOn: aStream
- 
- 	| |
- 	aStream 
- 		nextPutAll: self class name;
- 		nextPut: $[;
- 		nextPutAll: ('new: ', newTextInterval asString,' -> "', newText, '", rText: ', replacedTextInterval asString,' -> "', replacedText, '"');
- 		nextPut: $].!

Item was removed:
- ----- Method: EditCommand>>redoCommand (in category 'command execution') -----
- redoCommand
- 
- 	| |
- 
- "Debug dShow: ('rInterval: ', replacedTextInterval asString, '. rText: ', replacedText string, ' nInterval: ', newTextInterval asString, ' nText: ', newText string)."
- 	self textMorphEditor
- 		noUndoReplace: replacedTextInterval
- 		with: newText.
- 
- "Debug dShow: ('lastSelInt: ', lastSelectionInterval asString)."
- !

Item was removed:
- ----- Method: EditCommand>>redoSelectionInterval (in category 'selection') -----
- redoSelectionInterval
- "Return an interval to be displayed as a subtle selection after undo, or nil"
- 
- 	^newTextInterval
- !

Item was removed:
- ----- Method: EditCommand>>replacedText (in category 'accessors') -----
- replacedText
- 	^replacedText!

Item was removed:
- ----- Method: EditCommand>>replacedText: (in category 'accessors') -----
- replacedText: aText
- 	^replacedText := aText!

Item was removed:
- ----- Method: EditCommand>>replacedTextInterval (in category 'accessors') -----
- replacedTextInterval
- 	^replacedTextInterval!

Item was removed:
- ----- Method: EditCommand>>replacedTextInterval: (in category 'accessors') -----
- replacedTextInterval: anInterval
- 	^replacedTextInterval := anInterval!

Item was removed:
- ----- Method: EditCommand>>textMorph:replacedText:replacedTextInterval:newText:newTextInterval: (in category 'initialization') -----
- textMorph: tm
- replacedText: rText 
- replacedTextInterval: rInterval
- newText: nText 
- newTextInterval: nInterval
- 
- 
- 	textMorph := tm.
- 	replacedText := rText.
- 	replacedTextInterval := rInterval.
- 	newText := nText.
- 	newTextInterval := nInterval.
- 
- !

Item was removed:
- ----- Method: EditCommand>>textMorphEditor (in category 'accessors') -----
- textMorphEditor
- 	^textMorph editor
- !

Item was removed:
- ----- Method: EditCommand>>textMorphString (in category 'accessors') -----
- textMorphString
- 	^textMorph text string 
- !

Item was removed:
- ----- Method: EditCommand>>textMorphStringSize (in category 'accessors') -----
- textMorphStringSize
- 	^textMorph text string size
- !

Item was removed:
- ----- Method: EditCommand>>undoCommand (in category 'command execution') -----
- undoCommand
- 
- "Debug dShow: ('new Interval: ', newTextInterval asString, '. rText: ', replacedText string)."
- 
- 	self textMorphEditor	
- 		noUndoReplace: newTextInterval
- 		with: replacedText.
- 		
- 	
- !

Item was removed:
- ----- Method: EditCommand>>undoSelection (in category 'selection') -----
- undoSelection
- "Return an interval to be displayed as a selection after undo, or nil"
- 
- 	^replacedTextInterval first to: (replacedTextInterval first + replacedText size - 1)
- !

Item was removed:
- ----- Method: EditCommand>>undoSelectionInterval (in category 'selection') -----
- undoSelectionInterval
- "Return an interval to be displayed as a selection after undo, or nil"
- 
- 	| i |
- 	i := (replacedTextInterval first min: self textMorphStringSize).
- 	^i to: i - 1
- !

Item was changed:
  ----- Method: Editor>>backspace: (in category 'typing/selecting keys') -----
  backspace: aKeyboardEvent 
  	"Backspace over the last character."
  
  	| startIndex |
  	aKeyboardEvent shiftPressed ifTrue: [^ self backWord: aKeyboardEvent].
  	startIndex := self markIndex +
  				(self hasCaret ifTrue: [0] ifFalse: [1]).
  	startIndex := 1 max: startIndex - 1.
+ 
+ 	^ self backTo: startIndex!
- 	self backTo: startIndex.
- 	^false!

Item was changed:
  ----- Method: Editor>>firstWordBoundaryAfter: (in category 'private') -----
  firstWordBoundaryAfter: position
  	"If the character at position is whitespace, answer the position of the first character after position which is not whitespace.
  	If the character at position is not whitespace, answer the position of the first character after position which is whitespace."
  	| string index atWhitespace |
  	string := self string.
  	index := position.
  	(atWhitespace := (string at: index) isSeparator)
  		ifTrue:
  			[ "find next non-separator"
+ 			[ (index <= string size) and: [ (string at: index) isSeparator ] ] whileTrue: [ index := index + 1 ] ]
- 			[ (index
- 				between: 1
- 				and: string size) and: [ (string at: index) isSeparator ] ] whileTrue: [ index := index + 1 ] ]
  		ifFalse:
  			[ "find next separator"
+ 			[ (index <= string size) and: [ (string at: index) isSeparator not ] ] whileTrue: [ index := index + 1 ] ].
- 			[ (index
- 				between: 1
- 				and: string size) and: [ (string at: index) isSeparator ] ] whileFalse: [ index := index + 1 ] ].
  	^ index!

Item was changed:
  ----- Method: MenuIcons class>>itemsIcons (in category 'menu decoration') -----
  itemsIcons
  	"answer a collection of associations wordings -> icon to  
  	decorate  
  	the menus all over the image"
  	| icons |
  	icons := OrderedCollection new.
  
  	"icons add: #('Test Runner' ) -> self smallTrafficIcon."
  
  	" 
  	world menu"
  	"icons add: #('previous project' 'go to previous project') -> self smallProjectBackIcon."
  	icons add: #('go to next project') -> self smallProjectNextIcon.
  	icons add: #('select' ) -> self smallSelectIcon.
  	icons add: #('jump to project...' ) -> self smallProjectJumpIcon.
  	icons add: #('open...' ) -> self smallOpenIcon.
  	icons add: #('appearance...' ) -> self smallConfigurationIcon.
  	icons add: #('help...' ) -> self smallHelpIcon.
  	"icons add: #('windows...' ) -> self smallWindowIcon."
  	icons add: #('changes...' ) -> self smallDocumentClockIcon.
  	icons add: #('print PS to file...' ) -> self smallPrintIcon.
  	icons add: #('debug...' ) -> self smallDebugIcon.
  	icons add: #('export...' ) -> self smallExportIcon.
  	icons add: #('save' ) -> self smallSaveIcon.
  	"icons add: #('save project on file...' ) -> self smallProjectSaveIcon."
  	"icons add: #('save as...') -> self smallSaveAsIcon.
  	icons add: #('save as new version') -> self smallSaveNewIcon.
  	icons add: #('save and quit' ) -> self smallQuitIcon."
  	icons add: #('quit') -> self smallQuitNoSaveIcon.
  	"icons add: #('load project from file...' ) -> self smallProjectLoadIcon."
  	""
  	icons add: #('do it (d)' ) -> self smallDoItIcon.
  	icons add: #('inspect it (i)' 'inspect world' 'explore world' 'inspect model' 'inspect morph' 'explore morph' 'inspect owner chain' 'explore' 'inspect' 'explore (I)' 'inspect (i)' 'basic inspect' ) -> self smallInspectItIcon.
  	icons add: #('print it (p)' ) -> self smallPrintIcon.
  	icons add: #('debug it (D)' ) -> self smallDebugIcon.
  	icons add: #('tally it' ) -> self smallTimerIcon.
  	""
  	icons add: #('copy (c)' 'copy to paste buffer' 'copy text' ) -> self smallCopyIcon.
  	icons add: #('paste (v)') -> self smallPasteIcon.
  	icons add: #('cut (x)' ) -> self smallCutIcon.
  	""
  	icons add: #('accept (s)' 'yes' 'Yes' ) -> self smallOkIcon.
  	icons add: #('cancel (l)' 'no' 'No' ) -> self smallCancelIcon.
  	""
+ 	icons add: #('redo (Z)' ) -> self smallRedoIcon.
- 	icons add: #('do again (j)' ) -> self smallRedoIcon.
  	icons add: #('undo (z)' ) -> self smallUndoIcon.
  	""
  	icons add: #( 'find class... (f)' 'find method...' ) -> self smallSearchIcon.
  	icons add: #('find...(f)') -> self smallFindIcon.
  	""
  	icons add: #('remove' 'remove class (x)' 'delete method from changeset (d)' 'remove method from system (x)' 'delete class from change set (d)' 'remove class from system (x)' 'destroy change set (X)' ) -> self smallDeleteIcon.
  	icons add: #('add item...' 'new category...' 'new change set... (n)' ) -> self smallNewIcon.
  	""
  	icons add: #('objects (o)' ) -> self smallObjectCatalogIcon.
  	icons add: #('authoring tools...')  -> self smallAuthoringToolsIcon.
  	icons add: #('projects...')  -> self smallProjectIcon.
  	""
  	icons add: #('make screenshot')  -> self smallScreenshotIcon.
  	
  	""
  	icons add: #('leftFlush' ) -> self smallLeftFlushIcon.
  	icons add: #('rightFlush' ) -> self smallRightFlushIcon.
  	icons add: #('centered' 'set alignment... (u)' ) -> self smallCenteredIcon.
  	icons add: #('justified' ) -> self smallJustifiedIcon.
  	""
  	icons add: #('set font... (k)' 'list font...' 'set subtitles font' 'change font' 'system fonts...' 'change font...' 'default text font...' 'flaps font...' 'eToys font...' 'eToys title font...' 'halo label font...' 'menu font...' 'window-title font...' 'balloon-help font...' 'code font...' 'button font...') -> self smallFontsIcon.
  	icons add: #('full screen on') -> self smallFullscreenOnIcon.
  	icons add: #('full screen off' ) -> self smallFullscreenOffIcon.
  	""
  	^ icons!

Item was changed:
  ----- Method: PasteUpMorph>>handleListenEvent: (in category 'events-processing') -----
  handleListenEvent: aUserInputEvent 
  	"Handlers for *global* keys, regardless of which widget has keyboard focus."
  	aUserInputEvent type = #keystroke ifTrue:
  		[ aUserInputEvent commandKeyPressed ifTrue:
  			[ aUserInputEvent keyValue = $R asciiValue ifTrue: [ Utilities browseRecentSubmissions ].
  			aUserInputEvent keyValue = $L asciiValue ifTrue: [ World findAFileList: aUserInputEvent ].
  			aUserInputEvent keyValue = $O asciiValue ifTrue: [ World findAMonticelloBrowser ].
  			aUserInputEvent keyValue = $P asciiValue ifTrue: [ World findAPreferencesPanel: aUserInputEvent ].
+ 			"aUserInputEvent keyValue = $Z asciiValue ifTrue: [ ChangeList browseRecentLog ]."
- 			aUserInputEvent keyValue = $Z asciiValue ifTrue: [ ChangeList browseRecentLog ].
  			aUserInputEvent keyValue = $] asciiValue ifTrue:
  				[ Smalltalk
  					snapshot: true
  					andQuit: false ] ] ]!

Item was added:
+ ----- Method: PluggableTextMorph>>findReplace (in category 'menu commands') -----
+ findReplace
+ 	self handleEdit: [textMorph editor findReplace]!

Item was added:
+ ----- Method: PluggableTextMorph>>redo (in category 'menu commands') -----
+ redo
+ 	self handleEdit: [textMorph editor redo]!

Item was changed:
  ----- Method: PluggableTextMorph>>update: (in category 'updating') -----
  update: aSymbol 
  	aSymbol ifNil: [^self].
  	aSymbol == #flash ifTrue: [^self flash].
  
  	aSymbol == getTextSelector
  		ifTrue: [
  			self setText: self getText.
  			getSelectionSelector
  				ifNotNil: [self setSelection: self getSelection].
  			^ self].
  	aSymbol == getSelectionSelector 
  		ifTrue: [^self setSelection: self getSelection].
  
  	aSymbol == #acceptChanges ifTrue: [^ self accept].
  	aSymbol == #revertChanges ifTrue: [^ self cancel].
  
  	(aSymbol == #autoSelect and: [getSelectionSelector notNil]) 
  		ifTrue: 
  			[self handleEdit: 
  					[(textMorph editor)
  						abandonChangeText; "no replacement!!"
  						setSearch: model autoSelectString;
+ 						findAgain]].
- 						againOrSame: true]].
  	aSymbol == #clearUserEdits ifTrue: [^self hasUnacceptedEdits: false].
  	aSymbol == #wantToChange 
  		ifTrue: 
  			[self canDiscardEdits ifFalse: [^self promptForCancel].
  			^self].
  	aSymbol == #appendEntry 
  		ifTrue: 
  			[self handleEdit: [self appendEntry].
  			^self refreshWorld].
  	aSymbol == #appendEntryLater
  		ifTrue: [self handleEdit: [self appendEntry]].
  	aSymbol == #clearText 
  		ifTrue: 
  			[self handleEdit: [self changeText: Text new].
  			^self refreshWorld].
  	aSymbol == #bs 
  		ifTrue: 
  			[self handleEdit: [self bsText].
  			^self refreshWorld].
  	aSymbol == #codeChangedElsewhere 
  		ifTrue: 
  			[self hasEditingConflicts: true.
  			^self changed].
  	aSymbol == #saveContents
  		ifTrue:
  			[^self saveContentsInFile].
  !

Item was changed:
  ----- Method: SmalltalkEditor class>>initializeCmdKeyShortcuts (in category 'keyboard shortcut tables') -----
  initializeCmdKeyShortcuts
  	"Initialize the (unshifted) command-key (or alt-key) shortcut table."
  	"NOTE: if you don't know what your keyboard generates, use Sensor kbdTest"
  	"SmalltalkEditor initialize"
  	| cmds |
  	super initializeCmdKeyShortcuts.
+ 	cmds := #($b #browseIt: $d #doIt: $i #inspectIt: $l #cancel: $m #implementorsOfIt: $n #sendersOfIt: $o #spawnIt: $p #printIt: $q #querySymbol: $s #save: ).
- 	cmds := #($b #browseIt: $d #doIt: $i #inspectIt: $j #doAgainOnce: $l #cancel: $m #implementorsOfIt: $n #sendersOfIt: $o #spawnIt: $p #printIt: $q #querySymbol: $s #save: ).
  	1 to: cmds size
  		by: 2
  		do: [ : i | cmdActions at: (cmds at: i) asciiValue + 1 put: (cmds at: i + 1)].
  	"Set up type-method argument hot keys, 1-4.."
  	'1234' do:
  		[ : eachKeyboardChar |
  		cmdActions 
  			at: eachKeyboardChar asciiValue + 1
  			put: #typeMethodArgument: ]!

Item was changed:
  Editor subclass: #TextEditor
+ 	instanceVariableNames: 'model paragraph markBlock pointBlock beginTypeInIndex emphasisHere lastParenLocation otherInterval oldInterval typeAhead history'
+ 	classVariableNames: 'AutoEnclose AutoIndent ChangeText FindText'
- 	instanceVariableNames: 'model paragraph markBlock pointBlock beginTypeInIndex emphasisHere lastParenLocation otherInterval oldInterval typeAhead'
- 	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 class>>cleanUp (in category 'class initialization') -----
+ cleanUp
+ 
+ 	TextEditor allSubInstancesDo: [:editor |
+ 		editor history ifNotNil: [:h | 
+ 			h current ifNotNil: [editor closeTypeIn].
+ 			h reset]].!

Item was changed:
  ----- Method: TextEditor class>>initialize (in category 'class initialization') -----
  initialize 
  	"Initialize the keyboard shortcut maps and the shared buffers
  	for copying text across views and managing again and undo." 
   
  	"TextEditor initialize"
  
+ 	FindText := ChangeText := Text new.
- 	UndoSelection := FindText := ChangeText := Text new.
- 	UndoMessage := Message selector: #halt.
  
  	self initializeCmdKeyShortcuts.
  	self initializeShiftCmdKeyShortcuts.
  	self initializeYellowButtonMenu.
  	self initializeShiftedYellowButtonMenu!

Item was changed:
  ----- Method: TextEditor class>>initializeCmdKeyShortcuts (in category 'keyboard shortcut tables') -----
  initializeCmdKeyShortcuts
  	"Initialize the (unshifted) command-key (or alt-key) shortcut table."
  
  	"NOTE: if you don't know what your keyboard generates, use Sensor kbdTest"
  
  	"TextEditor initialize"
  
  	| cmdMap cmds |
  	cmdMap := Array new: 256 withAll: #noop:.		"use temp in case of a crash"
  	cmdMap at: 1 + 1 put: #cursorHome:.				"home key"
  	cmdMap at: 4 + 1 put: #cursorEnd:.				"end key"
  	cmdMap at: 8 + 1 put: #backspace:.				"ctrl-H or delete key"
  	cmdMap at: 11 + 1 put: #cursorPageUp:.			"page up key"
  	cmdMap at: 12 + 1 put: #cursorPageDown:.		"page down key"
  	cmdMap at: 13 + 1 put: #crWithIndent:.			"cmd-Return"
  	cmdMap at: 27 + 1 put: #offerMenuFromEsc:.		"escape key"
  	cmdMap at: 28 + 1 put: #cursorLeft:.				"left arrow key"
  	cmdMap at: 29 + 1 put: #cursorRight:.				"right arrow key"
  	cmdMap at: 30 + 1 put: #cursorUp:.				"up arrow key"
  	cmdMap at: 31 + 1 put: #cursorDown:.				"down arrow key"
  	cmdMap at: 32 + 1 put: #selectWord:.				"space bar key"
  	cmdMap at: 127 + 1 put: #forwardDelete:.		"del key"
  			
  	'0123456789-=' 
  		do: [:char | cmdMap at: char asciiValue + 1 put: #changeEmphasis:].
  		
  	'([<{|"''' do: [:char | cmdMap at: char asciiValue + 1 put: #enclose:].
  	
+ 	cmds := #($a #selectAll: $c #copySelection: $e #exchange: $f #find: $g #findAgain: $h #setSearchString: $j #doAgain: $k #offerFontMenu: $u #align: $v #paste: $w #backWord: $x #cut: $y #swapChars: $z #undo:).
- 	cmds := #($a #selectAll: $c #copySelection: $e #exchange: $f #find: $g #findAgain: $h #setSearchString: $k #offerFontMenu: $u #align: $v #paste: $w #backWord: $x #cut: $y #swapChars: $z #undo:).
  	1 to: cmds size
  		by: 2
  		do: [:i | cmdMap at: (cmds at: i) asciiValue + 1 put: (cmds at: i + 1)].
  		
  	cmdActions := cmdMap!

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

Item was changed:
  ----- Method: TextEditor class>>initializeYellowButtonMenu (in category 'keyboard shortcut tables') -----
  initializeYellowButtonMenu
  	"Initialize the yellow button pop-up menu and corresponding messages."
  
  	"TextEditor initialize"
  
  	yellowButtonMenu := MenuMorph fromArray: {
  		{'find...(f)' translated.				#find}.
+ 		{'find again (g)' translated.				#findAgain}.
+ 		{'find and replace ...' translated.			#findReplace}.
+ 		{'do/replace again (j)' translated.			#again}.
- 		{'find again (g)' translated.			#findAgain}.
- 		{'set search string (h)' translated.	#setSearchString}.
  		#-.
- 		{'do again (j)' translated.			#again}.
  		{'undo (z)' translated.				#undo}.
+ 		{'redo (Z)' translated.				#redo}.
  		#-.
  		{'copy (c)' translated.				#copySelection}.
  		{'cut (x)' translated.				#cut}.
  		{'paste (v)' translated.				#paste}.
  		{'paste...' translated.				#pasteRecent}.
  		#-.
  		{'set font... (k)' translated.			#offerFontMenu}.
  		{'set style... (K)' translated.		#changeStyle}.
  		{'set alignment...' translated.		#chooseAlignment}.
  		"
  		#-.
  		{'more...' translated.				#shiftedTextPaneMenuRequest}.
  		"
  	}!

Item was added:
+ ----- Method: TextEditor class>>resetAllHistory (in category 'class initialization') -----
+ resetAllHistory
+ 
+ 	TextEditor allSubInstances do: [:editor |
+ 		editor history reset].
+ 
+ 	!

Item was changed:
  ----- Method: TextEditor>>addString: (in category 'typing support') -----
  addString: aString
+ 
  	morph readOnly ifTrue: [^ self].
+ 
+ 	"If we modifying the text like backward or forward delete, we have to finish that operation."
+ 	(self isTypingIn and: [self history current type notNil])
+ 		ifTrue: [self closeTypeIn].
+ 
  	self typeAhead nextPutAll: aString.!

Item was changed:
  ----- Method: TextEditor>>again (in category 'menu messages') -----
  again
+ 	"Do the same replace command again. Unlike #findReplaceAgain, this looks up the editor's own command history and uses the previous command."
+ 	
+ 	self history hasPrevious ifFalse: [morph flash. ^ self].
+ 	
+ 	self history previous hasReplacedSomething
+ 		ifFalse: [morph flash. ^ self]
+ 		ifTrue: [
+ 			"Reset shared find/replace state."
+ 			FindText := self history previous contentsBefore.
+ 			ChangeText := self history previous contentsAfter.
+ 			
+ 			self selectAt: self stopIndex.
+ 			self findReplaceAgain].!
- 	"Text substitution. If the left shift key is down, the substitution is made 
- 	throughout the entire Paragraph. Otherwise, only the next possible 
- 	substitution is made.
- 	Undoer & Redoer: #undoAgain:andReselect:typedKey:."
- 
- 	"If last command was also 'again', use same keys as before"
- 	self againOrSame: (UndoMessage sends: #undoAgain:andReselect:typedKey:)!

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

Item was removed:
- ----- 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.
- 
- 	(morph respondsTo: #editView) 
- 		ifTrue: [morph editView selectionInterval: self selectionInterval]!

Item was removed:
- ----- 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."
- 		"If the last command was in another paragraph, ChangeText is set..."
- 		paragraph == UndoParagraph ifTrue: [ "... else set it now as follows."
- 			UndoInterval ~= home ifTrue: [self selectInterval: UndoInterval]. "blink"
- 			ChangeText := ((UndoMessage sends: #undoCutCopy:) and: [self hasSelection])
- 				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.
- 			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]].
- 
- 	"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.
- 		wasTypedKey ifFalse: [^self]].
- 
- 	(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 added:
+ ----- Method: TextEditor>>againUpToEnd (in category 'menu messages') -----
+ againUpToEnd
+ 	"Find and replace until the end."
+ 	
+ 	| interval pivot isFirst last |
+ 	self history hasPrevious ifFalse: [morph flash. ^ self].
+ 	
+ 	pivot := self history previous.
+ 	pivot hasReplacedSomething ifFalse: [morph flash. ^ self].
+ 
+ 	"Reset shared find/replace state."
+ 	FindText := pivot contentsBefore.
+ 	ChangeText := pivot contentsAfter.
+ 
+ 	isFirst := true.
+ 	last := pivot.
+ 	[self selectionInterval ~= interval] whileTrue: [
+ 		last ~= pivot ifTrue: [
+ 			last
+ 				isCompositeUndo: isFirst not;
+ 				isCompositeRedo: true.
+ 			isFirst := false].
+ 		last := self history previous.
+ 		interval := self selectionInterval.
+ 		
+ 		self selectAt: self stopIndex. "No selection to make find work."
+ 		self findReplaceAgain].
+ 
+ 	last isCompositeRedo: false.!

Item was changed:
  ----- Method: TextEditor>>autoEncloseFor: (in category 'typing support') -----
  autoEncloseFor: typedChar 
  	"Answer whether typeChar was handled by auto-enclosure.  Caller should call normalCharacter if not."
  	| openers closers |
  	openers := '([{'.
  	closers := ')]}'.
  	(closers includes: typedChar) ifTrue:
  		[ | pos |
  		self blinkPrevParen: typedChar.
  		((pos := self indexOfNextNonwhitespaceCharacter) notNil and: [ (paragraph string at: pos) = typedChar ])
  			ifTrue:
  				[ self
  					moveCursor: [ : position | position + pos - pointBlock stringIndex + 1 ]
  					forward: true
  					select: false.
  				^ true ]
  			ifFalse: [ ^ false ] ].
+ 	(openers includes: typedChar) ifTrue: [
+ 		self
+ 			openTypeIn;
+ 			addString: typedChar asString;
+ 			addString: (closers at: (openers indexOf: typedChar)) asString ;
+ 			insertAndCloseTypeIn ;
- 	(self class autoEnclose and: [ openers includes: typedChar ]) ifTrue:
- 		[ self
- 			 addString: (closers at: (openers indexOf: typedChar)) asString ;
- 			 insertTypeAhead ;
  			
  			moveCursor: [ : position | position - 1 ]
  			forward: false
  			select: false.
+ 		^ true ].
- 		^ false ].
  	^ false!

Item was changed:
  ----- Method: TextEditor>>backTo: (in category 'typing support') -----
  backTo: startIndex
+ 	"During typing, backspace to startIndex. If there already is a selection, just delete that selection. Otherwise, check if we did something else than backward-deletion and start a new command if so."
- 	"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
- 	 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 |
  	morph readOnly ifTrue: [^ self].
+ 
+ 	self hasSelection ifTrue: [
+ 		"Add checkpoint in undo history."
+ 		self replaceSelectionWith: self nullText.
+ 		^ true].
+ 
+ 	startIndex > self text size ifTrue: [^ false].
+ 
+ 	self selectInvisiblyFrom: startIndex to: self stopIndex-1.
+ 	
+ 	self isTypingIn ifTrue: [
+ 		self history current type = #backward
+ 			ifFalse: [self closeTypeIn]
+ 			ifTrue: [
+ 				"Accumulate all deleted characters in current undo command."
+ 				self history current contentsBefore replaceFrom: 1 to: 0 with: self selection.
+ 				self history current intervalBefore in: [:i |
+ 					self history current intervalBefore: (startIndex to: i last)]]].
+ 		
+ 	self openTypeInFor: #backward.
- 	saveLimit := beginTypeInIndex
- 		ifNil: [self openTypeIn. UndoSelection := self nullText. self stopIndex].
- 	markBlock := paragraph characterBlockForIndex: startIndex.
- 	startIndex < saveLimit ifTrue: [
- 		newBackovers := beginTypeInIndex - startIndex.
- 		beginTypeInIndex := self startIndex.
- 		UndoSelection replaceFrom: 1 to: 0 with:
- 			(self text copyFrom: startIndex to: saveLimit - 1).
- 		UndoMessage arguments size > 0 ifTrue: [
- 			UndoMessage argument: (UndoMessage argument ifNil: [1]) + newBackovers]].
  	self zapSelectionWith: self nullText.
+ 	
+ 	^ false!
- 	self unselect!

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

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

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."
- 	 menu commands.
- 	 Undoer & Redoer: undoAndReselect:redoAndReselect:."
  
  	| begin stop |
  	beginTypeInIndex ifNotNil: [
+ 		begin := beginTypeInIndex.
+ 		stop := self stopIndex.
+ 				
+ 		self history current
+ 			contentsAfter: (stop <= begin
+ 				ifTrue: [self nullText]
+ 				ifFalse: [paragraph text copyFrom: begin to: stop-1]);
+ 			intervalAfter: (stop to: stop-1);
+ 			intervalBetween: (stop < begin
+ 				ifTrue: [stop to: stop-1]
+ 				ifFalse: [begin to: stop-1]);
+ 			messageToUndo: (Message selector: #undoAndReselect);
+ 			messageToRedo: (Message selector: #redoAndReselect).
+ 			
+ 		self history finishRemember.
+ 
- 		(UndoMessage sends: #noUndoer) ifTrue: [ "should always be true, but just in case..."
- 			begin := beginTypeInIndex.
- 			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]!

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

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

Item was changed:
  ----- Method: TextEditor>>cut (in category 'menu messages') -----
  cut
  	"Cut out the current selection and redisplay the paragraph if necessary.  Undoer & Redoer: undoCutCopy:"
  
  	self lineSelectAndEmptyCheck: [^ self].
  
+ 	self clipboardTextPut: self selection.
+ 	self replaceSelectionWith: self nullText.!
- 	self replaceSelectionWith: self nullText. 
- 	self undoer: #undoCutCopy: with: self clipboardText.
- 	self clipboardTextPut: UndoSelection!

Item was changed:
  ----- 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."
+ 	
- 	"Carry out the action associated with this character, if any.  	Type-ahead is passed so some routines can flush or use it."
  	| honorCommandKeys typedChar |
+ 	typedChar := aKeyboardEvent keyCharacter.
+ 	
+ 	"Create a new command for separating characters."
+ 	(Character separators includes: typedChar)
+ 		ifTrue: [self closeTypeIn].
+ 	
+ 	"Handle one-line input fields."
+ 	(typedChar == Character cr and: [morph acceptOnCR])
+ 		ifTrue: [^ true].
+ 	
+ 	"Clear highlight for last opened parenthesis."
- 	((typedChar := aKeyboardEvent keyCharacter) == Character cr and: [ morph acceptOnCR ]) ifTrue:
- 		[ self closeTypeIn.
- 		^ true ].
  	self clearParens.
+ 	
+ 	"Handle line breaks and auto indent."
+ 	typedChar == Character cr ifTrue: [
+ 		aKeyboardEvent controlKeyPressed
+ 			ifTrue: [^ self normalCharacter: aKeyboardEvent].
+ 		aKeyboardEvent shiftPressed
+ 			ifTrue: [^ self lf: aKeyboardEvent].
+ 		aKeyboardEvent commandKeyPressed
+ 			ifTrue: [^ self crlf: aKeyboardEvent].
+ 		^ self crWithIndent: aKeyboardEvent].
+ 
+ 	"Handle indent/outdent with selected text block."
+ 	(typedChar == Character tab and: [self hasSelection]) ifTrue: [
+ 		aKeyboardEvent shiftPressed
+ 			ifTrue: [self outdent: aKeyboardEvent]
+ 			ifFalse: [self indent: aKeyboardEvent].
+ 		^ true].
+ 
+ 	honorCommandKeys := Preferences cmdKeysInText.
+ 
+ 	(honorCommandKeys and: [typedChar == Character enter])
+ 		ifTrue: [^ self dispatchOnEnterWith: aKeyboardEvent].
+ 	
- 	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 ].
- 	(aKeyboardEvent keyCharacter = Character tab and: [ self selection notEmpty ]) ifTrue:
- 		[ aKeyboardEvent shiftPressed
- 			ifTrue: [ self outdent: aKeyboardEvent ]
- 			ifFalse: [ self indent: aKeyboardEvent ].
- 		^ true ].
- 	((honorCommandKeys := Preferences cmdKeysInText) and: [ typedChar = 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]].
+ 			
- 	((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]].
+ 
- 	((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].
+ 
+ 	"Automatically enclose paired characters such as brackets."
- 	(honorCommandKeys and: [ aKeyboardEvent controlKeyPressed ]) ifTrue: [ ^ self
- 			perform: (self class shiftCmdActions at: aKeyboardEvent keyValue + 1)
- 			with: aKeyboardEvent ].
  	self class autoEnclose
+ 		ifTrue: [((self hasSelection and: [self enclose: aKeyboardEvent])
+ 			or: [self autoEncloseFor: typedChar])
+ 				ifTrue: [^ true]].
+ 					
+ 	self normalCharacter: aKeyboardEvent.
- 		ifTrue:
- 			[ (self autoEncloseFor: typedChar) ifFalse: [ self normalCharacter: aKeyboardEvent ] ]
- 		ifFalse: [ self normalCharacter: aKeyboardEvent ].
  	^ false!

Item was added:
+ ----- Method: TextEditor>>doAgain: (in category 'typing/selecting keys') -----
+ doAgain: aKeyboardEvent 
+ 	"Do the previous thing again once. 1/26/96 sw"
+ 
+ 	self insertAndCloseTypeIn.
+ 	self again.
+ 	^ true!

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

Item was removed:
- ----- Method: TextEditor>>doAgainOnce: (in category 'typing/selecting keys') -----
- doAgainOnce: aKeyboardEvent 
- 	"Do the previous thing again once. 1/26/96 sw"
- 
- 	self insertAndCloseTypeIn.
- 	self again.
- 	^ true!

Item was added:
+ ----- Method: TextEditor>>doAgainUpToEnd: (in category 'typing/selecting keys') -----
+ doAgainUpToEnd: aKeyboardEvent 
+ 	"Do the previous thing again once. 1/26/96 sw"
+ 
+ 	self insertAndCloseTypeIn.
+ 	self againUpToEnd.
+ 	^ true!

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

Item was changed:
  ----- Method: TextEditor>>enclose: (in category 'editing keys') -----
  enclose: aKeyboardEvent
  	"Insert or remove bracket characters around the current selection."
  
  	| character left right startIndex stopIndex oldSelection which t |
  	character := aKeyboardEvent shiftPressed
  					ifTrue: ['{}|"<>' at: ('[]\'',.' indexOf: aKeyboardEvent keyCharacter) ifAbsent: [aKeyboardEvent keyCharacter]]
  					ifFalse: [aKeyboardEvent keyCharacter].
  	self closeTypeIn.
  	startIndex := self startIndex.
  	stopIndex := self stopIndex.
  	oldSelection := self selection.
+ 	which := '([<{|"''9' indexOf: character ifAbsent: [ ^false ].
- 	which := '([<{|"''9' indexOf: character ifAbsent: [ ^true ].
  	"Allow Control key in lieu of Alt+Shift for (, {, and double-quote."
  	left := ((Preferences cmdKeysInText and: [ aKeyboardEvent controlKeyPressed ])
  		ifTrue: [ '({<{|""(' ]
  		ifFalse: ['([<{|"''(']) at: which.
  	right := ((Preferences cmdKeysInText and: [ aKeyboardEvent controlKeyPressed ])
  		ifTrue: [ ')}>}|"")' ] 
  		ifFalse: [')]>}|"'')']) at: which.
  	t := self text.
  	((startIndex > 1 and: [stopIndex <= t size])
  			and: [ (t at: startIndex-1) = left and: [(t 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>>exchange (in category 'menu messages') -----
  exchange
  	"See comment in exchangeWith:"
  
+ 	self exchangeWith: otherInterval.!
- 	self exchangeWith: otherInterval!

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

Item was changed:
  ----- Method: TextEditor>>find (in category 'menu messages') -----
  find
  	"Prompt the user for a string to search for, and search the receiver from the current selection onward for it.  1/26/96 sw"
  
+ 	(UIManager default request: 'Find what to select? ' initialAnswer: (self selection ifEmpty: [FindText]))
+ 		ifEmpty: [^ self]
+ 		ifNotEmpty: [:reply |
+ 			self setSearch: reply.
+ 			self findAgain].!
- 	| reply |
- 	reply := UIManager default request: 'Find what? ' initialAnswer: ''.
- 	reply size = 0 ifTrue: [
- 		^ self].
- 	self setSearch: reply.
- 	ChangeText := FindText.  "Implies no replacement to againOnce: method"
- 	self againOrSame: true.
- 
- 	morph installEditorToReplace: self!

Item was changed:
  ----- Method: TextEditor>>findAgain (in category 'menu messages') -----
  findAgain
- 	"Find the text-to-find again.  1/24/96 sw"
  
+ 	| where |	
+ 	where := self text
+ 				findString: FindText
+ 				startingAt: self stopIndex
+ 				caseSensitive: Preferences caseSensitiveFinds.
+ 	
+ 	where = 0 ifTrue: [^ false].
+ 
+ 	self selectFrom: where to: where + FindText size - 1.
+ 
+ 	^ true!
- 	self againOrSame: true!

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

Item was added:
+ ----- Method: TextEditor>>findReplace (in category 'menu messages') -----
+ findReplace
+ 
+ 	(UIManager default request: 'Find what to replace?' initialAnswer: (self selection ifEmpty: [FindText]))
+ 		ifEmpty: [^ self]
+ 		ifNotEmpty: [:find |
+ 			(UIManager default request: ('Replace ''{1}'' with?' format: {find}) initialAnswer: (ChangeText ifEmpty: [find]))
+ 				ifEmpty: [^ self]
+ 				ifNotEmpty: [:replace |
+ 					FindText := find.
+ 					ChangeText := replace.
+ 					self findReplaceAgain]]!

Item was added:
+ ----- Method: TextEditor>>findReplace: (in category 'typing/selecting keys') -----
+ findReplace: aKeyboardEvent
+ 
+ 	self insertAndCloseTypeIn.
+ 	self findReplace.
+ 	^ true!

Item was added:
+ ----- Method: TextEditor>>findReplaceAgain (in category 'menu messages') -----
+ findReplaceAgain
+ 
+ 	| where |
+ 	self hasSelection ifTrue: [
+ 		"Search from the beginning of the current selection. Supports a nice combination with regular find feature."
+ 		self selectInvisiblyFrom: self startIndex to: self startIndex - 1].
+ 	
+ 	where := self text
+ 				findString: FindText
+ 				startingAt: self stopIndex
+ 				caseSensitive: Preferences caseSensitiveFinds.
+ 	
+ 	where = 0 ifTrue: [^ false].
+ 
+ 	self selectInvisiblyFrom: where to: where + FindText size - 1.
+ 	self replaceSelectionWith: ChangeText.
+ 
+ 	^ true!

Item was added:
+ ----- Method: TextEditor>>findReplaceAgain: (in category 'typing/selecting keys') -----
+ findReplaceAgain: aKeyboardEvent 
+ 
+ 	self insertAndCloseTypeIn.
+ 	self findReplaceAgain.
+ 	^ true!

Item was changed:
  ----- Method: TextEditor>>forwardDelete: (in category 'typing/selecting keys') -----
  forwardDelete: aKeyboardEvent
  	"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 stopIndex |
+ 	morph readOnly ifTrue: [^ self].
+ 	
- 	| startIndex usel upara uinterval ind stopIndex |
- 	startIndex := self markIndex.
- 	startIndex > self text size ifTrue: [
- 		^ false].
  	self hasSelection ifTrue: [
+ 		"Create checkpoint in history."
+ 		self replaceSelectionWith: self nullText.
+ 		^ true].
+ 
+ 	startIndex := self markIndex.
+ 	startIndex > self text size ifTrue: [^ false].
+ 
- 		"there was a selection"
- 		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.
  	stopIndex := startIndex.
+ 
+ 	"Forward delete next word"
+ 	self flag: #consistency. "mt: We might want to implemented it like #backspace: and #backWord:."
+ 	aKeyboardEvent shiftPressed
- 	(aKeyboardEvent keyValue = 127 and: [ aKeyboardEvent shiftPressed ])
  		ifTrue: [stopIndex := (self firstWordBoundaryAfter: stopIndex) - 1].
+ 
+ 	self selectInvisiblyFrom: startIndex to: stopIndex.
+ 	
+ 	self isTypingIn ifTrue: [
+ 		self history current type = #forwardDelete
+ 			ifFalse: [self closeTypeIn]
+ 			ifTrue: [
+ 				"Append next characters that will be removed."
+ 				self history current contentsBefore append: self selection.
+ 				self history current intervalBefore in:  [:i |
+ 					self history current intervalBefore: (i first to: i last + (stopIndex - startIndex + 1))]]].
+ 	
+ 	self openTypeInFor: #forwardDelete.
+ 	self zapSelectionWith: self nullText.
+ 	
+ 	^ false!
- 	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]].
- 	^false!

Item was added:
+ ----- Method: TextEditor>>history (in category 'accessing') -----
+ history
+ 	^ history!

Item was added:
+ ----- Method: TextEditor>>history: (in category 'accessing') -----
+ history: commandHistory
+ 	history := commandHistory.!

Item was changed:
  ----- Method: TextEditor>>insertAndSelect:at: (in category 'new selection') -----
  insertAndSelect: aString at: anInteger
  
+ 	self closeTypeIn.
+ 	
+ 	self selectInvisiblyFrom: anInteger to: anInteger - 1.
+ 	self openTypeIn.
+ 
+ 	self
+ 		replace: self selectionInterval
+ 		with: (Text string: (' ', aString) attributes: emphasisHere)
+ 		and: [self].
+ 
+ 	self closeTypeIn.!
- 	self replace: (anInteger to: anInteger - 1)
- 		with: (Text string: (' ' , aString)
- 					attributes: emphasisHere)
- 		and: [self ]!

Item was removed:
- ----- Method: TextEditor>>isDoing (in category 'undo support') -----
- isDoing
- 	"Call from a doer/undoer/redoer any time to see which it is."
- 
- 	^(self isUndoing | self isRedoing) not!

Item was removed:
- ----- Method: TextEditor>>isRedoing (in category 'undo support') -----
- isRedoing
- 	"Call from a doer/undoer/redoer any time to see which it is."
- 
- 	^UndoParagraph == #redoing!

Item was added:
+ ----- Method: TextEditor>>isTypingIn (in category 'typing support') -----
+ isTypingIn
+ 	^ beginTypeInIndex notNil!

Item was removed:
- ----- Method: TextEditor>>isUndoing (in category 'undo support') -----
- isUndoing
- 	"Call from a doer/undoer/redoer any time to see which it is."
- 
- 	^UndoParagraph == #undoing!

Item was changed:
  ----- Method: TextEditor>>keyStroke: (in category 'events') -----
  keyStroke: anEvent
   	self resetTypeAhead; deselect.
+ 
  	(self dispatchOnKeyboardEvent: anEvent) 
+ 		ifTrue: [
+ 			self closeTypeIn.
- 		ifTrue:
- 			[self doneTyping.
  			self storeSelectionInParagraph.
  			^self].
+ 
  	self openTypeIn.
- 	self hasSelection ifTrue: [ "save highlighted characters"
- 		UndoSelection := self selection].
  	self 
+ 		zapSelectionWith: self typeAhead contents; 
+ 		resetTypeAhead;
+ 		unselect;
+ 		storeSelectionInParagraph.!
- 		zapSelectionWith: self typeAhead contents ; 
- 		resetTypeAhead ;
- 		unselect ;
- 		storeSelectionInParagraph!

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

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

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

Item was added:
+ ----- Method: TextEditor>>openTypeInFor: (in category 'typing support') -----
+ openTypeInFor: editType
+ 	"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: [
+ 		beginTypeInIndex := self startIndex.
+ 		self history beginRemember: (TextEditorCommand new
+ 			type: editType;
+ 			contentsBefore: (self hasSelection ifTrue: [self selection] ifFalse: [self nullText]);
+ 			intervalBefore: (beginTypeInIndex to: self stopIndex-1)
+ 			yourself)].!

Item was added:
+ ----- Method: TextEditor>>paste (in category 'menu messages') -----
+ paste
+ 	"Update command history."
+ 	
+ 	self openTypeIn.
+ 	super paste.
+ 	self closeTypeIn.!

Item was changed:
  ----- Method: TextEditor>>querySymbol: (in category 'typing/selecting keys') -----
  querySymbol: aKeyboardEvent
+ 	"Invoked by Ctrl-q to query the Symbol table and display alternate symbols."
- 	"Invoked by Ctrl-q to query the Symbol table and display alternate symbols.
- 	 See comment in completeSymbol:lastOffering: for details."
  
+ 	| hintText lastOffering offering |
+ 	self isTypingIn
+ 		ifFalse: [
+ 			self selectPrecedingIdentifier.
+ 			hintText := self selection string]
+ 		ifTrue: [
+ 			self history current type = #query
+ 				ifFalse: [
+ 					self closeTypeIn.
+ 					self selectPrecedingIdentifier.
+ 					hintText := self selection string]
+ 				ifTrue: [		
+ 					self history hasPrevious
+ 						ifFalse: [morph flash. self closeTypeIn. ^ true].
+ 					
+ 					hintText := self history previous contentsAfter string.
+ 					hintText := hintText copyFrom: (hintText
+ 						lastIndexOfAnyOf: Character separators, #($#)
+ 						startingAt: hintText size ifAbsent: [0])+1 to: hintText size.
+ 					
+ 					self selectPrecedingIdentifier.
+ 					lastOffering := self selection string]].
+ 	
+ 	offering := '-'.
+ 	[offering allSatisfy: [:ea | ea tokenish]] whileFalse: [
+ 		offering := (Symbol thatStarts: hintText skipping: lastOffering) ifNil: [hintText].
+ 		lastOffering := offering].
+ 
+ 	self openTypeInFor: #query.
+ 	self typeAhead nextPutAll: offering.
+ 
+ 	^ false!
- 	self insertAndCloseTypeIn.
- 	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 added:
+ ----- Method: TextEditor>>redo (in category 'menu messages') -----
+ redo
+ 
+ 	self closeTypeIn.
+ 	self history redoIn: self.!

Item was added:
+ ----- Method: TextEditor>>redo: (in category 'editing keys') -----
+ redo: aKeyboardEvent 
+ 	"Redo the last edit."
+ 
+ 	self insertAndCloseTypeIn.
+ 	self redo.
+ 	^true!

Item was added:
+ ----- Method: TextEditor>>redoAndReselect (in category 'undoers') -----
+ redoAndReselect
+ 
+ 	self
+ 		replace: self history current intervalBefore
+ 		with: self history current contentsAfter
+ 		and: [self selectInterval: self history current intervalAfter].!

Item was added:
+ ----- Method: TextEditor>>replace:with: (in category 'accessing') -----
+ replace: interval with: newText
+ 
+ 	self
+ 		replace: interval
+ 		with: newText
+ 		and: ["Do nothing."].!

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

Item was changed:
  ----- Method: TextEditor>>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."
  
+ 	self openTypeIn.
- 	beginTypeInIndex ifNotNil: [^self zapSelectionWith: aText]. "called from old code"
- 	UndoSelection := self selection.
  	self zapSelectionWith: aText.
+ 	self closeTypeIn.!
- 	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.
+ 	otherInterval := 1 to: 0.
- 	UndoInterval := otherInterval := 1 to: 0.
  	self setEmphasisHere.
  	selectionShowing := false!

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

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

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

Item was changed:
  ----- Method: TextEditor>>stateArray (in category 'initialize-release') -----
  stateArray
  	^ {ChangeText.
  		FindText.
+ 		history ifNil: [TextEditorCommandHistory new]. "Convert old instances"
- 		UndoInterval.
- 		UndoMessage.
- 		UndoParagraph.
- 		UndoSelection.
- 		Undone.
  		self selectionInterval.
  		self startOfTyping.
  		emphasisHere}!

Item was changed:
  ----- Method: TextEditor>>stateArrayPut: (in category 'initialize-release') -----
  stateArrayPut: stateArray
  	| sel |
  	ChangeText := stateArray at: 1.
  	FindText := stateArray at: 2.
+ 	history := stateArray at: 3.
+ 	sel := stateArray at: 4.
- 	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: 5.
+ 	emphasisHere := stateArray at: 6!
- 	beginTypeInIndex := stateArray at: 9.
- 	emphasisHere := stateArray at: 10!

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."
  
  	self closeTypeIn.
+ 	self history undoIn: self.
+ 	self history hasPrevious ifFalse: [morph hasUnacceptedEdits: false].!
- 
- 	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].
- 
- 	"Leave a signal of which phase is in progress"
- 	UndoParagraph := Undone ifTrue: [#redoing] ifFalse: [#undoing].
- 	UndoMessage sentTo: self.
- 	UndoParagraph := paragraph!

Item was removed:
- ----- Method: TextEditor>>undoAgain:andReselect:typedKey: (in category 'undoers') -----
- undoAgain: indices andReselect: home typedKey: wasTypedKey
- 	"The last command was again.  Undo it. Redoer: itself."
- 
- 	| findSize substText |
- 	(self isRedoing & wasTypedKey) ifTrue: "redelete search key"
- 		[self selectInterval: home.
- 		self zapSelectionWith: self nullText].
- 
- 	findSize := (self isRedoing ifTrue: [FindText] ifFalse: [ChangeText]) size.
- 	substText := self isUndoing ifTrue: [FindText] ifFalse: [ChangeText].
- 	(self isUndoing ifTrue: [indices size to: 1 by: -1] ifFalse: [1 to: indices size]) do:
- 		[:i |
- 		| index subject |
- 		index := indices at: i.
- 		(subject := index to: index + findSize - 1) = self selectionInterval ifFalse:
- 			[self selectInterval: subject].
- 		FindText == ChangeText ifFalse: [self zapSelectionWith: substText]].
- 
- 	self isUndoing
- 		ifTrue:  "restore selection to where it was when 'again' was invoked"
- 			[wasTypedKey
- 				ifTrue: "search started by typing key at a caret; restore it"
- 					[self selectAt: home first.
- 					self zapSelectionWith: FindText.
- 					self selectAt: home last + 1]
- 				ifFalse: [self selectInterval: home]].
- 
- 	self undoMessage: UndoMessage forRedo: self isUndoing!

Item was added:
+ ----- Method: TextEditor>>undoAndReselect (in category 'undoers') -----
+ undoAndReselect
+ 
+ 	self
+ 		replace: self history current intervalBetween
+ 		with: self history current contentsBefore
+ 		and: [self selectInterval: self history current intervalBefore].!

Item was removed:
- ----- Method: TextEditor>>undoAndReselect:redoAndReselect: (in category 'undoers') -----
- undoAndReselect: undoHighlight redoAndReselect: redoHighlight
- 	"Undo typing, cancel, paste, and other operations that are like replaces
- 	 but the selection is not the whole restored text after undo, redo, or both.
- 	 undoHighlight is selected after this phase and redoHighlight after the next phase.
- 	Redoer: itself."
- 
- 	self replace: self selectionInterval with: UndoSelection and:
- 		[self selectInterval: undoHighlight].
- 	self undoMessage: (UndoMessage argument: redoHighlight) forRedo: self isUndoing
- !

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

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

Item was removed:
- ----- Method: TextEditor>>undoQuery:lastOffering: (in category 'undoers') -----
- undoQuery: hintText lastOffering: selectorOrNil
- 	"Undo ctrl-q.  selectorOrNil (if not nil) is the previously offered selector.
- 	 hintText is the original hint.  Redoer: completeSymbol."
- 
- 	self zapSelectionWith: UndoSelection.
- 	self undoMessage: (Message selector: #completeSymbol:lastOffering: arguments: UndoMessage arguments) forRedo: true.
- 	self selectAt: self stopIndex!

Item was removed:
- ----- Method: TextEditor>>undoReplace (in category 'undoers') -----
- undoReplace
- 	"Undo of any command that replaced a selection by other text that it left
- 	 highlighted, and that is undone and redone by simple reversal of the
- 	 operation.  This is the most common Undoer; call replaceSelectionWith:
- 	 to get this setup.  Redoer: itself, so never isRedoing."
- 
- 	self replaceSelectionWith: UndoSelection!

Item was removed:
- ----- Method: TextEditor>>undoer: (in category 'undo support') -----
- undoer: aSelector
- 	"See comment in undoMessage:.  Use this version when aSelector has no arguments, and you are doing or redoing and want to prepare for undoing."
- 
- 	self undoMessage: (Message selector: aSelector) forRedo: false!

Item was removed:
- ----- Method: TextEditor>>undoer:with: (in category 'undo support') -----
- undoer: aSelector with: arg1
- 	"See comment in undoMessage:.  Use this version when aSelector has one argument, and you are doing or redoing and want to prepare for undoing."
- 
- 	self undoMessage: (Message selector: aSelector argument: arg1) forRedo: false!

Item was removed:
- ----- Method: TextEditor>>undoer:with:with: (in category 'undo support') -----
- undoer: aSelector with: arg1 with: arg2
- 	"See comment in undoMessage:.  Use this version when aSelector has two arguments, and you are doing or redoing and want to prepare for undoing."
- 
- 	self undoMessage: (Message selector: aSelector arguments: (Array with: arg1 with: arg2)) forRedo: false!

Item was removed:
- ----- Method: TextEditor>>undoer:with:with:with: (in category 'undo support') -----
- undoer: aSelector with: arg1 with: arg2 with: arg3
- 	"See comment in undoMessage:.  Use this version when aSelector has three arguments, and you are doing or redoing and want to prepare for undoing."
- 
- 	self undoMessage: (Message selector: aSelector arguments: (Array with: arg1 with: arg2 with: arg3)) forRedo: false!

Item was changed:
  ----- Method: TextEditor>>zapSelectionWith: (in category 'mvc compatibility') -----
  zapSelectionWith: replacement
  
  	| start stop rep |
  	morph readOnly ifTrue: [^ self].
  	self deselect.
  	start := self startIndex.
  	stop := self stopIndex.
  	(replacement 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.
+ 		otherInterval := self selectionInterval].
- 		UndoInterval := otherInterval := self selectionInterval].
  
  	self userHasEdited  " -- note text now dirty"!

Item was added:
+ Object subclass: #TextEditorCommand
+ 	instanceVariableNames: 'interval message paragraph selection contentsBefore contentsAfter intervalBefore intervalAfter valid messageToUndo messageToRedo intervalBetween type isCompositeUndo isCompositeRedo'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Text Support'!

Item was added:
+ ----- Method: TextEditorCommand>>contentsAfter (in category 'accessing') -----
+ contentsAfter
+ 
+ 	^ contentsAfter!

Item was added:
+ ----- Method: TextEditorCommand>>contentsAfter: (in category 'accessing') -----
+ contentsAfter: anObject
+ 
+ 	contentsAfter := anObject!

Item was added:
+ ----- Method: TextEditorCommand>>contentsBefore (in category 'accessing') -----
+ contentsBefore
+ 
+ 	^ contentsBefore!

Item was added:
+ ----- Method: TextEditorCommand>>contentsBefore: (in category 'accessing') -----
+ contentsBefore: anObject
+ 
+ 	contentsBefore := anObject!

Item was added:
+ ----- Method: TextEditorCommand>>hasReplacedSomething (in category 'testing') -----
+ hasReplacedSomething
+ 
+ 	^ self contentsBefore size > 0!

Item was added:
+ ----- Method: TextEditorCommand>>intervalAfter (in category 'accessing') -----
+ intervalAfter
+ 
+ 	^ intervalAfter!

Item was added:
+ ----- Method: TextEditorCommand>>intervalAfter: (in category 'accessing') -----
+ intervalAfter: anObject
+ 
+ 	intervalAfter := anObject!

Item was added:
+ ----- Method: TextEditorCommand>>intervalBefore (in category 'accessing') -----
+ intervalBefore
+ 
+ 	^ intervalBefore!

Item was added:
+ ----- Method: TextEditorCommand>>intervalBefore: (in category 'accessing') -----
+ intervalBefore: anObject
+ 
+ 	intervalBefore := anObject!

Item was added:
+ ----- Method: TextEditorCommand>>intervalBetween (in category 'accessing') -----
+ intervalBetween
+ 
+ 	^ intervalBetween!

Item was added:
+ ----- Method: TextEditorCommand>>intervalBetween: (in category 'accessing') -----
+ intervalBetween: anObject
+ 
+ 	intervalBetween := anObject!

Item was added:
+ ----- Method: TextEditorCommand>>isCompositeRedo (in category 'accessing') -----
+ isCompositeRedo
+ 
+ 	^ isCompositeRedo!

Item was added:
+ ----- Method: TextEditorCommand>>isCompositeRedo: (in category 'accessing') -----
+ isCompositeRedo: boolean
+ 
+ 	isCompositeRedo := boolean.!

Item was added:
+ ----- Method: TextEditorCommand>>isCompositeUndo (in category 'accessing') -----
+ isCompositeUndo
+ 
+ 	^ isCompositeUndo!

Item was added:
+ ----- Method: TextEditorCommand>>isCompositeUndo: (in category 'accessing') -----
+ isCompositeUndo: boolean
+ 
+ 	isCompositeUndo := boolean.!

Item was added:
+ ----- Method: TextEditorCommand>>messageToRedo (in category 'accessing') -----
+ messageToRedo
+ 	^ messageToRedo!

Item was added:
+ ----- Method: TextEditorCommand>>messageToRedo: (in category 'accessing') -----
+ messageToRedo: msg
+ 	messageToRedo := msg.!

Item was added:
+ ----- Method: TextEditorCommand>>messageToUndo (in category 'accessing') -----
+ messageToUndo
+ 	^ messageToUndo!

Item was added:
+ ----- Method: TextEditorCommand>>messageToUndo: (in category 'accessing') -----
+ messageToUndo: msg
+ 	messageToUndo := msg.!

Item was added:
+ ----- Method: TextEditorCommand>>postCopy (in category 'copying') -----
+ postCopy
+ 
+ 	super postCopy.
+ 	
+ 	contentsAfter := contentsAfter copy.
+ 	contentsBefore := contentsBefore copy.
+ 	intervalAfter := intervalAfter copy.
+ 	intervalBefore := intervalBefore copy.
+ 	intervalBetween := intervalBetween copy.
+ 
+ 	messageToUndo := messageToUndo copy.
+ 	messageToRedo := messageToRedo copy.!

Item was added:
+ ----- Method: TextEditorCommand>>redoIn: (in category 'undo/redo') -----
+ redoIn: editor
+ 
+ 	self messageToRedo sendTo: editor.!

Item was added:
+ ----- Method: TextEditorCommand>>type (in category 'accessing') -----
+ type
+ 
+ 	^ type!

Item was added:
+ ----- Method: TextEditorCommand>>type: (in category 'accessing') -----
+ type: symbol
+ 
+ 	type := symbol.!

Item was added:
+ ----- Method: TextEditorCommand>>undoIn: (in category 'undo/redo') -----
+ undoIn: editor
+ 
+ 	self messageToUndo sendTo: editor.!

Item was added:
+ Object subclass: #TextEditorCommandHistory
+ 	instanceVariableNames: 'commands currentIndex'
+ 	classVariableNames: 'MaximumTextHistoryDepth'
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Text Support'!

Item was added:
+ ----- Method: TextEditorCommandHistory class>>maximumTextHistoryDepth (in category 'preferences') -----
+ maximumTextHistoryDepth
+ 	<preference: 'Maximum text edit (undo/redo) history depth'
+ 		categoryList:  #(editing Morphic)
+ 		description: 'Specifies the number of editor commands that will be stored in a text editor'
+ 		type: #Number>
+ 	^ MaximumTextHistoryDepth ifNil: [500]!

Item was added:
+ ----- Method: TextEditorCommandHistory class>>maximumTextHistoryDepth: (in category 'preferences') -----
+ maximumTextHistoryDepth: number
+ 
+ 	MaximumTextHistoryDepth := number.!

Item was added:
+ ----- Method: TextEditorCommandHistory>>beginRemember: (in category 'undo/redo') -----
+ beginRemember: command
+ 
+ 	commands := commands
+ 		copyFrom: (1 max: (currentIndex + 2 - self class maximumTextHistoryDepth))
+ 		to: (currentIndex min: commands size).
+ 	commands := commands, {command}.
+ 	currentIndex := commands size - 1. "Select the new command."!

Item was added:
+ ----- Method: TextEditorCommandHistory>>current (in category 'accessing') -----
+ current
+ 
+ 	^ self next!

Item was added:
+ ----- Method: TextEditorCommandHistory>>detect: (in category 'enumeration') -----
+ detect: block
+ 
+ 	self do: [:command |
+ 		(block value: command) ifTrue: [^ command]].
+ 	^ nil!

Item was added:
+ ----- Method: TextEditorCommandHistory>>do: (in category 'enumeration') -----
+ do: block
+ 
+ 	((currentIndex min: commands size) to: 1 by: -1)
+ 		do: [:i | block value: (commands at: i)].!

Item was added:
+ ----- Method: TextEditorCommandHistory>>finishRemember (in category 'undo/redo') -----
+ finishRemember
+ 
+ 	currentIndex := commands size.!

Item was added:
+ ----- Method: TextEditorCommandHistory>>hasNext (in category 'accessing') -----
+ hasNext
+ 
+ 	^ currentIndex < commands size!

Item was added:
+ ----- Method: TextEditorCommandHistory>>hasPrevious (in category 'accessing') -----
+ hasPrevious
+ 
+ 	^ currentIndex > 0!

Item was added:
+ ----- Method: TextEditorCommandHistory>>initialize (in category 'initialization') -----
+ initialize
+ 
+ 	super initialize.
+ 	self reset.!

Item was added:
+ ----- Method: TextEditorCommandHistory>>next (in category 'accessing') -----
+ next
+ 
+ 	^ self hasNext
+ 		ifTrue: [commands at: currentIndex+1]
+ 		ifFalse: [nil]!

Item was added:
+ ----- Method: TextEditorCommandHistory>>previous (in category 'accessing') -----
+ previous
+ 
+ 	^ self hasPrevious
+ 		ifTrue: [commands at: currentIndex]
+ 		ifFalse: [nil]!

Item was added:
+ ----- Method: TextEditorCommandHistory>>redoIn: (in category 'undo/redo') -----
+ redoIn: editor
+ 
+ 	self hasNext ifFalse: [^ self].
+ 	
+ 	[self current redoIn: editor]
+ 		ensure: [currentIndex := currentIndex + 1].
+ 
+ 	self previous isCompositeRedo == true ifTrue: [self redoIn: editor].!

Item was added:
+ ----- Method: TextEditorCommandHistory>>reset (in category 'initialization') -----
+ reset
+ 
+ 	commands := #().
+ 	currentIndex := 0.!

Item was added:
+ ----- Method: TextEditorCommandHistory>>undoIn: (in category 'undo/redo') -----
+ undoIn: editor
+ 
+ 	self hasPrevious ifFalse: [^ self].
+ 	
+ 	currentIndex := currentIndex - 1.
+ 	self current undoIn: editor.
+ 
+ 	self current isCompositeUndo == true ifTrue: [self undoIn: editor].!

Item was added:
+ ----- Method: TextMorph class>>cleanUp (in category 'class initialization') -----
+ cleanUp
+ 
+ 	TextMorph allSubInstancesDo: [:m | m releaseEditor].!

Item was changed:
  ----- Method: TextMorph>>installEditorToReplace: (in category 'private') -----
  installEditorToReplace: priorEditor
  	"Install an editor for my paragraph.  This constitutes 'hasFocus'.
  	If priorEditor is not nil, then initialize the new editor from its state.
  	We may want to rework this so it actually uses the prior editor."
  
  	| stateArray |
  	priorEditor ifNotNil: [stateArray := priorEditor stateArray].
  	editor := self editorClass new morph: self.
  	editor changeParagraph: self paragraph.
+ 	priorEditor
+ 		ifNil: [editor history: TextEditorCommandHistory new]
+ 		ifNotNil: [editor stateArrayPut: stateArray].
- 	priorEditor ifNotNil: [editor stateArrayPut: stateArray].
  	self selectionChanged.
  	^ editor!



More information about the Squeak-dev mailing list