EditTextView.st
changeset 629 cf0a3ab9b9f1
parent 606 682579fa3b62
child 630 ed57feb12f92
--- a/EditTextView.st	Sun May 12 16:27:10 1996 +0200
+++ b/EditTextView.st	Sun May 12 16:31:16 1996 +0200
@@ -208,6 +208,29 @@
 
 
 
+    non-string (text) items:
+                                                                        [exBegin]
+        |top textView list|
+
+        list := '/etc/hosts' asFilename contentsOfEntireFile asStringCollection.
+        1 to:list size by:2 do:[:nr |
+            list at:nr put:(Text string:(list at:nr)
+                                 emphasis:(Array with:#bold with:(#color->Color red)))
+        ].
+
+        top := StandardSystemView new.
+        top extent:300@200.
+
+        textView := EditTextView new.
+        textView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
+        top addSubView:textView.
+
+        textView contents:list.
+        top open.
+                                                                        [exEnd]
+
+
+
   MVC operation:
     (the examples model here is a plug simulating a real model;
      real world applications would not use a plug ..)
@@ -545,28 +568,33 @@
     |wasOn nv|
 
     cursorVisibleLine notNil ifTrue:[
-	wasOn := self hideCursor.
-	nv := cursorVisibleLine + n - 1.
-	(nv >= nFullLinesShown) ifTrue:[
-	    self scrollDown:(nv - nFullLinesShown + 1)
-	].
-	cursorLine := cursorLine + n.
-	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
-	wasOn ifTrue:[self showCursor].
+        wasOn := self hideCursor.
+        nv := cursorVisibleLine + n - 1.
+        (nv >= nFullLinesShown) ifTrue:[
+            self scrollDown:(nv - nFullLinesShown + 1)
+        ].
+        cursorLine := cursorLine + n.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        wasOn ifTrue:[self showCursor].
     ] ifFalse:[
-	cursorLine isNil ifTrue:[
-	    cursorLine := firstLineShown
-	].
-	cursorLine := cursorLine + n.
-	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
-	self makeCursorVisible.
+        cursorLine isNil ifTrue:[
+            cursorLine := firstLineShown
+        ].
+        cursorLine := cursorLine + n.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        self makeCursorVisible.
     ].
-    "/ cursor no longer visible ?
-    cursorVisibleLine isNil ifTrue:[
-	cursorLine > list size ifTrue:[
-	    device beep. device sync.
-	]
-    ]
+
+    "/ cursor behond text ?
+    cursorLine > list size ifTrue:[
+        wasOn := self hideCursor.
+        cursorLine := list size + 1.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        wasOn ifTrue:[self showCursor].
+        device beep. device sync.
+    ].
+
+    "Modified: 12.5.1996 / 12:15:09 / cg"
 !
 
 cursorHome
@@ -1273,51 +1301,6 @@
     wasOn ifTrue:[self showCursor]
 !
 
-deleteCharAtLine:lineNr col:colNr
-    "delete single character at colNr in line lineNr"
-
-    |line lineSize newLine drawCharacterOnly wasLargest|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    line := self listAt:lineNr.
-    line isNil ifTrue: [^self].
-    lineSize := line size.
-    (colNr > lineSize) ifTrue: [^ self].
-
-    wasLargest := (self widthOfLineString:line) == widthOfWidestLine.
-
-    drawCharacterOnly := false.
-    (colNr == lineSize) ifTrue:[
-        newLine := line copyTo:(lineSize - 1).
-        fontIsFixedWidth ifTrue:[
-            drawCharacterOnly := true
-        ]
-    ] ifFalse:[
-        newLine := line species new:(lineSize - 1).
-        newLine replaceFrom:1 to:(colNr - 1)
-                       with:line startingAt:1.
-        newLine replaceFrom:colNr to:(lineSize - 1)
-                       with:line startingAt:(colNr + 1)
-    ].
-
-    newLine isBlank ifTrue:[
-        newLine := nil
-    ].
-    list at:lineNr put:newLine.
-    wasLargest ifTrue:[
-        widthOfWidestLine := nil. "/ i.e. unknown
-    ].
-    self textChanged.
-    drawCharacterOnly ifTrue:[
-        self redrawLine:lineNr col:colNr
-    ] ifFalse:[
-        self redrawLine:lineNr from:colNr
-    ]
-
-    "Modified: 23.2.1996 / 17:42:23 / cg"
-!
-
 deleteCharBeforeCursor
     "delete single character to the left of cursor and move cursor to left"
 
@@ -1356,214 +1339,12 @@
     wasOn ifTrue:[self showCursor].
 !
 
-deleteCharsAtLine:lineNr fromCol:colNr
-    "delete characters from colNr up to the end in line lineNr"
-
-    |line newLine|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    line := self listAt:lineNr.
-    line isNil ifTrue: [^self].
-    (colNr > line size) ifTrue: [^ self].
-    newLine := line copyTo:(colNr - 1).
-    newLine isBlank ifTrue:[
-	newLine := nil
-    ].
-    list at:lineNr put:newLine.
-    widthOfWidestLine := nil. "/ i.e. unknown
-    self textChanged.
-    self redrawLine:lineNr
-!
-
-deleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
-    "delete characters from startCol to endCol in line lineNr"
-
-    |line lineSize newLine|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    line := self listAt:lineNr.
-    line isNil ifTrue: [^self].
-    lineSize := line size.
-    (startCol > lineSize) ifTrue: [^ self].
-    (endCol == 0) ifTrue:[^ self].
-    (endCol < startCol) ifTrue:[^ self].
-
-    (startCol == endCol) ifTrue:[
-	self deleteCharAtLine:lineNr col:startCol.
-	^ self
-    ].
-    (endCol >= lineSize) ifTrue:[
-	self deleteCharsAtLine:lineNr fromCol:startCol.
-	^ self
-    ].
-    (startCol <= 1) ifTrue:[
-	self deleteCharsAtLine:lineNr toCol:endCol.
-	^ self
-    ].
-    newLine := (line copyTo:(startCol - 1)) 
-	       , (line copyFrom:(endCol + 1) to:lineSize).
-
-    newLine isBlank ifTrue:[
-	newLine := nil
-    ].
-    list at:lineNr put:newLine.
-    widthOfWidestLine := nil. "/ i.e. unknown
-    self textChanged.
-    self redrawLine:lineNr
-!
-
-deleteCharsAtLine:lineNr toCol:colNr
-    "delete characters from start up to colNr in line lineNr"
-
-    |line lineSize newLine|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    line := self listAt:lineNr.
-    line isNil ifTrue: [^self].
-    lineSize := line size.
-    (colNr >= lineSize) ifTrue:[
-	newLine := nil
-    ] ifFalse:[
-	newLine := line copyFrom:(colNr + 1) to:lineSize.
-	newLine isBlank ifTrue:[
-	    newLine := nil
-	]
-    ].
-    list at:lineNr put:newLine.
-    widthOfWidestLine := nil. "/ i.e. unknown
-    self textChanged.
-    self redrawLine:lineNr
-!
-
 deleteCursorLine
     "delete the line where the cursor sits"
 
     self deleteLine:cursorLine
 !
 
-deleteFromLine:startLine col:startCol toLine:endLine col:endCol
-    "delete all text from startLine/startCol to endLine/endCol -
-     joining lines if nescessary"
-
-    |line lineSize|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    list isNil ifTrue:[^ self].
-
-    (startLine == endLine) ifTrue:[
-        "delete chars within a line"
-        self deleteCharsAtLine:startLine fromCol:startCol toCol:endCol.
-        ^ self
-    ].
-
-    ((startCol == 1) and:[endCol == 0]) ifTrue:[
-        "delete full lines only"
-        endLine > startLine ifTrue:[
-            self deleteFromLine:startLine toLine:(endLine - 1)
-        ].
-        ^ self
-    ].
-
-    "delete right rest of 1st line"
-    self deleteCharsAtLine:startLine fromCol:startCol.
-
-    "delete the inner lines ..."
-    endLine > (startLine + 1) ifTrue:[
-        self deleteFromLine:(startLine + 1) toLine:(endLine - 1)
-    ].
-
-    (endCol ~~ 0) ifTrue:[
-        "delete the left rest of the last line"
-        self deleteCharsAtLine:(startLine + 1) toCol:endCol.
-
-        "must add blanks, if startCal lies behond end of startLine"
-        line := list at:startLine.
-        lineSize := line size.
-        (startCol > lineSize) ifTrue:[
-            line isNil ifTrue:[
-                line := String new:(startCol - 1)
-            ] ifFalse:[
-                line := line , (line species new:(startCol - 1 - lineSize))
-            ].
-            list at:startLine put:line.
-            widthOfWidestLine := nil. "/ i.e. unknown
-            self textChanged.
-        ]
-    ].
-
-    "merge the left rest of 1st line with right rest of last line into one"
-    self mergeLine:startLine
-
-    "Modified: 23.2.1996 / 19:08:21 / cg"
-!
-
-deleteFromLine:startLineNr toLine:endLineNr
-    "delete some lines"
-
-    |wasOn nLines|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-    list isNil ifTrue:[^ self].
-
-    wasOn := self hideCursor.
-    list removeFromIndex:startLineNr toIndex:(endLineNr min:list size).
-    widthOfWidestLine := nil. "/ i.e. unknown
-    self textChanged.
-    self redrawFromLine:startLineNr.
-
-    nLines := list size.
-    (firstLineShown >= nLines) ifTrue:[
-	self makeLineVisible:nLines
-    ].
-    wasOn ifTrue:[self showCursor].
-!
-
-deleteLine:lineNr
-    "delete line"
-
-    |wasOn visLine w
-     srcY "{ Class: SmallInteger }" |
-
-    w := self widthForScrollBetween:lineNr and:(firstLineShown + nLinesShown).
-    (self deleteLineWithoutRedraw:lineNr) ifFalse:[^ self].
-    shown ifFalse:[^ self].
-
-    wasOn := self hideCursor.
-
-    visLine := self listLineToVisibleLine:lineNr.
-    visLine notNil ifTrue:[
-	srcY :=  margin + topMargin + (visLine * fontHeight).
-	self catchExpose.
-	self copyFrom:self x:textStartLeft y:srcY
-			 toX:textStartLeft y:(srcY - fontHeight)
-		       width:w height:((nLinesShown - visLine) * fontHeight).
-	self redrawVisibleLine:nFullLinesShown.
-	(nFullLinesShown ~~ nLinesShown) ifTrue:[
-	    self redrawVisibleLine:nLinesShown
-	].
-	self waitForExpose
-    ].
-
-    wasOn ifTrue:[self showCursor].
-!
-
-deleteLineWithoutRedraw:lineNr
-    "delete line - no redraw;
-     return true, if something was really deleted"
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    (list isNil or:[lineNr > list size]) ifTrue:[^ false].
-    list removeIndex:lineNr.
-    widthOfWidestLine := nil. "/ i.e. unknown
-    self textChanged.
-    ^ true
-!
-
 deleteLinesWithoutRedrawFrom:startLine to:endLine
     "delete lines - no redraw;
      return true, if something was really deleted"
@@ -1608,64 +1389,6 @@
     ]
 !
 
-insert:aCharacter atLine:lineNr col:colNr
-    "insert a single character at lineNr/colNr"
-
-    |line lineSize newLine drawCharacterOnly|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    aCharacter == (Character cr) ifTrue:[
-        self splitLine:lineNr before:colNr.
-        ^ self
-    ].
-    drawCharacterOnly := false.
-    self checkForExistingLine:lineNr.
-    line := list at:lineNr.
-    lineSize := line size.
-    (aCharacter == Character space) ifTrue:[
-        (colNr > lineSize)  ifTrue:[
-            ^ self
-        ]
-    ].
-    (lineSize == 0) ifTrue:[
-        newLine := aCharacter asString species new:colNr.
-        drawCharacterOnly := true
-    ] ifFalse: [
-        (colNr > lineSize) ifTrue: [
-            newLine := line species new:colNr.
-            newLine replaceFrom:1 to:lineSize
-                           with:line startingAt:1.
-            drawCharacterOnly := true
-        ] ifFalse: [
-            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
-        ]
-    ].
-    newLine at:colNr put:aCharacter.
-    aCharacter == (Character tab) ifTrue:[
-        newLine := self withTabsExpanded:newLine.
-        drawCharacterOnly := false
-    ].
-    list at:lineNr put:newLine.
-    widthOfWidestLine notNil ifTrue:[
-        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
-    ].
-    self textChanged.
-    shown ifTrue:[
-        drawCharacterOnly ifTrue:[
-            self redrawLine:lineNr col:colNr
-        ] ifFalse:[
-            self redrawLine:lineNr from:colNr
-        ]
-    ]
-
-    "Modified: 23.2.1996 / 19:09:36 / cg"
-!
-
 insertCharAtCursor:aCharacter
     "insert a single character at cursor-position - advance cursor"
 
@@ -1681,37 +1404,6 @@
     self makeCursorVisibleAndShowCursor:wasOn.
 !
 
-insertLine:aString before:lineNr
-    "insert the line aString before line lineNr"
-
-    |wasOn visLine w 
-     dstY "{ Class: SmallInteger }" |
-
-    wasOn := self hideCursor.
-
-    visLine := self listLineToVisibleLine:lineNr.
-    (shown not or:[visLine isNil]) ifTrue:[
-	self withoutRedrawInsertLine:aString before:lineNr.
-    ] ifFalse:[
-	w := self widthForScrollBetween:lineNr
-				    and:(firstLineShown + nLinesShown).
-	dstY := topMargin + ((visLine ) * fontHeight).
-	self catchExpose.
-	self withoutRedrawInsertLine:aString before:lineNr.
-	self copyFrom:self x:textStartLeft y:(dstY - fontHeight)
-			 toX:textStartLeft y:dstY
-		       width:w
-		      height:((nLinesShown - visLine "- 1") * fontHeight).
-	self redrawVisibleLine:visLine.
-	self waitForExpose.
-    ].
-    widthOfWidestLine notNil ifTrue:[
-	widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:aString).
-    ].
-    self textChanged.
-    wasOn ifTrue:[self showCursor].
-!
-
 insertLines:aStringCollection before:lineNr
     "insert a bunch before line lineNr"
 
