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

commits at source.squeak.org commits at source.squeak.org
Mon Apr 27 13:39:05 UTC 2015


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

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

Name: Morphic-mt.938
Author: mt
Time: 27 April 2015, 3:38:24.714 pm
UUID: 54d200a1-ca2b-7841-a2cc-fa479a95d42e
Ancestors: Morphic-dtl.937

Fixed text morphs to honor "autoFit but no wrapping" by resizing whenever text is modified. This added check for #isAutoFit at a critical place. Thus I converted its state to an instVar (was a morph property).

Now, we can turn-off soft line wraps in the whole image if we want to. Added a preference for that.

This commit includes a fix in adjustRightX in paragraph to consider the caret width, which would otherwise be invisible and the edge.

=============== Diff against Morphic-dtl.937 ===============

Item was changed:
  ----- Method: NewParagraph>>adjustRightX (in category 'private') -----
  adjustRightX
  	| shrink |
  	shrink := container right - maxRightX.
  	lines do: [:line | line paddingWidth: (line paddingWidth - shrink)].
+ 	container := container withRight: maxRightX + self caretWidth.!
- 	container := container withRight: maxRightX!

Item was changed:
  ----- Method: NewParagraph>>caretWidth (in category 'access') -----
  caretWidth
  	^ Editor dumbbellCursor
+ 		ifTrue: [ 3 ]
+ 		ifFalse: [ 1 ]!
- 		ifTrue: [ 2 ]
- 		ifFalse: [ 0 ]!

Item was changed:
  ----- Method: NewParagraph>>displaySelectionInLine:on: (in category 'display') -----
  displaySelectionInLine: line on: aCanvas 
  	| leftX rightX w caretColor |
  	selectionStart ifNil: [^self].	"No selection"
  	aCanvas isShadowDrawing ifTrue: [ ^self ].	"don't draw selection with shadow"
  	selectionStart = selectionStop 
  		ifTrue: 
  			["Only show caret on line where clicked"
  
  			selectionStart textLine ~= line ifTrue: [^self]]
  		ifFalse: 
  			["Test entire selection before or after here"
  
  			(selectionStop stringIndex < line first 
  				or: [selectionStart stringIndex > (line last + 1)]) ifTrue: [^self].	"No selection on this line"
  			(selectionStop stringIndex = line first 
  				and: [selectionStop textLine ~= line]) ifTrue: [^self].	"Selection ends on line above"
  			(selectionStart stringIndex = (line last + 1) 
  				and: [selectionStop textLine ~= line]) ifTrue: [^self]].	"Selection begins on line below"
  	leftX := (selectionStart stringIndex < line first 
  				ifTrue: [line ]
  				ifFalse: [selectionStart ])left.
  	rightX := (selectionStop stringIndex > (line last + 1) or: 
  					[selectionStop stringIndex = (line last + 1) 
  						and: [selectionStop textLine ~= line]]) 
  				ifTrue: [line right]
  				ifFalse: [selectionStop left].
  	selectionStart = selectionStop 
  		ifTrue: 
  			[rightX := rightX + 1.
+ 			w := self caretWidth-1.
- 			w := self caretWidth.
  			caretRect := (leftX-w) @ line top corner: (rightX+w)@ line bottom.
  			self showCaret ifFalse:[^self].
  			caretColor := self insertionPointColor.
  			1 to: w
  				do: 
  					[:i | 
  					"Draw caret triangles at top and bottom"
  
  					aCanvas fillRectangle: ((leftX - w + i - 1) @ (line top + i - 1) 
  								extent: ((w - i) * 2 + 3) @ 1)
  						color: caretColor.
  					aCanvas fillRectangle: ((leftX - w + i - 1) @ (line bottom - i) 
  								extent: ((w - i) * 2 + 3) @ 1)
  						color: caretColor].
  			aCanvas fillRectangle: (leftX @ line top corner: rightX @ line bottom)
  				color: caretColor]
  		ifFalse: 
  			[caretRect := nil.
  			aCanvas fillRectangle: (leftX @ line top corner: rightX @ line bottom)
  				color: self selectionColor]!

Item was changed:
  ScrollPane subclass: #PluggableTextMorph
  	instanceVariableNames: 'textMorph getTextSelector setTextSelector getSelectionSelector hasUnacceptedEdits askBeforeDiscardingEdits selectionInterval hasEditingConflicts editTextSelector'
+ 	classVariableNames: 'AdornmentCache SimpleFrameAdornments SoftLineWrap'
- 	classVariableNames: 'AdornmentCache SimpleFrameAdornments'
  	poolDictionaries: ''
  	category: 'Morphic-Pluggable Widgets'!

Item was added:
+ ----- Method: PluggableTextMorph class>>softLineWrap (in category 'preferences') -----
+ softLineWrap
+ 	<preference: 'Use soft line wrap'
+ 		categoryList: #(scrolling editing)
+ 		description: 'Wrap text lines to avoid horizontal scrolling.'
+ 		type: #Boolean>
+ 	^ SoftLineWrap ifNil: [true]!

