#FEATURE by cg
authorClaus Gittinger <cg@exept.de>
Wed, 12 Oct 2016 20:09:17 +0200
changeset 5909 9895cf95cd00
parent 5908 8639f76963d4
child 5910 83afa19a39f7
#FEATURE by cg class: EditTextView added: #trimBlankLines #trimBlankLines: comment/format in: #st80Mode changed:7 methods category of: #st80EditMode decoupled st80editmode (cursor behavior) from trimming. trimming is on by default.
EditTextView.st
--- a/EditTextView.st	Wed Oct 12 19:46:22 2016 +0200
+++ b/EditTextView.st	Wed Oct 12 20:09:17 2016 +0200
@@ -486,7 +486,10 @@
 st80Mode
     "return true, if the st80 editing mode is turned on.
      This setting affects the behavior of the cursor, when positioned
-     beyond the end of a line or the end of the text."
+     beyond the end of a line or the end of the text.
+     This method is here for backward compatibility, when this flag was stored
+     in a class var. It is now in the user's settings.
+     Please do not call it, but go to the prefs directly, to make it easier to find those getters."
 
     ^ UserPreferences current st80EditMode
 
@@ -500,7 +503,10 @@
 
 st80Mode:aBoolean
     "turns on/off st80 behavior, where the cursor cannot be positioned
-     beyond the end of a line or the last line"
+     beyond the end of a line or the last line.
+     This method is here for backward compatibility, when this flag was stored
+     in a class var. It is now in the user's settings.
+     Please do not call it, but go to the prefs directly, to make it easier to find those setters."
 
     UserPreferences current st80EditMode:aBoolean.
 
@@ -1252,7 +1258,14 @@
     ^ self modifiedChannel
 !
 
-st80Mode:aBooleanOrNil
+st80EditMode
+    "If on, the cursor wraps at the line end (like in vi or st80);
+     if off, we have the Rand-editor behavior (random access)"
+
+    ^ st80Mode ? (UserPreferences current st80EditMode)
+!
+
+st80EditMode:aBooleanOrNil
     "set/clear the st80Mode flag.
      If on, the cursor wraps at the line end (like in vi or st80);
      if off, we have the Rand-editor behavior (random access)
@@ -1263,6 +1276,13 @@
     "Created: / 09-11-2010 / 13:55:50 / cg"
 !
 
+st80Mode:aBooleanOrNil
+    self obsoleteMethodWarning.
+    self st80EditMode:aBooleanOrNil
+
+    "Created: / 09-11-2010 / 13:55:50 / cg"
+!
+
 tabMeansNextField:aBoolean
     "set/clear tabbing to the next field.
      If true, Tab is ignored and shifts the keyboard focus.
@@ -1287,6 +1307,20 @@
      to allow for easier text entry"
 
     tabRequiresControl := aBoolean
+!
+
+trimBlankLines
+    "If on, the blank lines are trimmed to zero size;
+     if nil, the setting follows the current userPref setting."
+
+    ^ trimBlankLines ? (UserPreferences current trimBlankLines)
+!
+
+trimBlankLines:aBooleanOrNil
+    "If on, the blank lines are trimmed to zero size;
+     if nil, the setting follows the current userPref setting."
+
+    trimBlankLines := aBooleanOrNil.
 ! !
 
 !EditTextView methodsFor:'accessing-contents'!
@@ -4275,15 +4309,15 @@
     self unselect.
 
     cursorLine == lineNr ifTrue:[
-	cursorCol >= startCol ifTrue:[
-	    cursorCol >= endCol ifTrue:[
-		cursorCol := startCol.
-	    ] ifFalse:[
-		cursorCol := cursorCol - (endCol - startCol + 1).
-		"/ self assert:(cursorCol >= 0).
-		cursorCol := cursorCol max:1.
-	    ]
-	].
+        cursorCol >= startCol ifTrue:[
+            cursorCol >= endCol ifTrue:[
+                cursorCol := startCol.
+            ] ifFalse:[
+                cursorCol := cursorCol - (endCol - startCol + 1).
+                "/ self assert:(cursorCol >= 0).
+                cursorCol := cursorCol max:1.
+            ]
+        ].
     ].
 
     line := self listAt:lineNr.