@@ -1720,101 +1412,6 @@
     "Modified: 6.9.1995 / 20:51:03 / claus"
 !
 
-insertLines:someText from:start to:end before:lineNr
-    "insert a bunch of lines before line lineNr"
-
-    |visLine w nLines "{ Class: SmallInteger }"
-     srcY "{ Class: SmallInteger }"
-     dstY "{ Class: SmallInteger }" |
-
-    readOnly ifTrue:[
-	^ self
-    ].
-    visLine := self listLineToVisibleLine:lineNr.
-    (shown not or:[visLine isNil]) ifTrue:[
-	self withoutRedrawInsertLines:someText
-				 from:start to:end
-			       before:lineNr.
-    ] ifFalse:[
-	nLines := end - start + 1.
-	((visLine + nLines) >= nLinesShown) ifTrue:[
-	    self withoutRedrawInsertLines:someText
-				     from:start to:end
-				   before:lineNr.
-	    self redrawFromVisibleLine:visLine to:nLinesShown
-	] ifFalse:[
-	    w := self widthForScrollBetween:(lineNr + nLines)
-					and:(firstLineShown + nLines + nLinesShown).
-	    srcY := topMargin + ((visLine - 1) * fontHeight).
-	    dstY := srcY + (nLines * fontHeight).
-	    "
-	     stupid: must catchExpose before inserting new
-	     stuff - since catchExpose may perform redraws
-	    "
-	    self catchExpose.
-	    self withoutRedrawInsertLines:someText
-				     from:start to:end
-				   before:lineNr.
-	    self copyFrom:self x:textStartLeft y:srcY
-			     toX:textStartLeft y:dstY
-			   width:w
-			  height:(height - dstY).
-	    self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
-	    self waitForExpose
-	].
-    ].
-    widthOfWidestLine notNil ifTrue:[
-	someText do:[:line |
-	    widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
-	]
-    ].
-    self textChanged.
-!
-
-insertLines:lines withCr:withCr
-    "insert a bunch of lines at cursor position. Cursor
-     is moved behind insertion.
-     If withCr is true, append cr after last line"
-
-    |start end nLines wasOn|
-
-    lines notNil ifTrue:[
-	nLines := lines size.
-	(nLines == 1) ifTrue:[
-	    self insertStringAtCursor:(lines at:1).
-	    withCr ifTrue:[
-		self insertCharAtCursor:(Character cr)
-	    ] 
-	] ifFalse:[
-	    (cursorCol ~~ 1) ifTrue:[
-		self insertStringAtCursor:(lines at:1).
-		self insertCharAtCursor:(Character cr).
-		start := 2
-	    ] ifFalse:[
-		start := 1
-	    ].
-	    withCr ifTrue:[
-		end := nLines
-	    ] ifFalse:[
-		end := nLines - 1
-	    ].
-	    (start < nLines) ifTrue:[
-		(end >= start) ifTrue:[
-		    wasOn := self hideCursor.
-		    self insertLines:lines from:start to:end before:cursorLine.
-		    cursorLine := cursorLine + (end - start + 1).
-		    cursorVisibleLine := self absoluteLineToVisibleLine:cursorLine.
-		    wasOn ifTrue:[self showCursor].
-		]
-	    ].
-	    withCr ifFalse:[
-		"last line without cr"
-		self insertStringAtCursor:(lines at:nLines)
-	    ]
-	]
-    ]
-!
-
 insertSelectedStringAtCursor:aString
     "insert the argument, aString at cursor position and select it"
 