Item was added:
+ ----- Method: PluggableTextMorph class>>softLineWrap: (in category 'preferences') -----
+ softLineWrap: aBoolean
+ 
+ 	aBoolean == SoftLineWrap ifTrue: [^ self].
+ 	SoftLineWrap := aBoolean.
+ 	PluggableTextMorph allSubInstancesDo: [:m |
+ 		m text lineCount > 1 ifTrue: [m wrapFlag: aBoolean]].!

Item was changed:
  ----- Method: PluggableTextMorph>>isAutoFit (in category 'accessing') -----
  isAutoFit
+ 	"Whether I adjust the contents of my scroller to save a scroll bar."
+ 	
+ 	^ self wrapFlag!
- 
- 	^ textMorph notNil and: [textMorph isAutoFit]!

Item was changed:
+ ----- Method: PluggableTextMorph>>isWrapped (in category 'testing') -----
- ----- Method: PluggableTextMorph>>isWrapped (in category 'model access') -----
  isWrapped
  
+ 	^ self wrapFlag!
- 	^ textMorph isWrapped!

Item was changed:
  ----- Method: PluggableTextMorph>>resizeScroller (in category 'geometry') -----
  resizeScroller
  	"Also needs to resize the text morph"
  
  	super resizeScroller.
  
  	textMorph ifNotNil: [:tm |
+ 		tm isWrapped ifTrue: [textMorph extent: self scroller extent]].!
- 		tm isAutoFit ifTrue: [textMorph extent: self scroller extent]].!

Item was changed:
  ----- Method: PluggableTextMorph>>setText: (in category 'model access') -----
  setText: aText
  	textMorph
  		ifNil: [textMorph := self textMorphClass new
  					contents: aText
  					wrappedTo: self innerBounds width.
  				textMorph
  					margins: (3 at 0 corner: 0 at 0);
  					setEditView: self;
+ 					autoFit: true;
  					setProperty: #indicateKeyboardFocus toValue: #never.
  				scroller addMorph: textMorph.
  				"Reset minExtent because only now we can anser #isAutoFit correctly."
  				self minimumExtent: 0 at 0; updateMinimumExtent]
  		ifNotNil: [textMorph newContents: aText].
  	self hasUnacceptedEdits: false.
  	self setScrollDeltas.!

Item was added:
+ ----- Method: PluggableTextMorph>>wrapFlag (in category 'accessing') -----
+ wrapFlag
+ 
+ 	^ textMorph ifNil: [false] ifNotNil: [:tm | tm isWrapped]!

Item was changed:
+ ----- Method: PluggableTextMorph>>wrapFlag: (in category 'accessing') -----
- ----- Method: PluggableTextMorph>>wrapFlag: (in category 'model access') -----
  wrapFlag: aBoolean
  
+ 	textMorph ifNil: [self setText: ''].
+ 	textMorph
+ 		wrapFlag: aBoolean;
+ 		autoFit: true.
+ 	
+ 	"Text navigation will be tedious if there is no horizontal scroll bar w/o wrapping."
+ 	aBoolean ifFalse: [self showHScrollBarOnlyWhenNeeded].
+ 
+ 	self
+ 		resizeScrollBars;
+ 		resizeScroller;
+ 		hideOrShowScrollBars;
+ 		setScrollDeltas.!
- 	textMorph wrapFlag: aBoolean!

Item was changed:
  RectangleMorph subclass: #TextMorph
+ 	instanceVariableNames: 'textStyle text wrapFlag paragraph editor container predecessor successor backgroundColor margins editHistory readOnly autoFit'
- 	instanceVariableNames: 'textStyle text wrapFlag paragraph editor container predecessor successor backgroundColor margins editHistory readOnly'
  	classVariableNames: 'CaretForm DefaultEditorClass'
  	poolDictionaries: ''
  	category: 'Morphic-Basic'!
  
  !TextMorph commentStamp: 'nice 3/24/2010 07:40' prior: 0!
  TextMorphs support display of text with emphasis.  They also support reasonable text-editing capabilities, as well as embedded hot links, and the ability to embed submorphs in the text.
  
  Late in life, TextMorph was made a subclass of BorderedMorph to provide border and background color if desired.  In order to keep things compatible, protocols have been redirected so that color (preferably textColor) relates to the text, and backgroundColor relates to the inner fill color.
  
  Text display is clipped to the innerBounds of the rectangle, and text composition is normally performed within a rectangle which is innerBounds inset by the margins parameter.
  
  If text has been embedded in another object, one can elect to fill the owner's shape, in which case the text will be laid out in the shape of the owner's shadow image (including any submorphs other than the text).  One can also elect to have the text avoid occlusions, in which case it will avoid the bounds of any sibling morphs that appear in front of it.  It may be necessary to update bounds in order for the text runaround to notice the presence of a new occluding shape.
  
  The optional autoFitContents property enables the following feature:  if the text contents changes, then the bounds of the morph will be adjusted to fit the minimum rectangle that encloses the text (plus any margins specified).  Similarly, any attempt to change the size of the morph will be resisted if this parameter is set.  Except...
  
  If the wrapFlag parameter is true, then text will be wrapped at word boundaries based on the composition width (innerBounds insetBy: margins) width.  Thus an attempt to resize the morph in autofit mode, if it changes the width, will cause the text to be recomposed with the new width, and then the bounds will be reset to the minimum enclosing rectangle.  Similarly, if the text contents are changed with the wrapFlag set to true, word wrap will be performed based on the current compostion width, after which the bounds will be set (or not), based on the autoFitcontents property.
  
  Note that fonts can only be applied to the TextMorph as a whole.  While you can change the size, color, and emphasis of a subsection of the text and have it apply to only that subsection, changing the font changes the font for the entire contents of the TextMorph. 
  
  Still a TextMorph can be composed of several texts of different fonts
  | font1 font2 t1 t2 tMorph|
  tMorph := TextMorph new.
  font1 := (TextFontReference toFont: (StrikeFont familyName: 'Atlanta' size: 22)).
  font2 := (TextFontReference toFont: (StrikeFont familyName: 'Atlanta' size: 11)).
  t1 := 'this is font1' asText addAttribute: font1.
  t2 := ' and this is font2' asText addAttribute: font2.
  tMorph contents: (t1,t2).
  tMorph openInHand.
  
  
  Yet to do:
  Make a comprehensive control for the eyedropper, with border width and color, inner color and text color, and margin widths.!

