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

commits at source.squeak.org commits at source.squeak.org
Fri Apr 16 15:13:15 UTC 2021


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

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

Name: Morphic-mt.1752
Author: mt
Time: 16 April 2021, 5:13:09.752509 pm
UUID: cea50880-c57e-dc43-abdc-104a41e256e8
Ancestors: Morphic-mt.1751, Morphic-ct.1585, Morphic-ct.1586

Merges fixes and enhancements for TextEditor from Morphic-ct.1585, Morphic-ct.1586. 

Tweaks the proposed interactive print-it as follows:
- Make it a preference, ask for it during code loading
- Do not copy the (interactive) text action to avoid spreading object references (depends on Collections-mt.941)
- for the print-it text, append an extra space with the original emphasis to support type-in
- do not style obvious "store strings" such as strings and numbers

=============== Diff against Morphic-mt.1751 ===============

Item was changed:
  Editor subclass: #TextEditor
  	instanceVariableNames: 'model paragraph markBlock pointBlock beginTypeInIndex emphasisHere lastParenLocation otherInterval oldInterval typeAhead history'
+ 	classVariableNames: 'AutoEnclose AutoIndent ChangeText EncloseSelection FindText InteractivePrintIt'
- 	classVariableNames: 'AutoEnclose AutoIndent ChangeText EncloseSelection FindText'
  	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>>interactivePrintIt (in category 'preferences') -----
+ interactivePrintIt
+ 	<preference: 'Interactive print-it'
+ 		categoryList: #('Tools' 'Morphic')
+ 		description: 'When true, print-it styles the inserted printString to work as interactive link to an inspector. Just click on it.'
+ 		type: #Boolean>
+ 		
+ 	^ InteractivePrintIt ifNil: [ true ]!

Item was added:
+ ----- Method: TextEditor class>>interactivePrintIt: (in category 'preferences') -----
+ interactivePrintIt: aBoolean
+ 
+ 	InteractivePrintIt := aBoolean.!

Item was changed:
  ----- Method: TextEditor>>afterSelectionInsertAndSelect: (in category 'new selection') -----
+ afterSelectionInsertAndSelect: aStringOrText
- afterSelectionInsertAndSelect: aString
  
+ 	self insertAndSelect: aStringOrText at: self stopIndex !
- 	self insertAndSelect: aString at: self stopIndex !

Item was changed:
  ----- Method: TextEditor>>insertAndSelect:at: (in category 'new selection') -----
+ insertAndSelect: aStringOrText at: anInteger
- insertAndSelect: aString at: anInteger
  
+ 	| spacer |
  	self closeTypeIn.
- 	
  	self selectInvisiblyFrom: anInteger to: anInteger - 1.
  	self openTypeIn.
  
+ 	spacer := Text string: ' ' attributes: emphasisHere.
+ 
  	self
  		replace: self selectionInterval
+ 		with: (aStringOrText isString
+ 			ifTrue: [spacer, (Text string: aStringOrText attributes: emphasisHere)]
+ 			ifFalse: [spacer, aStringOrText, spacer "Extra spacer for type-in after insertion with current emphasis."])
- 		with: (Text string: (' ', aString) attributes: emphasisHere)
  		and: [].
- 
  	self closeTypeIn.!

Item was changed:
  ----- Method: TextEditor>>mouseDown: (in category 'events') -----
  mouseDown: evt 
  	"Either 1) handle text actions in the paragraph, 2) begin a text drag operation, or 3) modify the caret/selection."
  	
  	| clickPoint b |
  
  	oldInterval := self selectionInterval.
  	clickPoint := evt cursorPoint.
  	b := paragraph characterBlockAtPoint: clickPoint.
  
  	(paragraph clickAt: clickPoint for: model controller: self) ifTrue: [
+ 		self flag: #note. "mt: Do not reset the current text selection for successful text actions. Leave markBlock and pointBlock as is. This behavior matches the one in web browsers when clicking on links."
- 		markBlock := b.
- 		pointBlock := b.
  		evt hand releaseKeyboardFocus: morph.
  		evt hand releaseMouseFocus: morph.
  		^ self ].
  	
  	(morph dragEnabled and: [self isEventInSelection: evt]) ifTrue: [
  		evt hand
  			waitForClicksOrDrag: morph
  			event: evt
  			selectors: {#click:. nil. nil. #startDrag:}
  			threshold: HandMorph dragThreshold.
  		morph setProperty: #waitingForTextDrag toValue: true.
  		^ self].
  	
  	evt shiftPressed
  		ifFalse: [
  			self closeTypeIn.
  			markBlock := b.
  			pointBlock := b ]
  		 ifTrue: [
  			self closeTypeIn.
  			self mouseMove: evt ].
         self storeSelectionInParagraph!

Item was changed:
  ----- Method: TextEditor>>printIt (in category 'do-its') -----
  printIt
  
  	self evaluateSelectionAndDo: [:result |
  		(model respondsTo: #printIt:result:)
  			ifTrue: [model
  				perform: #printIt:result:
  				with: self selection
  				with: result]
+ 			ifFalse: [self afterSelectionInsertAndSelect: (self printItTextFor: result)]]!
- 			ifFalse: [self afterSelectionInsertAndSelect: result printString]]!

Item was added:
+ ----- Method: TextEditor>>printItTextFor: (in category 'do-its') -----
+ printItTextFor: anObject
+ 
+ 	^ (self class interactivePrintIt and: [(anObject isString or: [anObject isNumber]) not])
+ 		ifFalse: [anObject printString]
+ 		ifTrue: [Text string: anObject printString attribute: (TextInspectIt on: anObject)]!

Item was changed:
  ----- Method: TextEditor>>selection (in category 'accessing-selection') -----
  selection
  	"Answer the text in the paragraph that is currently selected."
  
+ 	| result |
+ 	result := paragraph text copyFrom: self startIndex to: self stopIndex - 1.
+ 	self class interactivePrintIt ifTrue: [
+ 		result removeAttributesThat: [:attr | attr isOblivious]].
+ 	^ result!
- 	^paragraph text copyFrom: self startIndex to: self stopIndex - 1 !

Item was changed:
+ (PackageInfo named: 'Morphic') postscript: 'TextEditor interactivePrintIt: (Project uiManager confirm: ''There is a new preference called "Interactive print-it".\\Do you want to enable it?'' withCRs).'!
- (PackageInfo named: 'Morphic') postscript: 'PasteUpMorph allSubInstancesDo: [:m | m isFlap ifTrue: [m morphicLayerNumber: Morph navigatorLayer]].
- TheWorldMainDockingBar updateInstances.
- SystemProgressMorph reset.
- self currentWorld reorderSubmorphsInLayers.'!



More information about the Squeak-dev mailing list