@@ -1944,31 +1541,6 @@
     self makeCursorVisibleAndShowCursor:wasOn.
 !
 
-mergeLine:lineNr
-    "merge line lineNr with line lineNr+1"
-
-    |leftPart rightPart bothParts nextLineNr|
-
-    list isNil ifFalse:[
-	nextLineNr := lineNr + 1.
-	(nextLineNr > list size) ifFalse:[
-	    (leftPart := self listAt:lineNr) isNil ifTrue:[
-		leftPart := ''
-	    ].
-	    (rightPart := self listAt:nextLineNr) isNil ifTrue:[
-		rightPart := ''
-	    ].
-	    bothParts := leftPart , rightPart.
-	    bothParts isBlank ifTrue:[bothParts := nil].
-	    list at:lineNr put:bothParts.
-	    self redrawLine:lineNr.
-	    self deleteLine:nextLineNr
-	]
-    ]
-
-    "Modified: 7.9.1995 / 15:56:17 / claus"
-!
-
 removeTrailingBlankLines
     "remove all blank lines at end of text"
 
@@ -2001,48 +1573,6 @@
     ]
 !
 
-replace:aCharacter atLine:lineNr col:colNr
-    "replace a single character at lineNr/colNr"
-
-    |line lineSize newLine drawCharacterOnly|
-
-    self checkModificationsAllowed ifFalse:[ ^ self].
-
-    aCharacter == (Character cr) ifTrue:[
-        ^ self
-    ].
-
-    self checkForExistingLine:lineNr.
-    line := list at:lineNr.
-    lineSize := line size.
-    (aCharacter == Character space) ifTrue:[
-        (colNr > lineSize)  ifTrue:[
-            ^ self
-        ]
-    ].
-    (lineSize == 0) ifTrue:[
-        newLine := aCharacter asString species new:colNr.
-    ] ifFalse: [
-        (colNr > lineSize) ifTrue: [
-            newLine := line species new:colNr.
-            newLine replaceFrom:1 to:lineSize with:line startingAt:1.
-        ] ifFalse: [
-            newLine := line copy.
-        ]
-    ].
-    newLine at:colNr put:aCharacter.
-    list at:lineNr put:newLine.
-    widthOfWidestLine notNil ifTrue:[
-        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
-    ].
-    self textChanged.
-    shown ifTrue:[
-        self redrawLine:lineNr col:colNr
-    ]
-
-    "Created: 6.3.1996 / 12:29:20 / cg"
-!
-
 replaceCharAtCursor:aCharacter
     "replace a single character at cursor-position - advance cursor"
 