@@ -4296,50 +4330,50 @@
     endCol > lineSize ifFalse:[ stop  := endCol ] ifTrue:[ stop  := lineSize ].
 
     stop >= start ifTrue:[
-	start ~~ 1 ifTrue:[ newLine := line copyFrom:1 to:(start-1) ]
-		  ifFalse:[ newLine := '' ].
-
-	stop == lineSize ifFalse:[
-	    line bitsPerCharacter > newLine bitsPerCharacter ifTrue:[
-		newLine := line string species fromString:newLine.
-	    ].
-	    newLine := newLine, (line copyFrom:(stop + 1) to:lineSize)
-	].
-
-	(trimBlankLines and:[newLine isBlank]) ifTrue:[
-	    newLine := nil
-	].
-
-	prevWidth := self widthOfLine:lineNr.
-
-	self basicListAt:lineNr put:newLine.
-
-	(prevWidth = widthOfWidestLine) ifTrue:[
-	    "/ remember old width of this line,
-	    "/ only clear widthOfWidestLine, if this lines
-	    "/ length was (one of) the longest.
-	    "/ avoids slow delete with huge texts.
-	    widthOfWidestLine := nil.   "i.e. unknown"
-
-	    "/ scroll left if reqiured
-	    viewOrigin x > 0 ifTrue:[
-		newWidth := self widthOfLine:lineNr.
-		newWidth < (viewOrigin x + width) ifTrue:[
-		    self scrollHorizontalTo:(newWidth
-					     - width
-					     + margin + margin
-					     + (gc font widthOf:'  '))
-		]
-	    ].
-	    self textChanged.
-	] ifFalse:[
-	    self textChanged "/ textChangedButNoSizeChange
-	].
-	gc font hasOverlappingCharacters ifTrue:[
-	    self invalidateLine:lineNr.
-	] ifFalse:[
-	    self redrawLine:lineNr from:start.
-	].
+        start ~~ 1 ifTrue:[ newLine := line copyFrom:1 to:(start-1) ]
+                  ifFalse:[ newLine := '' ].
+
+        stop == lineSize ifFalse:[
+            line bitsPerCharacter > newLine bitsPerCharacter ifTrue:[
+                newLine := line string species fromString:newLine.
+            ].
+            newLine := newLine, (line copyFrom:(stop + 1) to:lineSize)
+        ].
+
+        (self trimBlankLines and:[newLine isBlank]) ifTrue:[
+            newLine := nil
+        ].
+
+        prevWidth := self widthOfLine:lineNr.
+
+        self basicListAt:lineNr put:newLine.
+
+        (prevWidth = widthOfWidestLine) ifTrue:[
+            "/ remember old width of this line,
+            "/ only clear widthOfWidestLine, if this lines
+            "/ length was (one of) the longest.
+            "/ avoids slow delete with huge texts.
+            widthOfWidestLine := nil.   "i.e. unknown"
+
+            "/ scroll left if reqiured
+            viewOrigin x > 0 ifTrue:[
+                newWidth := self widthOfLine:lineNr.
+                newWidth < (viewOrigin x + width) ifTrue:[
+                    self scrollHorizontalTo:(newWidth
+                                             - width
+                                             + margin + margin
+                                             + (gc font widthOf:'  '))
+                ]
+            ].
+            self textChanged.
+        ] ifFalse:[
+            self textChanged "/ textChangedButNoSizeChange
+        ].
+        gc font hasOverlappingCharacters ifTrue:[
+            self invalidateLine:lineNr.
+        ] ifFalse:[
+            self redrawLine:lineNr from:start.
+        ].
     ].
 
     "Modified: / 09-11-2010 / 13:42:45 / cg"