Item was changed:
  ----- Method: TextMorph>>autoFitOnOff (in category 'menu') -----
  autoFitOnOff
+ 	autoFit := self isAutoFit not.
- 	self setProperty: #autoFitContents toValue: self isAutoFit not.
  	self isAutoFit ifTrue: [self fit]!

Item was changed:
  ----- Method: TextMorph>>isAutoFit (in category 'accessing') -----
  isAutoFit
+ 	"Migrating old instances. The #isNil check may be removed in the future."
+ 	^ autoFit isNil or: [autoFit]!
- 	^ self valueOfProperty: #autoFitContents ifAbsent: [true]
- !

Item was changed:
  ----- Method: TextMorph>>updateFromParagraph (in category 'private') -----
  updateFromParagraph
  	"A change has taken place in my paragraph, as a result of editing and I must be updated.  If a line break causes recomposition of the current paragraph, or it the selection has entered a different paragraph, then the current editor will be released, and must be reinstalled with the resulting new paragraph, while retaining any editor state, such as selection, undo state, and current typing emphasis."
  
  	| newStyle sel oldLast oldEditor back |
  	paragraph ifNil: [^self].
  	wrapFlag ifNil: [wrapFlag := true].
  	editor ifNotNil: 
  			[oldEditor := editor.
  			sel := editor selectionInterval.
  			editor storeSelectionInParagraph].
  	text := paragraph text.
  	paragraph textStyle = textStyle 
  		ifTrue: [self fit]
  		ifFalse: 
  			["Broadcast style changes to all morphs"
  
  			newStyle := paragraph textStyle.
  			(self firstInChain text: text textStyle: newStyle) recomposeChain.
  			editor ifNotNil: [self installEditorToReplace: editor]].
+ 	
+ 	(self isAutoFit and: [self isWrapped not])
+ 		ifTrue: [self extent: self paragraph extent; composeToBounds]
+ 		ifFalse: [super layoutChanged].
- 	super layoutChanged.
  	sel ifNil: [^self].
  
  	"If selection is in top line, then recompose predecessor for possible ripple-back"
  	predecessor ifNotNil: 
  			[sel first <= (self paragraph lines first last + 1) 
  				ifTrue: 
  					[oldLast := predecessor lastCharacterIndex.
  					predecessor paragraph 
  						recomposeFrom: oldLast
  						to: text size
  						delta: 0.
  					oldLast = predecessor lastCharacterIndex 
  						ifFalse: 
  							[predecessor changed.	"really only last line"
  							self predecessorChanged]]].
  	((back := predecessor notNil 
  				and: [sel first <= self paragraph firstCharacterIndex]) or: 
  				[successor notNil 
  					and: [sel first > (self paragraph lastCharacterIndex + 1)]]) 
  		ifTrue: 
  			["The selection is no longer inside this paragraph.
  		Pass focus to the paragraph that should be in control."
  
  			back ifTrue: [predecessor recomposeChain] ifFalse: [self recomposeChain].
  			self firstInChain withSuccessorsDo: 
  					[:m | 
  					(sel first between: m firstCharacterIndex and: m lastCharacterIndex + 1) 
  						ifTrue: 
  							[m installEditorToReplace: oldEditor.
  							^self passKeyboardFocusTo: m]].
  			self error: 'Inconsistency in text editor'	"Must be somewhere in the successor chain"].
  	editor ifNil: 
  			["Reinstate selection after, eg, style change"
  
  			self installEditorToReplace: oldEditor].
  	"self setCompositionWindow."
  !



More information about the Squeak-dev mailing list