@@ -2111,6 +1641,524 @@
     ]
 
     "Modified: 6.3.1996 / 12:26:31 / cg"
+! !
+
+!EditTextView methodsFor:'editing - basic'!
+
+deleteCharAtLine:lineNr col:colNr
+    "delete single character at colNr in line lineNr"
+
+    |line lineSize newLine drawCharacterOnly wasLargest|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    line := self listAt:lineNr.
+    line isNil ifTrue: [^self].
+    lineSize := line size.
+    (colNr > lineSize) ifTrue: [^ self].
+
+    wasLargest := (self widthOfLineString:line) == widthOfWidestLine.
+
+    drawCharacterOnly := false.
+    (colNr == lineSize) ifTrue:[
+        newLine := line copyTo:(lineSize - 1).
+        fontIsFixedWidth ifTrue:[
+            drawCharacterOnly := true
+        ]
+    ] ifFalse:[
+line storeString printNL.
+        newLine := line species new:(lineSize - 1).
+        newLine replaceFrom:1 to:(colNr - 1)
+                       with:line startingAt:1.
+        newLine replaceFrom:colNr to:(lineSize - 1)
+                       with:line startingAt:(colNr + 1).
+newLine storeString printNL.
+    ].
+
+    newLine isBlank ifTrue:[
+        newLine := nil
+    ].
+    list at:lineNr put:newLine.
+    wasLargest ifTrue:[
+        widthOfWidestLine := nil. "/ i.e. unknown
+    ].
+    self textChanged.
+    drawCharacterOnly ifTrue:[
+        self redrawLine:lineNr col:colNr
+    ] ifFalse:[
+        self redrawLine:lineNr from:colNr
+    ]
+
+    "Modified: 12.5.1996 / 15:57:08 / cg"
+!
+
+deleteCharsAtLine:lineNr fromCol:colNr
+    "delete characters from colNr up to the end in line lineNr"
+
+    |line newLine|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    line := self listAt:lineNr.
+    line isNil ifTrue: [^self].
+    (colNr > line size) ifTrue: [^ self].
+    newLine := line copyTo:(colNr - 1).
+    newLine isBlank ifTrue:[
+	newLine := nil
+    ].
+    list at:lineNr put:newLine.
+    widthOfWidestLine := nil. "/ i.e. unknown
+    self textChanged.
+    self redrawLine:lineNr
+!
+
+deleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
+    "delete characters from startCol to endCol in line lineNr"
+
+    |line lineSize newLine|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    line := self listAt:lineNr.
+    line isNil ifTrue: [^self].
+    lineSize := line size.
+    (startCol > lineSize) ifTrue: [^ self].
+    (endCol == 0) ifTrue:[^ self].
+    (endCol < startCol) ifTrue:[^ self].
+
+    (startCol == endCol) ifTrue:[
+	self deleteCharAtLine:lineNr col:startCol.
+	^ self
+    ].
+    (endCol >= lineSize) ifTrue:[
+	self deleteCharsAtLine:lineNr fromCol:startCol.
+	^ self
+    ].
+    (startCol <= 1) ifTrue:[
+	self deleteCharsAtLine:lineNr toCol:endCol.
+	^ self
+    ].
+    newLine := (line copyTo:(startCol - 1)) 
+	       , (line copyFrom:(endCol + 1) to:lineSize).
+
+    newLine isBlank ifTrue:[
+	newLine := nil
+    ].
+    list at:lineNr put:newLine.
+    widthOfWidestLine := nil. "/ i.e. unknown
+    self textChanged.
+    self redrawLine:lineNr
+!
+
+deleteCharsAtLine:lineNr toCol:colNr
+    "delete characters from start up to colNr in line lineNr"
+
+    |line lineSize newLine|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    line := self listAt:lineNr.
+    line isNil ifTrue: [^self].
+    lineSize := line size.
+    (colNr >= lineSize) ifTrue:[
+	newLine := nil
+    ] ifFalse:[
+	newLine := line copyFrom:(colNr + 1) to:lineSize.
+	newLine isBlank ifTrue:[
+	    newLine := nil
+	]
+    ].
+    list at:lineNr put:newLine.
+    widthOfWidestLine := nil. "/ i.e. unknown
+    self textChanged.
+    self redrawLine:lineNr
+!
+
+deleteFromLine:startLine col:startCol toLine:endLine col:endCol
+    "delete all text from startLine/startCol to endLine/endCol -
+     joining lines if nescessary"
+
+    |line lineSize|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    list isNil ifTrue:[^ self].
+
+    (startLine == endLine) ifTrue:[
+        "delete chars within a line"
+        self deleteCharsAtLine:startLine fromCol:startCol toCol:endCol.
+        ^ self
+    ].
+
+    ((startCol == 1) and:[endCol == 0]) ifTrue:[
+        "delete full lines only"
+        endLine > startLine ifTrue:[
+            self deleteFromLine:startLine toLine:(endLine - 1)
+        ].
+        ^ self
+    ].
+
+    "delete right rest of 1st line"
+    self deleteCharsAtLine:startLine fromCol:startCol.
+
+    "delete the inner lines ..."
+    endLine > (startLine + 1) ifTrue:[
+        self deleteFromLine:(startLine + 1) toLine:(endLine - 1)
+    ].
+
+    (endCol ~~ 0) ifTrue:[
+        "delete the left rest of the last line"
+        self deleteCharsAtLine:(startLine + 1) toCol:endCol.
+
+        "must add blanks, if startCal lies behond end of startLine"
+        line := list at:startLine.
+        lineSize := line size.
+        (startCol > lineSize) ifTrue:[
+            line isNil ifTrue:[
+                line := String new:(startCol - 1)
+            ] ifFalse:[
+                line := line , (line species new:(startCol - 1 - lineSize))
+            ].
+            list at:startLine put:line.
+            widthOfWidestLine := nil. "/ i.e. unknown
+            self textChanged.
+        ]
+    ].
+
+    "merge the left rest of 1st line with right rest of last line into one"
+    self mergeLine:startLine
+
+    "Modified: 23.2.1996 / 19:08:21 / cg"
+!
+
+deleteFromLine:startLineNr toLine:endLineNr
+    "delete some lines"
+
+    |wasOn nLines|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+    list isNil ifTrue:[^ self].
+
+    wasOn := self hideCursor.
+    list removeFromIndex:startLineNr toIndex:(endLineNr min:list size).
+    widthOfWidestLine := nil. "/ i.e. unknown
+    self textChanged.
+    self redrawFromLine:startLineNr.
+
+    nLines := list size.
+    (firstLineShown >= nLines) ifTrue:[
+	self makeLineVisible:nLines
+    ].
+    wasOn ifTrue:[self showCursor].
+!
+
+deleteLine:lineNr
+    "delete line"
+
+    |wasOn visLine w
+     srcY "{ Class: SmallInteger }" |
+
+    w := self widthForScrollBetween:lineNr and:(firstLineShown + nLinesShown).
+    (self deleteLineWithoutRedraw:lineNr) ifFalse:[^ self].
+    shown ifFalse:[^ self].
+
+    wasOn := self hideCursor.
+
+    visLine := self listLineToVisibleLine:lineNr.
+    visLine notNil ifTrue:[
+        srcY :=  margin + topMargin + (visLine * fontHeight).
+        "/
+        "/ scroll ...
+        "/
+        self catchExpose.
+        self copyFrom:self x:textStartLeft y:srcY
+                         toX:textStartLeft y:(srcY - fontHeight)
+                       width:w height:((nLinesShown - visLine) * fontHeight).
+        self redrawVisibleLine:nFullLinesShown.
+        (nFullLinesShown ~~ nLinesShown) ifTrue:[
+            self redrawVisibleLine:nLinesShown
+        ].
+        self waitForExpose
+    ].
+
+    wasOn ifTrue:[self showCursor].
+
+    "Modified: 12.5.1996 / 15:41:16 / cg"
+!
+
+deleteLineWithoutRedraw:lineNr
+    "delete line - no redraw;
+     return true, if something was really deleted"
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    (list isNil or:[lineNr > list size]) ifTrue:[^ false].
+    list removeIndex:lineNr.
+    widthOfWidestLine := nil. "/ i.e. unknown
+    self textChanged.
+    ^ true
+!
+
+insert:aCharacter atLine:lineNr col:colNr
+    "insert a single character at lineNr/colNr"
+
+    |line lineSize newLine drawCharacterOnly|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    aCharacter == (Character cr) ifTrue:[
+        self splitLine:lineNr before:colNr.
+        ^ self
+    ].
+    drawCharacterOnly := false.
+    self checkForExistingLine:lineNr.
+    line := list at:lineNr.
+    lineSize := line size.
+    (aCharacter == Character space) ifTrue:[
+        (colNr > lineSize)  ifTrue:[
+            ^ self
+        ]
+    ].
+    (lineSize == 0) ifTrue:[
+        newLine := aCharacter asString species new:colNr.
+        drawCharacterOnly := true
+    ] ifFalse: [
+        (colNr > lineSize) ifTrue: [
+            newLine := line species new:colNr.
+            newLine replaceFrom:1 to:lineSize
+                           with:line startingAt:1.
+            drawCharacterOnly := true
+        ] ifFalse: [
+            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
+        ]
+    ].
+    newLine at:colNr put:aCharacter.
+    aCharacter == (Character tab) ifTrue:[
+        newLine := self withTabsExpanded:newLine.
+        drawCharacterOnly := false
+    ].
+    list at:lineNr put:newLine.
+    widthOfWidestLine notNil ifTrue:[
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
+    ].
+    self textChanged.
+    shown ifTrue:[
+        drawCharacterOnly ifTrue:[
+            self redrawLine:lineNr col:colNr
+        ] ifFalse:[
+            self redrawLine:lineNr from:colNr
+        ]
+    ]
+
+    "Modified: 23.2.1996 / 19:09:36 / cg"
+!
+
+insertLine:aString before:lineNr
+    "insert the line aString before line lineNr"
+
+    |wasOn visLine w 
+     dstY "{ Class: SmallInteger }" |
+
+    wasOn := self hideCursor.
+
+    visLine := self listLineToVisibleLine:lineNr.
+    (shown not or:[visLine isNil]) ifTrue:[
+        self withoutRedrawInsertLine:aString before:lineNr.
+    ] ifFalse:[
+        w := self widthForScrollBetween:lineNr
+                                    and:(firstLineShown + nLinesShown).
+        dstY := topMargin + ((visLine ) * fontHeight).
+        "/
+        "/ scroll ...
+        "/
+        self catchExpose.
+        self withoutRedrawInsertLine:aString before:lineNr.
+        self copyFrom:self x:textStartLeft y:(dstY - fontHeight)
+                         toX:textStartLeft y:dstY
+                       width:w
+                      height:((nLinesShown - visLine "- 1") * fontHeight).
+        self redrawVisibleLine:visLine.
+        self waitForExpose.
+    ].
+    widthOfWidestLine notNil ifTrue:[
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:aString).
+    ].
+    self textChanged.
+    wasOn ifTrue:[self showCursor].
+
+    "Modified: 12.5.1996 / 15:41:24 / cg"
+!
+
+insertLines:someText from:start to:end before:lineNr
+    "insert a bunch of lines before line lineNr"
+
+    |visLine w nLines "{ Class: SmallInteger }"
+     srcY "{ Class: SmallInteger }"
+     dstY "{ Class: SmallInteger }" |
+
+    readOnly ifTrue:[
+        ^ self
+    ].
+    visLine := self listLineToVisibleLine:lineNr.
+    (shown not or:[visLine isNil]) ifTrue:[
+        self withoutRedrawInsertLines:someText
+                                 from:start to:end
+                               before:lineNr.
+    ] ifFalse:[
+        nLines := end - start + 1.
+        ((visLine + nLines) >= nLinesShown) ifTrue:[
+            self withoutRedrawInsertLines:someText
+                                     from:start to:end
+                                   before:lineNr.
+            self redrawFromVisibleLine:visLine to:nLinesShown
+        ] ifFalse:[
+            w := self widthForScrollBetween:(lineNr + nLines)
+                                        and:(firstLineShown + nLines + nLinesShown).
+            srcY := topMargin + ((visLine - 1) * fontHeight).
+            dstY := srcY + (nLines * fontHeight).
+
+            "/
+            "/ scroll ...
+            "/
+            "
+             stupid: must catchExpose before inserting new
+             stuff - since catchExpose may perform redraws
+            "
+            self catchExpose.
+            self withoutRedrawInsertLines:someText
+                                     from:start to:end
+                                   before:lineNr.
+            self copyFrom:self x:textStartLeft y:srcY
+                             toX:textStartLeft y:dstY
+                           width:w
+                          height:(height - dstY).
+            self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
+            self waitForExpose
+        ].
+    ].
+    widthOfWidestLine notNil ifTrue:[
+        someText do:[:line |
+            widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
+        ]
+    ].
+    self textChanged.
+
+    "Modified: 12.5.1996 / 15:41:36 / cg"
+!
+
+insertLines:lines withCr:withCr
+    "insert a bunch of lines at cursor position. Cursor
+     is moved behind insertion.
+     If withCr is true, append cr after last line"
+
+    |start end nLines wasOn|
+
+    lines notNil ifTrue:[
+	nLines := lines size.
+	(nLines == 1) ifTrue:[
+	    self insertStringAtCursor:(lines at:1).
+	    withCr ifTrue:[
+		self insertCharAtCursor:(Character cr)
+	    ] 
+	] ifFalse:[
+	    (cursorCol ~~ 1) ifTrue:[
+		self insertStringAtCursor:(lines at:1).
+		self insertCharAtCursor:(Character cr).
+		start := 2
+	    ] ifFalse:[
+		start := 1
+	    ].
+	    withCr ifTrue:[
+		end := nLines
+	    ] ifFalse:[
+		end := nLines - 1
+	    ].
+	    (start < nLines) ifTrue:[
+		(end >= start) ifTrue:[
+		    wasOn := self hideCursor.
+		    self insertLines:lines from:start to:end before:cursorLine.
+		    cursorLine := cursorLine + (end - start + 1).
+		    cursorVisibleLine := self absoluteLineToVisibleLine:cursorLine.
+		    wasOn ifTrue:[self showCursor].
+		]
+	    ].
+	    withCr ifFalse:[
+		"last line without cr"
+		self insertStringAtCursor:(lines at:nLines)
+	    ]
+	]
+    ]
+!
+
+mergeLine:lineNr
+    "merge line lineNr with line lineNr+1"
+
+    |leftPart rightPart bothParts nextLineNr|
+
+    list isNil ifFalse:[
+	nextLineNr := lineNr + 1.
+	(nextLineNr > list size) ifFalse:[
+	    (leftPart := self listAt:lineNr) isNil ifTrue:[
+		leftPart := ''
+	    ].
+	    (rightPart := self listAt:nextLineNr) isNil ifTrue:[
+		rightPart := ''
+	    ].
+	    bothParts := leftPart , rightPart.
+	    bothParts isBlank ifTrue:[bothParts := nil].
+	    list at:lineNr put:bothParts.
+	    self redrawLine:lineNr.
+	    self deleteLine:nextLineNr
+	]
+    ]
+
+    "Modified: 7.9.1995 / 15:56:17 / claus"
+!
+
+replace:aCharacter atLine:lineNr col:colNr
+    "replace a single character at lineNr/colNr"
+
+    |line lineSize newLine drawCharacterOnly|
+
+    self checkModificationsAllowed ifFalse:[ ^ self].
+
+    aCharacter == (Character cr) ifTrue:[
+        ^ self
+    ].
+
+    self checkForExistingLine:lineNr.
+    line := list at:lineNr.
+    lineSize := line size.
+    (aCharacter == Character space) ifTrue:[
+        (colNr > lineSize)  ifTrue:[
+            ^ self
+        ]
+    ].
+    (lineSize == 0) ifTrue:[
+        newLine := aCharacter asString species new:colNr.
+    ] ifFalse: [
+        (colNr > lineSize) ifTrue: [
+            newLine := line species new:colNr.
+            newLine replaceFrom:1 to:lineSize with:line startingAt:1.
+        ] ifFalse: [
+            newLine := line copy.
+        ]
+    ].
+    newLine at:colNr put:aCharacter.
+    list at:lineNr put:newLine.
+    widthOfWidestLine notNil ifTrue:[
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
+    ].
+    self textChanged.
+    shown ifTrue:[
+        self redrawLine:lineNr col:colNr
+    ]
+
+    "Created: 6.3.1996 / 12:29:20 / cg"
 !
 
 splitLine:lineNr before:colNr
@@ -3725,5 +3773,5 @@
 !EditTextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.68 1996-04-30 15:35:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.69 1996-05-12 14:31:16 cg Exp $'
 ! !