@@ -4407,8 +4441,8 @@
     self checkModificationsAllowed ifFalse:[ ^ self].
 
     aCharacter == (Character cr) ifTrue:[
-	self splitLine:lineNr before:colNr.
-	^ self
+        self splitLine:lineNr before:colNr.
+        ^ self
     ].
 
     drawCharacterOnly := false.
@@ -4417,92 +4451,92 @@
     lineSize := line size.
 
     self st80EditMode ifFalse:[
-	(trimBlankLines
-	and:[colNr > lineSize
-	and:[aCharacter == Character space]]) ifTrue:[
-	    ^ self
-	]
+        (self trimBlankLines
+        and:[colNr > lineSize
+        and:[aCharacter == Character space]]) ifTrue:[
+            ^ self
+        ]
     ].
 
     (lineSize == 0) ifTrue:[
-	newLine := aCharacter asString species new:colNr.
-	drawCharacterOnly := true
+        newLine := aCharacter asString species new:colNr.
+        drawCharacterOnly := true
     ] ifFalse: [
-	(colNr > lineSize) ifTrue: [
-	    colNr == (lineSize +1) ifTrue:[
-		attribute := line emphasisAt:lineSize
-	    ].
-	    newLine := line species new:colNr.
-	    newLine replaceFrom:1 to:lineSize with:line startingAt:1.
-	    drawCharacterOnly := true
-	] ifFalse: [
-	    attribute := line emphasisAt:colNr.
-	    newLine   := line species new:(lineSize + 1).
-
-	    newLine replaceFrom:1 to:(colNr - 1) with:line startingAt:1.
-	    newLine replaceFrom:(colNr + 1) to:(lineSize + 1) with:line startingAt:colNr
-	]
+        (colNr > lineSize) ifTrue: [
+            colNr == (lineSize +1) ifTrue:[
+                attribute := line emphasisAt:lineSize
+            ].
+            newLine := line species new:colNr.
+            newLine replaceFrom:1 to:lineSize with:line startingAt:1.
+            drawCharacterOnly := true
+        ] ifFalse: [
+            attribute := line emphasisAt:colNr.
+            newLine   := line species new:(lineSize + 1).
+
+            newLine replaceFrom:1 to:(colNr - 1) with:line startingAt:1.
+            newLine replaceFrom:(colNr + 1) to:(lineSize + 1) with:line startingAt:colNr
+        ]
     ].
 
     aCharacter asString bitsPerCharacter > newLine bitsPerCharacter ifTrue:[
-	newLine := aCharacter asString species fromString:newLine.
-	line isText ifTrue:[
-	    newLine := newLine asText
-	]
+        newLine := aCharacter asString species fromString:newLine.
+        line isText ifTrue:[
+            newLine := newLine asText
+        ]
     ].
     newLine at:colNr put:aCharacter.
 
     attribute notNil ifTrue:[
-	newLine emphasisAt:colNr put:attribute.
+        newLine emphasisAt:colNr put:attribute.
     ].
 
     aCharacter == (Character tab) ifTrue:[
-	newLine := self withTabsExpanded:newLine.
-	drawCharacterOnly := false
+        newLine := self withTabsExpanded:newLine.
+        drawCharacterOnly := false
     ].
 
     self basicListAt:lineNr put:(newLine ifNil:[newLine] ifNotNil:[newLine asSingleByteStringIfPossible]).
     widthOfWidestLine notNil ifTrue:[
-	widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
     ].
     self textChanged.
     shown ifTrue:[
-	"/ care for italic text - in this case, we must also
-	"/ redraw the character before the insertion in order
-	"/ to fix the slanted piece of the character.
-	"/ (but we must clip, to avoid destoying the character before)
-	(newLine notNil and:[newLine isText]) ifTrue:[
-	    colNr > 1 ifTrue:[
-		cursorVisibleLine notNil ifTrue:[
-		    oldClip := self clippingRectangleOrNil.
-		    x := (self xOfCol:colNr-1 inVisibleLine:cursorVisibleLine) - viewOrigin x.
-		    y := self yOfVisibleLine:cursorVisibleLine.
-
-		    gc font hasOverlappingCharacters ifTrue:[
-			self invalidateLine:lineNr.
-		    ] ifFalse:[
-			drawCharacterOnly ifTrue:[
-			    self clippingRectangle:(x@y extent:((gc font width * 2) @ fontHeight)).
-			    self redrawLine:lineNr from:colNr-1 to:colNr
-			] ifFalse:[
-			    self clippingRectangle:(x@y extent:((width - x) @ fontHeight)).
-			    self redrawLine:lineNr from:colNr-1
-			].
-			self clippingRectangle:oldClip.
-		    ].
-		].
-		^ self.
-	    ].
-	].
-	gc font hasOverlappingCharacters ifTrue:[
-	    self invalidateLine:lineNr.
-	] ifFalse:[
-	    drawCharacterOnly ifTrue:[
-		self redrawLine:lineNr col:colNr
-	    ] ifFalse:[
-		self redrawLine:lineNr from:colNr
-	    ]
-	]
+        "/ care for italic text - in this case, we must also
+        "/ redraw the character before the insertion in order
+        "/ to fix the slanted piece of the character.
+        "/ (but we must clip, to avoid destoying the character before)
+        (newLine notNil and:[newLine isText]) ifTrue:[
+            colNr > 1 ifTrue:[
+                cursorVisibleLine notNil ifTrue:[
+                    oldClip := self clippingRectangleOrNil.
+                    x := (self xOfCol:colNr-1 inVisibleLine:cursorVisibleLine) - viewOrigin x.
+                    y := self yOfVisibleLine:cursorVisibleLine.
+
+                    gc font hasOverlappingCharacters ifTrue:[
+                        self invalidateLine:lineNr.
+                    ] ifFalse:[
+                        drawCharacterOnly ifTrue:[
+                            self clippingRectangle:(x@y extent:((gc font width * 2) @ fontHeight)).
+                            self redrawLine:lineNr from:colNr-1 to:colNr
+                        ] ifFalse:[
+                            self clippingRectangle:(x@y extent:((width - x) @ fontHeight)).
+                            self redrawLine:lineNr from:colNr-1
+                        ].
+                        self clippingRectangle:oldClip.
+                    ].
+                ].
+                ^ self.
+            ].
+        ].
+        gc font hasOverlappingCharacters ifTrue:[
+            self invalidateLine:lineNr.
+        ] ifFalse:[
+            drawCharacterOnly ifTrue:[
+                self redrawLine:lineNr col:colNr
+            ] ifFalse:[
+                self redrawLine:lineNr from:colNr
+            ]
+        ]
     ]
 
     "Modified: / 09-11-2010 / 13:43:18 / cg"
