[Pkg] The Trunk: Morphic-eem.606.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jan 11 21:24:14 UTC 2012


Eliot Miranda uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-eem.606.mcz

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

Name: Morphic-eem.606
Author: eem
Time: 11 January 2012, 1:22:24.829 pm
UUID: 1685a14b-68f9-475f-9339-e84f6fc5601a
Ancestors: Morphic-laza.605

Nuke TextMorphEditor which is not used anymore and inherits
from ParagraphEditor (hence avoiding problems when
ParagraphEditor is unloaded as part of the ST80 package).

=============== Diff against Morphic-laza.605 ===============

Item was removed:
- ParagraphEditor subclass: #TextMorphEditor
- 	instanceVariableNames: 'morph oldInterval pivotBlock editHistory'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Text Support'!
- 
- !TextMorphEditor commentStamp: '<historical>' prior: 0!
- This is the ParagraphEditor for TextMorphs.
- 
- 
- 
- -----
- In the past, BookMorphs had the ability to have each page be on the server as a .sp SqueakPage file.  The index of the book was a .bo file.  In text, Cmd-6 had a LinkTo option that linked to a page by its name, or created a new page of that name.  It assumed the book was on a server with a file per page.  Ted removed that code, and kept a copy on his disk in 'TME-ChngEmphasis.st for .bo .sp'!

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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



More information about the Packages mailing list