@@ -4526,36 +4560,36 @@
     |leftPart rightPart bothParts nextLineNr i|
 
     (list notNil and:[(list size) >= lineNr]) ifFalse:[
-	"/ empty list or beyond end of text
-	^ self
+        "/ empty list or beyond end of text
+        ^ self
     ].
     leftPart := self listAt:lineNr.
 
     leftPart isNil ifTrue:[
-	leftPart := ''.
-	autoIndent ifTrue:[
-	    (i := self leftIndentForLine:cursorLine) == 0 ifFalse:[
-		leftPart := String new:i
-	    ]
-	]
+        leftPart := ''.
+        autoIndent ifTrue:[
+            (i := self leftIndentForLine:cursorLine) == 0 ifFalse:[
+                leftPart := String new:i
+            ]
+        ]
     ].
     self cursorLine:lineNr col:((leftPart size) + 1).
     nextLineNr := self validateCursorLine:(lineNr + 1).
 
     nextLineNr > (list size) ifFalse:[
-	(rightPart := self listAt:nextLineNr) isNil ifTrue:[
-	    rightPart := ''
-	] ifFalse:[
-	    removeBlanks ifTrue:[
-		rightPart := rightPart withoutLeadingSeparators.
-	    ]
-	].
-
-	bothParts := leftPart , rightPart.
-	(trimBlankLines and:[bothParts isBlank]) ifTrue:[bothParts := nil].
-	self basicListAt:lineNr put:bothParts.
-	self redrawLine:lineNr.
-	self deleteLine:nextLineNr
+        (rightPart := self listAt:nextLineNr) isNil ifTrue:[
+            rightPart := ''
+        ] ifFalse:[
+            removeBlanks ifTrue:[
+                rightPart := rightPart withoutLeadingSeparators.
+            ]
+        ].
+
+        bothParts := leftPart , rightPart.
+        (self trimBlankLines and:[bothParts isBlank]) ifTrue:[bothParts := nil].
+        self basicListAt:lineNr put:bothParts.
+        self redrawLine:lineNr.
+        self deleteLine:nextLineNr
     ]
 
     "Created: 9.9.1997 / 09:27:38 / cg"
@@ -4570,7 +4604,7 @@
     self checkModificationsAllowed ifFalse:[ ^ self].
 
     aCharacter == (Character cr) ifTrue:[
-	^ self
+        ^ self
     ].
 
     drawCharacterOnly := true.
@@ -4578,43 +4612,43 @@
     line := list at:lineNr.
     lineSize := line size.
 
-    (trimBlankLines
+    (self trimBlankLines
     and:[colNr > lineSize
     and:[aCharacter == Character space]]) ifTrue:[
-	^ self
+        ^ self
     ].
 
     (lineSize == 0) ifTrue:[
-	newLine := aCharacter asString species new:colNr.
+        newLine := aCharacter asString species new:colNr.
     ] ifFalse: [
-	(aCharacter bitsPerCharacter > line bitsPerCharacter) ifTrue:[
-	    newLineSpecies := aCharacter stringSpecies
-	] ifFalse:[
-	    newLineSpecies := line species
-	].
-	newLine := newLineSpecies new:(colNr max:lineSize).
-	newLine replaceFrom:1 to:lineSize with:line startingAt:1.
+        (aCharacter bitsPerCharacter > line bitsPerCharacter) ifTrue:[
+            newLineSpecies := aCharacter stringSpecies
+        ] ifFalse:[
+            newLineSpecies := line species
+        ].
+        newLine := newLineSpecies new:(colNr max:lineSize).
+        newLine replaceFrom:1 to:lineSize with:line startingAt:1.
     ].
     newLine at:colNr put:aCharacter.
     aCharacter == (Character tab) ifTrue:[
-	newLine := self withTabsExpanded:newLine.
-	drawCharacterOnly := false
+        newLine := self withTabsExpanded:newLine.
+        drawCharacterOnly := false
     ].
     self basicListAt:lineNr put:(newLine ifNil:[newLine] ifNotNil:[newLine asSingleByteStringIfPossible]).
     widthOfWidestLine notNil ifTrue:[
-	widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
     ].
     self textChanged.
     shown ifTrue:[
-	gc font hasOverlappingCharacters ifTrue:[
-	    self invalidateLine:lineNr.
-	] ifFalse:[
-	    drawCharacterOnly ifTrue:[
-		self redrawLine:lineNr col:colNr
-	    ] ifFalse:[
-		self redrawLine:lineNr from:colNr
-	    ]
-	]
+        gc font hasOverlappingCharacters ifTrue:[
+            self invalidateLine:lineNr.
+        ] ifFalse:[
+            drawCharacterOnly ifTrue:[
+                self redrawLine:lineNr col:colNr
+            ] ifFalse:[
+                self redrawLine:lineNr from:colNr
+            ]
+        ]
     ]
 
     "Created: / 06-03-1996 / 12:29:20 / cg"
@@ -4679,50 +4713,50 @@
     lineNr > (list size) ifTrue:[ ^ self ].
 
     (colNr == 1) ifTrue:[
-	self nonUndoableDo:[
-	    self insertLine:nil before:lineNr.
-	].
-	^ self
+        self nonUndoableDo:[
+            self insertLine:nil before:lineNr.
+        ].
+        ^ self
     ].
 
     line := list at:lineNr.
     line notNil ifTrue:[
-	lineSize := line size.
-	(colNr <= lineSize) ifTrue:[
-	    rightRest := line copyFrom:colNr to:lineSize.
-	    (colNr > 1) ifTrue:[
-		leftRest := line copyTo:(colNr - 1)
-	    ]
-	] ifFalse:[
-	    leftRest := line
-	]
+        lineSize := line size.
+        (colNr <= lineSize) ifTrue:[
+            rightRest := line copyFrom:colNr to:lineSize.
+            (colNr > 1) ifTrue:[
+                leftRest := line copyTo:(colNr - 1)
+            ]
+        ] ifFalse:[
+            leftRest := line
+        ]
     ].
     leftRest notNil ifTrue:[
-	(trimBlankLines and:[leftRest isBlank]) ifTrue:[leftRest := nil]
+        (self trimBlankLines and:[leftRest isBlank]) ifTrue:[leftRest := nil]
     ].
     self basicListAt:lineNr put:leftRest.
     self nonUndoableDo:[
-	self withoutRedrawInsertLine:rightRest before:(lineNr + 1).
+        self withoutRedrawInsertLine:rightRest before:(lineNr + 1).
     ].
     visLine := self listLineToVisibleLine:(lineNr).
     visLine notNil ifTrue:[
-	w := self widthForScrollBetween:lineNr
-				    and:(firstLineShown + nLinesShown).
-	srcY := topMargin + (visLine * fontHeight).
-	h := ((nLinesShown - visLine - 1) * fontHeight).
-	(mustWait := (w > 0 and:[h > 0])) ifTrue:[
-	    self catchExpose.
-	    self
-		copyFrom:self
-		x:textStartLeft y:srcY
-		toX:textStartLeft y:(srcY + fontHeight)
-		width:w
-		height:((nLinesShown - visLine - 1) * fontHeight)
-		async:true.
-	].
-	self redrawLine:lineNr.
-	self redrawLine:(lineNr + 1).
-	mustWait ifTrue:[self waitForExpose]
+        w := self widthForScrollBetween:lineNr
+                                    and:(firstLineShown + nLinesShown).
+        srcY := topMargin + (visLine * fontHeight).
+        h := ((nLinesShown - visLine - 1) * fontHeight).
+        (mustWait := (w > 0 and:[h > 0])) ifTrue:[
+            self catchExpose.
+            self
+                copyFrom:self
+                x:textStartLeft y:srcY
+                toX:textStartLeft y:(srcY + fontHeight)
+                width:w
+                height:((nLinesShown - visLine - 1) * fontHeight)
+                async:true.
+        ].
+        self redrawLine:lineNr.
+        self redrawLine:(lineNr + 1).
+        mustWait ifTrue:[self waitForExpose]
     ].
     widthOfWidestLine := nil. "/ unknown
     self textChanged.
@@ -6149,7 +6183,6 @@
     autoIndent := false.
     editMode := ValueHolder with:EditMode insertMode.
     learnMode := ValueHolder with:false.
-    trimBlankLines := self st80EditMode not.
     cursorMovementWhenUpdating := #beginOfText.
     lastReplacementInfo := LastReplacementInfo new.
 
@@ -7622,13 +7655,6 @@
     lastReplacementInfo lastReplaceIgnoredCase: lastReplaceIgnoredCase.
 !
 
-st80EditMode
-    "If on, the cursor wraps at the line end (like in vi or st80);
-     if off, we have the Rand-editor behavior (random access)"
-
-    ^ st80Mode ? (UserPreferences current st80EditMode)
-!
-
 suppressEmphasisInSelection
     "selection is shown without emphasis"