letfOver halt removed
authorClaus Gittinger <cg@exept.de>
Thu, 26 Apr 2001 14:24:21 +0200
changeset 2357 527d93ed293a
parent 2356 6416beb0f23a
child 2358 eadde3a9c586
letfOver halt removed
EditTextView.st
--- a/EditTextView.st	Thu Apr 26 12:12:03 2001 +0200
+++ b/EditTextView.st	Thu Apr 26 14:24:21 2001 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
+              All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -13,21 +13,21 @@
 "{ Package: 'stx:libwidg' }"
 
 TextView subclass:#EditTextView
-	instanceVariableNames:'cursorLine cursorVisibleLine cursorCol cursorShown
-		prevCursorState readOnly modifiedChannel fixedSize exceptionBlock
-		cursorFgColor cursorBgColor cursorNoFocusFgColor cursorType
-		cursorTypeNoFocus undoAction typeOfSelection lastString
-		lastReplacement lastAction replacing showMatchingParenthesis
-		hasKeyboardFocus acceptAction lockUpdates tabMeansNextField
-		autoIndent insertMode trimBlankLines wordWrap
-		replacementWordSelectStyle acceptChannel acceptEnabled st80Mode
-		disableIfInvisible cursorMovementWhenUpdating learnMode
-		learnedMacro'
-	classVariableNames:'DefaultCursorForegroundColor DefaultCursorBackgroundColor
-		DefaultCursorType DefaultCursorNoFocusForegroundColor ST80Mode
-		DefaultCursorTypeNoFocus'
-	poolDictionaries:''
-	category:'Views-Text'
+        instanceVariableNames:'cursorLine cursorVisibleLine cursorCol cursorShown
+                prevCursorState readOnly modifiedChannel fixedSize exceptionBlock
+                cursorFgColor cursorBgColor cursorNoFocusFgColor cursorType
+                cursorTypeNoFocus undoAction typeOfSelection lastString
+                lastReplacement lastAction replacing showMatchingParenthesis
+                hasKeyboardFocus acceptAction lockUpdates tabMeansNextField
+                autoIndent insertMode trimBlankLines wordWrap
+                replacementWordSelectStyle acceptChannel acceptEnabled st80Mode
+                disableIfInvisible cursorMovementWhenUpdating learnMode
+                learnedMacro'
+        classVariableNames:'DefaultCursorForegroundColor DefaultCursorBackgroundColor
+                DefaultCursorType DefaultCursorNoFocusForegroundColor ST80Mode
+                DefaultCursorTypeNoFocus'
+        poolDictionaries:''
+        category:'Views-Text'
 !
 
 !EditTextView class methodsFor:'documentation'!
@@ -35,7 +35,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
+              All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -175,176 +175,176 @@
   non MVC operation:
 
     basic setup:
-									[exBegin]
-	|top textView|
-
-	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:('/etc/hosts' asFilename contentsOfEntireFile).
-
-	top open.
-									[exEnd]
+                                                                        [exBegin]
+        |top textView|
+
+        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:('/etc/hosts' asFilename contentsOfEntireFile).
+
+        top open.
+                                                                        [exEnd]
 
 
     with vertical scrollbar:
-									[exBegin]
-	|top scrollView textView|
-
-	top := StandardSystemView new.
-	top extent:300@200.
-
-	scrollView := ScrollableView for:EditTextView.
-	textView := scrollView scrolledView.
-	scrollView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
-	top addSubView:scrollView.
-
-	textView contents:('/etc/hosts' asFilename contentsOfEntireFile).
-
-	top open.
-									[exEnd]
+                                                                        [exBegin]
+        |top scrollView textView|
+
+        top := StandardSystemView new.
+        top extent:300@200.
+
+        scrollView := ScrollableView for:EditTextView.
+        textView := scrollView scrolledView.
+        scrollView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
+        top addSubView:scrollView.
+
+        textView contents:('/etc/hosts' asFilename contentsOfEntireFile).
+
+        top open.
+                                                                        [exEnd]
 
 
     with horizontal & vertical scrollbars:
-									[exBegin]
-	|top scrollView textView|
-
-	top := StandardSystemView new.
-	top extent:300@200.
-
-	scrollView := HVScrollableView for:EditTextView.
-	textView := scrollView scrolledView.
-	scrollView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
-	top addSubView:scrollView.
-
-	textView contents:('/etc/hosts' asFilename contentsOfEntireFile).
-
-	top open.
-									[exEnd]
+                                                                        [exBegin]
+        |top scrollView textView|
+
+        top := StandardSystemView new.
+        top extent:300@200.
+
+        scrollView := HVScrollableView for:EditTextView.
+        textView := scrollView scrolledView.
+        scrollView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
+        top addSubView:scrollView.
+
+        textView contents:('/etc/hosts' asFilename contentsOfEntireFile).
+
+        top open.
+                                                                        [exEnd]
 
 
     set the action for accept:
-									[exBegin]
-	|top textView|
-
-	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:('/etc/hosts' asFilename contentsOfEntireFile).
-	textView acceptAction:[:contents |
-				Transcript showCR:'will not overwrite the file with:'.
-				Transcript showCR:contents asString
-			      ].
-	top open.
-									[exEnd]
+                                                                        [exBegin]
+        |top textView|
+
+        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:('/etc/hosts' asFilename contentsOfEntireFile).
+        textView acceptAction:[:contents |
+                                Transcript showCR:'will not overwrite the file with:'.
+                                Transcript showCR:contents asString
+                              ].
+        top open.
+                                                                        [exEnd]
 
 
 
     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]
+                                                                        [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 ..)
-									[exBegin]
-	|top textView model|
-
-	model := Plug new.
-	model respondTo:#accepted:
-		   with:[:newContents | 
-				Transcript showCR:'will not overwrite the file with:'.
-				Transcript showCR:newContents asString
-			].
-	model respondTo:#getList
-		   with:['/etc/hosts' asFilename contentsOfEntireFile].
+                                                                        [exBegin]
+        |top textView model|
+
+        model := Plug new.
+        model respondTo:#accepted:
+                   with:[:newContents | 
+                                Transcript showCR:'will not overwrite the file with:'.
+                                Transcript showCR:newContents asString
+                        ].
+        model respondTo:#getList
+                   with:['/etc/hosts' asFilename contentsOfEntireFile].
 
         
-	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 listMessage:#getList;
-		 model:model;
-		 changeMessage:#accepted:;
-		 aspect:#list.
-	top open.
-									[exEnd]
+        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 listMessage:#getList;
+                 model:model;
+                 changeMessage:#accepted:;
+                 aspect:#list.
+        top open.
+                                                                        [exEnd]
 
 
     two textViews on the same model:
-									[exBegin]
-	|top1 textView1 top2 textView2 model currentContents|
-
-	model := Plug new.
-	model respondTo:#accepted:
-		   with:[:newContents |
-				Transcript showCR:'accepted:'.
-				Transcript showCR:newContents asString.
-				currentContents := newContents.
-				model changed:#contents
-			].
-	model respondTo:#getList
-		   with:[Transcript showCR:'query'.
-			 currentContents].
-
-
-	top1 := StandardSystemView new.
-	top1 extent:300@200.
-
-	textView1 := EditTextView new.
-	textView1 origin:0.0 @ 0.0 corner:1.0 @ 1.0.
-	top1 addSubView:textView1.
-
-	textView1 listMessage:#getList;
-		  model:model;
-		  aspect:#contents;
-		  changeMessage:#accepted:.
-	top1 open.
-
-	top2 := StandardSystemView new.
-	top2 extent:300@200.
-
-	textView2 := EditTextView new.
-	textView2 origin:0.0 @ 0.0 corner:1.0 @ 1.0.
-	top2 addSubView:textView2.
-
-	textView2 listMessage:#getList;
-		  model:model;
-		  aspect:#contents;
-		  changeMessage:#accepted:.
-	top2 open.
-									[exEnd]
+                                                                        [exBegin]
+        |top1 textView1 top2 textView2 model currentContents|
+
+        model := Plug new.
+        model respondTo:#accepted:
+                   with:[:newContents |
+                                Transcript showCR:'accepted:'.
+                                Transcript showCR:newContents asString.
+                                currentContents := newContents.
+                                model changed:#contents
+                        ].
+        model respondTo:#getList
+                   with:[Transcript showCR:'query'.
+                         currentContents].
+
+
+        top1 := StandardSystemView new.
+        top1 extent:300@200.
+
+        textView1 := EditTextView new.
+        textView1 origin:0.0 @ 0.0 corner:1.0 @ 1.0.
+        top1 addSubView:textView1.
+
+        textView1 listMessage:#getList;
+                  model:model;
+                  aspect:#contents;
+                  changeMessage:#accepted:.
+        top1 open.
+
+        top2 := StandardSystemView new.
+        top2 extent:300@200.
+
+        textView2 := EditTextView new.
+        textView2 origin:0.0 @ 0.0 corner:1.0 @ 1.0.
+        top2 addSubView:textView2.
+
+        textView2 listMessage:#getList;
+                  model:model;
+                  aspect:#contents;
+                  changeMessage:#accepted:.
+        top2 open.
+                                                                        [exEnd]
 "
 ! !
 
@@ -384,9 +384,9 @@
     "extract values from the styleSheet and cache them in class variables"
 
     <resource: #style (#'textCursor.foregroundColor' #'textCursor.backgroundColor'
-		       #'textCursor.noFocusForegroundColor' 
-		       #'textCursor.type' #'textCursor.typeNoFocus'
-		       #'editText.st80Mode')>
+                       #'textCursor.noFocusForegroundColor' 
+                       #'textCursor.type' #'textCursor.typeNoFocus'
+                       #'editText.st80Mode')>
 
     DefaultCursorForegroundColor := StyleSheet colorAt:'textCursor.foregroundColor'.
     DefaultCursorBackgroundColor := StyleSheet colorAt:'textCursor.backgroundColor'.
@@ -454,7 +454,7 @@
     line := self lineOfCharacterPosition:aCharacterPosition.
     col := aCharacterPosition - (self characterPositionOfLine:line col:1) + 1.
     col < 1 ifTrue:[
-	col := 1
+        col := 1
     ].
     self insertString:aString atLine:line col:col.
 
@@ -517,18 +517,18 @@
     |line1 col1 line2 col2|
 
     startPos > endPos ifTrue:[
-	^ self unselect
+        ^ self unselect
     ].
 
     line1 := self lineOfCharacterPosition:startPos.
     col1 := startPos - (self characterPositionOfLine:line1 col:1) + 1.
     col1 < 1 ifTrue:[
-	col1 := 1
+        col1 := 1
     ].
     line2 := self lineOfCharacterPosition:endPos.
     col2 := startPos - (self characterPositionOfLine:line2 col:1) + 1.
     col2 < 1 ifTrue:[
-	col2 := 1
+        col2 := 1
     ].
     self selectFromLine:line1 col:col1 toLine:line2 col:col2
 
@@ -668,14 +668,14 @@
     "change a line without change notification"
 
     (self at:lineNr) = aLine ifFalse:[
-	super at:lineNr put:aLine.
+        super at:lineNr put:aLine.
     ].
 !
 
 at:lineNr put:aLine
     (self at:lineNr) = aLine ifFalse:[
-	super at:lineNr put:aLine.
-	self textChanged
+        super at:lineNr put:aLine.
+        self textChanged
     ].
 !
 
@@ -737,10 +737,10 @@
 
     self obsoleteMethodWarning:'use #readOnly:'.
     readOnly == true ifFalse:[
-	readOnly := true.
-	middleButtonMenu notNil ifTrue:[
-	    middleButtonMenu disableAll:#(cut paste replace indent)
-	]
+        readOnly := true.
+        middleButtonMenu notNil ifTrue:[
+            middleButtonMenu disableAll:#(cut paste replace indent)
+        ]
     ]
 
     "Modified: 14.2.1997 / 17:35:24 / cg"
@@ -863,7 +863,7 @@
 cursorType
     "return the style of the text cursor.
      Currently, supported are: #block, #frame, #ibeam, #caret, #solidCaret
-			       #bigCaret and #bigSolidCaret"
+                               #bigCaret and #bigSolidCaret"
 
     ^ cursorType
 
@@ -873,7 +873,7 @@
 cursorType:aCursorTypeSymbol
     "set the style of the text cursor.
      Currently, supported are: #block, #frame, #ibeam, #caret, #solidCaret
-			       #bigCaret and #bigSolidCaret"
+                               #bigCaret and #bigSolidCaret"
 
     cursorType := aCursorTypeSymbol.
 
@@ -976,10 +976,10 @@
 
 update:something with:aParameter from:changedObject
     changedObject == acceptChannel ifTrue:[
-	acceptChannel value == true ifTrue:[ 
-	    self accept.
-	].
-	^ self.
+        acceptChannel value == true ifTrue:[ 
+            self accept.
+        ].
+        ^ self.
     ].
     super update:something with:aParameter from:changedObject
 
@@ -1017,13 +1017,13 @@
 
     "/ cursor behond text ?
     cursorLine > list size ifTrue:[
-	wasOn := self hideCursor.
-	cursorLine := self validateCursorLine:(list size + 1).
-	cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
-	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
-	"/ wasOn ifTrue:[self showCursor].
-	self makeCursorVisibleAndShowCursor:wasOn.
-	self beep.
+        wasOn := self hideCursor.
+        cursorLine := self validateCursorLine:(list size + 1).
+        cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        "/ wasOn ifTrue:[self showCursor].
+        self makeCursorVisibleAndShowCursor:wasOn.
+        self beep.
     ].
 
     "Modified: / 10.6.1998 / 17:00:23 / cg"
@@ -1035,24 +1035,24 @@
     |wasOn nv|
 
     cursorVisibleLine notNil ifTrue:[
-	wasOn := self hideCursor.
-	nv := cursorVisibleLine + n - 1.
-	(nv >= nFullLinesShown) ifTrue:[
-	    self scrollDown:(nv - nFullLinesShown + 1)
-	].
-	cursorLine := self validateCursorLine:(cursorLine + n).
-	cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
-	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
-	"/ wasOn ifTrue:[self showCursor].
-	self makeCursorVisibleAndShowCursor:wasOn.
+        wasOn := self hideCursor.
+        nv := cursorVisibleLine + n - 1.
+        (nv >= nFullLinesShown) ifTrue:[
+            self scrollDown:(nv - nFullLinesShown + 1)
+        ].
+        cursorLine := self validateCursorLine:(cursorLine + n).
+        cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        "/ wasOn ifTrue:[self showCursor].
+        self makeCursorVisibleAndShowCursor:wasOn.
     ] ifFalse:[
-	cursorLine isNil ifTrue:[
-	    cursorLine := firstLineShown
-	].
-	cursorLine := self validateCursorLine:(cursorLine + n).
-	cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
-	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
-	self makeCursorVisible.
+        cursorLine isNil ifTrue:[
+            cursorLine := firstLineShown
+        ].
+        cursorLine := self validateCursorLine:(cursorLine + n).
+        cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        self makeCursorVisible.
     ].
 
     "Modified: / 10.6.1998 / 16:59:17 / cg"
@@ -1078,7 +1078,7 @@
     "move cursor to left"
 
     (cursorCol ~~ 1) ifTrue:[
-	self cursorCol:(cursorCol - 1)
+        self cursorCol:(cursorCol - 1)
     ] ifFalse:[
 "/ no, do not wrap back to previous line
 "/        cursorLine ~~ 1 ifTrue:[
@@ -1101,15 +1101,15 @@
     cursorLine := self validateCursorLine:line.
     cursorVisibleLine := self listLineToVisibleLine:cursorLine.
     (col < 1) ifTrue:[
-	newCol := 1
+        newCol := 1
     ] ifFalse:[
-	newCol := col.
+        newCol := col.
     ].
     st80Mode ifTrue:[
-	(cursorLine == list size
-	and:[cursorLine ~~ line]) ifTrue:[
-	    newCol := (self listAt:(list size)) size + 1.
-	]
+        (cursorLine == list size
+        and:[cursorLine ~~ line]) ifTrue:[
+            newCol := (self listAt:(list size)) size + 1.
+        ]
     ].
     cursorCol := self validateCursorCol:newCol inLine:cursorLine.
     self makeCursorVisibleAndShowCursor:wasOn.
@@ -1136,9 +1136,9 @@
 
     self checkForExistingLine:(cursorLine + 1).
     cursorVisibleLine notNil ifTrue:[
-	nFullLinesShown notNil ifTrue:[
-	    (cursorVisibleLine >= nFullLinesShown) ifTrue:[self scrollDown]
-	]
+        nFullLinesShown notNil ifTrue:[
+            (cursorVisibleLine >= nFullLinesShown) ifTrue:[self scrollDown]
+        ]
     ].
 
     wasOn := self hideCursor.
@@ -1156,14 +1156,14 @@
     |l|
 
     st80Mode == true ifTrue:[
-	l := (self listAt:cursorLine).
-	cursorCol >= (l size + 1) ifTrue:[
+        l := (self listAt:cursorLine).
+        cursorCol >= (l size + 1) ifTrue:[
 "/ no, do not wrap to next line
 "/            cursorLine < list size ifTrue:[
 "/                self cursorReturn.
 "/            ].
-	    ^ self    
-	]
+            ^ self    
+        ]
     ].    
     self cursorCol:(cursorCol + 1)
 
@@ -1179,11 +1179,11 @@
     oldState := cursorShown.
 
     aBoolean ifTrue:[
-	self drawCursor.
+        self drawCursor.
     ] ifFalse:[
-	(cursorShown and:[shown]) ifTrue: [
-	    self undrawCursor.
-	].
+        (cursorShown and:[shown]) ifTrue: [
+            self undrawCursor.
+        ].
     ].
     cursorShown := aBoolean.
 
@@ -1247,10 +1247,10 @@
     l := list size.
 
     cursorLine >= l ifTrue:[
-	line := self listAt:cursorLine.
-	(line isNil or:[line isEmpty]) ifTrue:[
-	    ^ self
-	]
+        line := self listAt:cursorLine.
+        (line isNil or:[line isEmpty]) ifTrue:[
+            ^ self
+        ]
     ].
 
     wasOn := self hideCursor.
@@ -1258,7 +1258,7 @@
     l := l + 1.
     newTop :=  l - nFullLinesShown.
     (newTop < 1) ifTrue:[
-	newTop := 1
+        newTop := 1
     ].
     self scrollToLine:newTop.
     cursorLine := self validateCursorLine:l.
@@ -1320,26 +1320,26 @@
 
     (cursorLine > list size) ifTrue:[^ self].
     self wordAtLine:cursorLine col:cursorCol do:[
-	:beginLine :beginCol :endLine :endCol :style | 
-
-	line := endLine.
-	col := endCol + 1.
-	searching := true.
-	[searching 
-	 and:[(self characterAtLine:line col:col) isSeparator]] whileTrue:[
-	    self wordAtLine:line col:col do:[
-		:beginLine :beginCol :endLine :endCol :style |
-
-		(line > list size) ifTrue:[
-		    "break out"
-		    searching := false
-		] ifFalse:[
-		    line := endLine.
-		    col := endCol + 1.
-		]
-	    ]
-	].
-	self cursorLine:line col:col
+        :beginLine :beginCol :endLine :endCol :style | 
+
+        line := endLine.
+        col := endCol + 1.
+        searching := true.
+        [searching 
+         and:[(self characterAtLine:line col:col) isSeparator]] whileTrue:[
+            self wordAtLine:line col:col do:[
+                :beginLine :beginCol :endLine :endCol :style |
+
+                (line > list size) ifTrue:[
+                    "break out"
+                    searching := false
+                ] ifFalse:[
+                    line := endLine.
+                    col := endCol + 1.
+                ]
+            ]
+        ].
+        self cursorLine:line col:col
     ]
 !
 
@@ -1351,50 +1351,50 @@
     (cursorLine > list size) ifTrue:[^ self].
 
     self wordAtLine:cursorLine col:cursorCol do:[
-	:beginLine :beginCol :endLine :endCol :style | 
-
-	line := beginLine.
-	col := beginCol.
-	style == #wordLeft ifTrue:[
-	    col := col + 1
-	].
-
-	(cursorLine == line
-	and:[cursorCol == col]) ifTrue:[
-	    searching := true.
-
-	    col > 1 ifTrue:[
-		col := col - 1.
-	    ].
-
-	    [searching] whileTrue:[
-		(col == 1) ifTrue:[    
-		    line == 1 ifTrue:[
-			searching := false
-		    ] ifFalse:[
-			line := line - 1.
-			l := list at:line.
-			col := l size + 1.
-		    ]
-		] ifFalse:[
-		    (self characterAtLine:line col:col) isSeparator ifFalse:[
-			self wordAtLine:line col:col do:[
-			    :beginLine :beginCol :endLine :endCol :style |
-
-			    line := beginLine.
-			    col := beginCol.
-			    style == #wordLeft ifTrue:[
-				col := col + 1
-			    ].
-			    searching := false.
-			]
-		    ] ifTrue:[
-			col := col - 1
-		    ]
-		]
-	    ]
-	].
-	self cursorLine:line col:col
+        :beginLine :beginCol :endLine :endCol :style | 
+
+        line := beginLine.
+        col := beginCol.
+        style == #wordLeft ifTrue:[
+            col := col + 1
+        ].
+
+        (cursorLine == line
+        and:[cursorCol == col]) ifTrue:[
+            searching := true.
+
+            col > 1 ifTrue:[
+                col := col - 1.
+            ].
+
+            [searching] whileTrue:[
+                (col == 1) ifTrue:[    
+                    line == 1 ifTrue:[
+                        searching := false
+                    ] ifFalse:[
+                        line := line - 1.
+                        l := list at:line.
+                        col := l size + 1.
+                    ]
+                ] ifFalse:[
+                    (self characterAtLine:line col:col) isSeparator ifFalse:[
+                        self wordAtLine:line col:col do:[
+                            :beginLine :beginCol :endLine :endCol :style |
+
+                            line := beginLine.
+                            col := beginCol.
+                            style == #wordLeft ifTrue:[
+                                col := col + 1
+                            ].
+                            searching := false.
+                        ]
+                    ] ifTrue:[
+                        col := col - 1
+                    ]
+                ]
+            ]
+        ].
+        self cursorLine:line col:col
     ]
 
     "Created: 8.3.1996 / 21:52:48 / cg"
@@ -1419,23 +1419,23 @@
     |wasOn nv nl|
 
     cursorLine isNil ifTrue:[
-	cursorLine := firstLineShown + nFullLinesShown - 1.
+        cursorLine := firstLineShown + nFullLinesShown - 1.
     ].
     nl := cursorLine - n.
     nl < 1 ifTrue:[nl := 1].
 
     (nl ~~ cursorLine) ifTrue: [
-	wasOn := self hideCursor.
-	cursorVisibleLine notNil ifTrue:[
-	    nv := cursorVisibleLine - n.
-	    nv < 1 ifTrue:[
-		self scrollUp:(nv negated + 1)
-	    ].
-	].
-	cursorLine := self validateCursorLine:nl.
-	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
-	cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
-	wasOn ifTrue:[self showCursor].
+        wasOn := self hideCursor.
+        cursorVisibleLine notNil ifTrue:[
+            nv := cursorVisibleLine - n.
+            nv < 1 ifTrue:[
+                self scrollUp:(nv negated + 1)
+            ].
+        ].
+        cursorLine := self validateCursorLine:nl.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
+        wasOn ifTrue:[self showCursor].
 "/
 "/ to make cursor visible (even if below visible end):
 "/
@@ -1455,7 +1455,7 @@
     cursorVisibleLine := visibleLineNr.
     newCol := colNr.
     (newCol < 1) ifTrue:[
-	newCol := 1
+        newCol := 1
     ].
     cursorCol := self validateCursorCol:newCol inLine:cursorLine.
     self makeCursorVisibleAndShowCursor:wasOn.
@@ -1478,11 +1478,11 @@
      (but not, if there is a selection - to avoid confusion)"
 
     shown ifTrue:[
-	cursorVisibleLine notNil ifTrue:[
-	    self hasSelection ifFalse:[
-		self drawCursorCharacter
-	    ]
-	]
+        cursorVisibleLine notNil ifTrue:[
+            self hasSelection ifFalse:[
+                self drawCursorCharacter
+            ]
+        ]
     ]
 !
 
@@ -1585,9 +1585,9 @@
     (hasKeyboardFocus 
     and:[self enabled
     and:[readOnly not]]) ifTrue:[
-	self drawFocusCursor
+        self drawFocusCursor
     ] ifFalse:[
-	self drawNoFocusCursor
+        self drawNoFocusCursor
     ]
 
     "Modified: / 23.3.1999 / 13:52:48 / cg"
@@ -1597,10 +1597,10 @@
     "draw the cursor when the focus is in the view."
 
     self hasSelection ifTrue:[
-	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
+        ^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
     ].
     cursorType == #none ifTrue:[
-	^ self undrawCursor
+        ^ self undrawCursor
     ].
     self drawCursor:cursorType with:cursorFgColor and:cursorBgColor.
 
@@ -1613,16 +1613,16 @@
     |cType|
 
     self hasSelection ifTrue:[
-	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
+        ^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
     ].
 
     cType := cursorTypeNoFocus ? cursorType.
     cType == #none ifTrue:[
-	^ self undrawCursor
+        ^ self undrawCursor
     ].
 
     cType == #block ifTrue:[
-	^ self drawCursor:#frame with:cursorNoFocusFgColor and:cursorBgColor
+        ^ self drawCursor:#frame with:cursorNoFocusFgColor and:cursorBgColor
     ].
 
     ^ self drawCursor:cType with:cursorNoFocusFgColor and:cursorNoFocusFgColor.
@@ -1653,24 +1653,24 @@
     |line col|
 
     cursorLine notNil ifTrue:[
-	line := cursorLine.
-	col := cursorCol.
-	"
-	 if there is a selection, its better to
-	 have its start being visible, instead of the end
-	"
-	(selectionStartLine notNil 
-	and:[selectionEndLine notNil]) ifTrue:[
-	    expandingTop ~~ false ifTrue:[
-		line := selectionStartLine.
-		col := selectionStartCol.
-	    ] ifFalse:[
-		line := selectionEndLine.
-		col := selectionEndCol
-	    ]
-	].
-	self makeLineVisible:line.
-	self makeColVisible:col inLine:line 
+        line := cursorLine.
+        col := cursorCol.
+        "
+         if there is a selection, its better to
+         have its start being visible, instead of the end
+        "
+        (selectionStartLine notNil 
+        and:[selectionEndLine notNil]) ifTrue:[
+            expandingTop ~~ false ifTrue:[
+                line := selectionStartLine.
+                col := selectionStartCol.
+            ] ifFalse:[
+                line := selectionEndLine.
+                col := selectionEndCol
+            ]
+        ].
+        self makeLineVisible:line.
+        self makeColVisible:col inLine:line 
     ]
 
     "Modified: 6.3.1996 / 13:46:46 / cg"
@@ -1788,11 +1788,11 @@
     "/ end of a line or behond the last line of the text
     "/
     st80Mode == true ifTrue:[
-	l := (self listAt:line).
-	max := l size + 1.
-	col > max ifTrue:[
-	    ^ max
-	]
+        l := (self listAt:line).
+        max := l size + 1.
+        col > max ifTrue:[
+            ^ max
+        ]
     ].
     ^ col
 
@@ -1812,7 +1812,7 @@
     "/ behond the last line
     "/
     st80Mode == true ifTrue:[
-	^ (line min:(list size)) max:1
+        ^ (line min:(list size)) max:1
     ].
     ^ line
 
@@ -1824,11 +1824,11 @@
     "evaluate aBlock with cursor off; turn it on afterwards."
 
     (shown not or:[cursorShown not]) ifTrue:[
-	^ aBlock value
+        ^ aBlock value
     ].
     self hideCursor.
     aBlock valueNowOrOnUnwindDo:[
-	self showCursor
+        self showCursor
     ]
 ! !
 
@@ -1838,8 +1838,8 @@
     "copy the selection into the pastBuffer and delete it"
 
     selectionStartLine notNil ifTrue:[
-	self setTextSelection:(self selection).
-	self deleteSelection.
+        self setTextSelection:(self selection).
+        self deleteSelection.
     ].
 
     "Created: 27.1.1996 / 16:23:28 / cg"
@@ -1899,7 +1899,6 @@
             lineNrAboveCursor := self validateCursorLine:(cursorLine - 1).
             lineNrAboveCursor < cursorLine ifTrue:[
                 (lineNrAboveCursor > 0 and:[lineNrAboveCursor > list size]) ifTrue:[
-self halt.
                     "/ we are behond the end of the text.
                     "/ move the cursor to the previous line.
                     self cursorLine:lineNrAboveCursor col:1.
@@ -1920,7 +1919,7 @@
     |line|
 
     (line := self listAt:lineNr) notNil ifTrue:[
-	self deleteCharsAtLine:lineNr fromCol:colNr toCol:(line size)
+        self deleteCharsAtLine:lineNr fromCol:colNr toCol:(line size)
     ]
 
 !
@@ -1957,9 +1956,9 @@
 
     (list isNil or:[startLine > list size]) ifTrue:[^ false].
     (endLine > list size) ifTrue:[
-	lastLine := list size
+        lastLine := list size
     ] ifFalse:[
-	lastLine := endLine
+        lastLine := endLine
     ].
     list removeFromIndex:startLine toIndex:lastLine.
     "/ TODO: remember old maxwidth of linerange,
@@ -1981,19 +1980,19 @@
     self checkModificationsAllowed ifFalse:[ ^ self].
 
     selectionStartLine notNil ifTrue:[
-	wasOn := self hideCursor.
-
-	startLine := selectionStartLine.
-	startCol := selectionStartCol.
-	endLine := selectionEndLine.
-	endCol := selectionEndCol.
-	self unselectWithoutRedraw.
-	self deleteFromLine:startLine col:startCol 
-		     toLine:endLine col:endCol.
-	cursorCol := startCol.
-	cursorLine := startLine.
-	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
-	self makeCursorVisibleAndShowCursor:wasOn
+        wasOn := self hideCursor.
+
+        startLine := selectionStartLine.
+        startCol := selectionStartCol.
+        endLine := selectionEndLine.
+        endCol := selectionEndCol.
+        self unselectWithoutRedraw.
+        self deleteFromLine:startLine col:startCol 
+                     toLine:endLine col:endCol.
+        cursorCol := startCol.
+        cursorLine := startLine.
+        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
+        self makeCursorVisibleAndShowCursor:wasOn
     ]
 !
 
@@ -2024,15 +2023,15 @@
 
     wasOn := self hideCursor.
     aCharacter == Character tab ifTrue:[
-	"/ needs special care to advance cursor correctly
-	self insertTabAtCursor
+        "/ needs special care to advance cursor correctly
+        self insertTabAtCursor
     ] ifFalse:[
-	self insert:aCharacter atLine:cursorLine col:cursorCol.
-	aCharacter == (Character cr) ifTrue:[
-	    self cursorReturn
-	] ifFalse:[
-	    self cursorRight.
-	].
+        self insert:aCharacter atLine:cursorLine col:cursorCol.
+        aCharacter == (Character cr) ifTrue:[
+            self cursorReturn
+        ] ifFalse:[
+            self cursorRight.
+        ].
     ].
     self makeCursorVisibleAndShowCursor:wasOn.
 
@@ -2063,39 +2062,39 @@
     |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)
-	    ]
-	]
+        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)
+            ]
+        ]
     ]
 
     "Created: / 18.5.1996 / 15:32:06 / cg"
@@ -2122,7 +2121,7 @@
     startCol := cursorCol.
     self insertStringAtCursor:aString.
     self selectFromLine:startLine col:startCol
-		 toLine:cursorLine col:(cursorCol - 1)
+                 toLine:cursorLine col:(cursorCol - 1)
 !
 
 insertString:aString atCharacterPosition:charPos
@@ -2147,7 +2146,7 @@
 
     aString isNil ifTrue:[^ self].
     (aString includes:(Character cr)) ifFalse:[
-	^ self insertStringWithoutCRs:aString atLine:lineNr col:colNr
+        ^ self insertStringWithoutCRs:aString atLine:lineNr col:colNr
     ].
 
     l := lineNr.
@@ -2155,19 +2154,19 @@
     start := 1.
     end := aString size.
     [start <= end] whileTrue:[
-	stop := aString indexOf:(Character cr) startingAt:start.
-	stop == 0 ifTrue:[
-	    stop := end + 1
-	].
-	subString := aString copyFrom:start to:(stop - 1).
-	self insertStringWithoutCRs:subString atLine:l col:c.
-	(stop <= end) ifTrue:[
-	    c := c + subString size.
-	    self insert:(Character cr) atLine:l col:c.
-	    l := l + 1.
-	    c := 1
-	].
-	start := stop + 1
+        stop := aString indexOf:(Character cr) startingAt:start.
+        stop == 0 ifTrue:[
+            stop := end + 1
+        ].
+        subString := aString copyFrom:start to:(stop - 1).
+        self insertStringWithoutCRs:subString atLine:l col:c.
+        (stop <= end) ifTrue:[
+            c := c + subString size.
+            self insert:(Character cr) atLine:l col:c.
+            l := l + 1.
+            c := 1
+        ].
+        start := stop + 1
     ]
 
     "Modified: / 10.6.1998 / 19:03:59 / cg"
@@ -2178,12 +2177,12 @@
      handle cr's correctly. A nil argument is interpreted as an empty line."
 
     aString isNil ifTrue:[
-	"new:"
-	self insertCharAtCursor:(Character cr).
-	^ self
+        "new:"
+        self insertCharAtCursor:(Character cr).
+        ^ self
     ].
     (aString includes:(Character cr)) ifFalse:[
-	^ self insertStringWithoutCRsAtCursor:aString
+        ^ self insertStringWithoutCRsAtCursor:aString
     ].
 
     self insertLines:aString asStringCollection withCR:false.
@@ -2207,18 +2206,18 @@
     |wasOn oldLen newLen|
 
     aString notNil ifTrue:[
-	wasOn := self hideCursor.
-	(aString includes:Character tab) ifTrue:[
-	    self checkForExistingLine:cursorLine.
-	    oldLen := (list at:cursorLine) size.
-	    self insertString:aString atLine:cursorLine col:cursorCol.
-	    newLen := (list at:cursorLine) size.
-	    cursorCol := cursorCol + (newLen - oldLen).
-	] ifFalse:[
-	    self insertString:aString atLine:cursorLine col:cursorCol.
-	    cursorCol := cursorCol + aString size.
-	].
-	wasOn ifTrue:[self showCursor]
+        wasOn := self hideCursor.
+        (aString includes:Character tab) ifTrue:[
+            self checkForExistingLine:cursorLine.
+            oldLen := (list at:cursorLine) size.
+            self insertString:aString atLine:cursorLine col:cursorCol.
+            newLen := (list at:cursorLine) size.
+            cursorCol := cursorCol + (newLen - oldLen).
+        ] ifFalse:[
+            self insertString:aString atLine:cursorLine col:cursorCol.
+            cursorCol := cursorCol + aString size.
+        ].
+        wasOn ifTrue:[self showCursor]
     ]
 
     "Modified: / 10.6.1998 / 20:43:52 / cg"
@@ -2244,25 +2243,25 @@
     lastLine := list size.
     finished := false.
     [finished] whileFalse:[
-	(lastLine <= 1) ifTrue:[
-	    finished := true
-	] ifFalse:[
-	    line := list at:lastLine.
-	    line notNil ifTrue:[
-		line isBlank ifTrue:[
-		    list at:lastLine put:nil.
-		    line := nil
-		]
-	    ].
-	    line notNil ifTrue:[
-		finished := true
-	    ] ifFalse:[
-		lastLine := lastLine - 1
-	    ]
-	]
+        (lastLine <= 1) ifTrue:[
+            finished := true
+        ] ifFalse:[
+            line := list at:lastLine.
+            line notNil ifTrue:[
+                line isBlank ifTrue:[
+                    list at:lastLine put:nil.
+                    line := nil
+                ]
+            ].
+            line notNil ifTrue:[
+                finished := true
+            ] ifFalse:[
+                lastLine := lastLine - 1
+            ]
+        ]
     ].
     (lastLine ~~ list size) ifTrue:[
-	list grow:lastLine.
+        list grow:lastLine.
 "/        self textChanged
     ]
 !
@@ -2274,10 +2273,10 @@
 
     wasOn := self hideCursor.
     aCharacter == (Character cr) ifTrue:[
-	self cursorReturn
+        self cursorReturn
     ] ifFalse:[
-	self replace:aCharacter atLine:cursorLine col:cursorCol.
-	self cursorRight.
+        self replace:aCharacter atLine:cursorLine col:cursorCol.
+        self cursorRight.
     ].
     self makeCursorVisibleAndShowCursor:wasOn.
 
@@ -2293,22 +2292,22 @@
     |line col nLines wasOn|
 
     lines notNil ifTrue:[
-	wasOn := self hideCursor.
-	nLines := lines size.
-	line := cursorLine.
-	col := cursorCol.
-	lines keysAndValuesDo:[:i :l |
-	    self replaceString:l atLine:line col:col.
-	    (i ~~ nLines or:[withCr]) ifTrue:[
-		line := line + 1.
-		col := 1.
-	    ] ifFalse:[
-		col := col + (l size).
-	    ]
-	].
-	self cursorLine:line col:col.
-	self makeCursorVisibleAndShowCursor:wasOn.
-	"/ wasOn ifTrue:[self showCursor].
+        wasOn := self hideCursor.
+        nLines := lines size.
+        line := cursorLine.
+        col := cursorCol.
+        lines keysAndValuesDo:[:i :l |
+            self replaceString:l atLine:line col:col.
+            (i ~~ nLines or:[withCr]) ifTrue:[
+                line := line + 1.
+                col := 1.
+            ] ifFalse:[
+                col := col + (l size).
+            ]
+        ].
+        self cursorLine:line col:col.
+        self makeCursorVisibleAndShowCursor:wasOn.
+        "/ wasOn ifTrue:[self showCursor].
     ]
 
     "Created: / 18.5.1996 / 15:32:06 / cg"
@@ -2333,38 +2332,38 @@
 
     sel := self selection.
     sel notNil ifTrue:[
-	lastString := sel.
-	self deleteSelection.
-	replacing := true.
-	lastReplacement := ''
+        lastString := sel.
+        self deleteSelection.
+        replacing := true.
+        lastReplacement := ''
     ].
 
     (something isMemberOf:Character) ifTrue:[
-	lastReplacement notNil ifTrue:[
+        lastReplacement notNil ifTrue:[
 "/ "XXX - replacing text with spaces ..."
 "/            (lastReplacement endsWith:Character space) ifTrue:[
 "/                lastReplacement := lastReplacement copyWithoutLast:1 "copyTo:(lastReplacement size - 1)".
 "/                lastReplacement := lastReplacement copyWith:something.
 "/                lastReplacement := lastReplacement copyWith:Character space
 "/            ] ifFalse:[
-		lastReplacement := lastReplacement copyWith:something.
+                lastReplacement := lastReplacement copyWith:something.
 "/            ]
-	].
-	insertMode ifTrue:[
-	    self insertCharAtCursor:something
-	] ifFalse:[
-	    self replaceCharAtCursor:something
-	]
+        ].
+        insertMode ifTrue:[
+            self insertCharAtCursor:something
+        ] ifFalse:[
+            self replaceCharAtCursor:something
+        ]
     ] ifFalse:[
-	lastReplacement := something.
-	insertMode ifTrue:[
-	    self insertStringAtCursor:something
-	] ifFalse:[
-	    self replaceStringAtCursor
-	]
+        lastReplacement := something.
+        insertMode ifTrue:[
+            self insertStringAtCursor:something
+        ] ifFalse:[
+            self replaceStringAtCursor
+        ]
     ].
     keep ifTrue:[
-	self cursorLine:l col:c
+        self cursorLine:l col:c
     ]
 
     "Modified: 9.10.1996 / 16:14:35 / cg"
@@ -2377,26 +2376,26 @@
 
     wasOn := self hideCursor.
     (aString includes:Character tab) ifTrue:[
-	"/ need special care for TAB (to move cursor correctly)
-	i1 := 1.
-	[i1 ~~ 0] whileTrue:[
-	    i2 := aString indexOf:Character tab startingAt:i1.
-	    i2 ~~ 0 ifTrue:[
-		i1 ~~ i2 ifTrue:[
-		    self replaceString:(aString copyFrom:i1 to:i2-1) atLine:cursorLine col:cursorCol.
-		    self cursorCol:(cursorCol + (i2 - i1)).
-		].
-		self replaceTABAtCursor.
-		i2 := i2 + 1.
-	    ] ifFalse:[
-		self replaceString:(aString copyFrom:i1) atLine:cursorLine col:cursorCol.
-		self cursorCol:(cursorCol + (aString size - i1 + 1)).
-	    ].
-	    i1 := i2.
-	]
+        "/ need special care for TAB (to move cursor correctly)
+        i1 := 1.
+        [i1 ~~ 0] whileTrue:[
+            i2 := aString indexOf:Character tab startingAt:i1.
+            i2 ~~ 0 ifTrue:[
+                i1 ~~ i2 ifTrue:[
+                    self replaceString:(aString copyFrom:i1 to:i2-1) atLine:cursorLine col:cursorCol.
+                    self cursorCol:(cursorCol + (i2 - i1)).
+                ].
+                self replaceTABAtCursor.
+                i2 := i2 + 1.
+            ] ifFalse:[
+                self replaceString:(aString copyFrom:i1) atLine:cursorLine col:cursorCol.
+                self cursorCol:(cursorCol + (aString size - i1 + 1)).
+            ].
+            i1 := i2.
+        ]
     ] ifFalse:[
-	self replaceString:aString atLine:cursorLine col:cursorCol.
-	self cursorCol:(cursorCol + aString size).
+        self replaceString:aString atLine:cursorLine col:cursorCol.
+        self cursorCol:(cursorCol + aString size).
     ].
     self makeCursorVisibleAndShowCursor:wasOn.
 
@@ -2494,17 +2493,17 @@
     startLine > list size ifTrue:[ ^ self]. "/ deleted space below text
 
     (startLine == endLine) ifTrue:[
-	"/ delete chars within a line
-	self deleteCharsAtLine:startLine fromCol:startCol toCol:endCol.
-	^ self
+        "/ 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 full lines only
+        endLine > startLine ifTrue:[
+            self deleteFromLine:startLine toLine:(endLine - 1)
+        ].
+        ^ self
     ].
 
     "/ delete right rest of 1st line
@@ -2512,38 +2511,38 @@
 
     "/ delete the inner lines ...
     endLine > (startLine + 1) ifTrue:[
-	self deleteFromLine:(startLine + 1) toLine:(endLine - 1)
+        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 startCol lies behond end of startLine
-
-	line := list at:startLine.
-	lineSize := line size.
-	(startCol > lineSize) ifTrue:[
-	    newLine := line.
-	    line isNil ifTrue:[
-		newLine := String new:(startCol - 1)
-	    ] ifFalse:[
-		nMore := startCol - 1 - lineSize.
-		nMore > 0 ifTrue:[
-		    newLine := line , (line species new:nMore)
-		]
-	    ].
-	    newLine ~~ line ifTrue:[
-		list at:startLine put:newLine.
-	    ].
-	    "/ TODO: remember old maxwidth of linerange,
-	    "/ only clear widthOfWidestLine, if this max
-	    "/ length was (one of) the longest.
-	    "/ avoids slow delete with huge texts.
-	    widthOfWidestLine := nil. "/ i.e. unknown
-	    self textChanged.
-	]
+        "/ delete the left rest of the last line
+
+        self deleteCharsAtLine:(startLine + 1) toCol:endCol.
+
+        "/ must add blanks, if startCol lies behond end of startLine
+
+        line := list at:startLine.
+        lineSize := line size.
+        (startCol > lineSize) ifTrue:[
+            newLine := line.
+            line isNil ifTrue:[
+                newLine := String new:(startCol - 1)
+            ] ifFalse:[
+                nMore := startCol - 1 - lineSize.
+                nMore > 0 ifTrue:[
+                    newLine := line , (line species new:nMore)
+                ]
+            ].
+            newLine ~~ line ifTrue:[
+                list at:startLine put:newLine.
+            ].
+            "/ TODO: remember old maxwidth of linerange,
+            "/ only clear widthOfWidestLine, if this max
+            "/ length was (one of) the longest.
+            "/ avoids slow delete with huge texts.
+            widthOfWidestLine := nil. "/ i.e. unknown
+            self textChanged.
+        ]
     ].
 
     "/ merge the left rest of 1st line with right rest of last line into one
@@ -2577,7 +2576,7 @@
 
     nLines := list size.
     (firstLineShown >= nLines) ifTrue:[
-	self makeLineVisible:nLines
+        self makeLineVisible:nLines
     ].
     wasOn ifTrue:[self showCursor].
 
@@ -2706,71 +2705,71 @@
      dstY "{ Class: SmallInteger }" |
 
     self isReadOnly ifTrue:[
-	^ self
+        ^ self
     ].
 
     autoIndent ifTrue:[
-	indent := self leftIndentForLine:lineNr.
-
-	text := someText collect:[:ln||line|
-	    ln notNil ifTrue:[
-		line := ln withoutLeadingSeparators.
-		(line isEmpty or:[indent == 0]) ifFalse:[
-		    line := (String new:indent), line
-		].
-		line
-	    ] ifFalse:[
-		nil
-	    ]
-	].
+        indent := self leftIndentForLine:lineNr.
+
+        text := someText collect:[:ln||line|
+            ln notNil ifTrue:[
+                line := ln withoutLeadingSeparators.
+                (line isEmpty or:[indent == 0]) ifFalse:[
+                    line := (String new:indent), line
+                ].
+                line
+            ] ifFalse:[
+                nil
+            ]
+        ].
     ] ifFalse:[
-	text := someText
+        text := someText
     ].
 
     visLine := self listLineToVisibleLine:lineNr.
     (shown not or:[visLine isNil]) ifTrue:[
-	self withoutRedrawInsertLines:text
-				 from:start to:end
-			       before:lineNr.
+        self withoutRedrawInsertLines:text
+                                 from:start to:end
+                               before:lineNr.
     ] ifFalse:[
-	nLines := end - start + 1.
-	((visLine + nLines) >= nLinesShown) ifTrue:[
-	    self withoutRedrawInsertLines:text
-				     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:text
-				     from:start to:end
-				   before:lineNr.
-	    self 
-		copyFrom:self 
-		x:textStartLeft y:srcY
-		toX:textStartLeft y:dstY
-		width:w
-		height:(height - dstY)
-		async:true.
-	    self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
-	    self waitForExpose
-	].
+        nLines := end - start + 1.
+        ((visLine + nLines) >= nLinesShown) ifTrue:[
+            self withoutRedrawInsertLines:text
+                                     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:text
+                                     from:start to:end
+                                   before:lineNr.
+            self 
+                copyFrom:self 
+                x:textStartLeft y:srcY
+                toX:textStartLeft y:dstY
+                width:w
+                height:(height - dstY)
+                async:true.
+            self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
+            self waitForExpose
+        ].
     ].
     widthOfWidestLine notNil ifTrue:[
-	text do:[:line |
-	    widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
-	]
+        text do:[:line |
+            widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
+        ]
     ].
     self textChanged.
 
@@ -2835,7 +2834,7 @@
     self checkModificationsAllowed ifFalse:[ ^ self].
 
     aCharacter == (Character cr) ifTrue:[
-	^ self
+        ^ self
     ].
 
     drawCharacterOnly := true.
@@ -2846,35 +2845,35 @@
     (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: [
-	(colNr > lineSize) ifTrue: [
-	    newLine := line species new:colNr.
-	    newLine replaceFrom:1 to:lineSize with:line startingAt:1.
-	] ifFalse: [
-	    newLine := line copy.
-	]
+        (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.
     aCharacter == (Character tab) ifTrue:[
-	newLine := self withTabsExpanded:newLine.
-	drawCharacterOnly := false
+        newLine := self withTabsExpanded:newLine.
+        drawCharacterOnly := false
     ].
     list at:lineNr put:newLine.
     widthOfWidestLine notNil ifTrue:[
-	widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
     ].
     self textChanged.
     shown ifTrue:[
-	drawCharacterOnly ifTrue:[
-	    self redrawLine:lineNr col:colNr
-	] ifFalse:[
-	    self redrawLine:lineNr from:colNr
-	]
+        drawCharacterOnly ifTrue:[
+            self redrawLine:lineNr col:colNr
+        ] ifFalse:[
+            self redrawLine:lineNr from:colNr
+        ]
     ]
 
     "Created: / 6.3.1996 / 12:29:20 / cg"
@@ -2896,35 +2895,35 @@
 
     endCol := colNr + aString size - 1.
     (lineSize == 0) ifTrue:[
-	newLine := aString species new:endCol.
+        newLine := aString species new:endCol.
     ] ifFalse: [
-	(endCol > lineSize) ifTrue: [
-	    aString isText ifTrue:[
-		newLine := aString species new:endCol.
-	    ] ifFalse:[
-		newLine := line species new:endCol.
-	    ].
-	    newLine replaceFrom:1 to:lineSize with:line startingAt:1.
-	] ifFalse: [
-	    aString isText ifTrue:[
-		newLine := aString species new:line size.
-		newLine replaceFrom:1 to:lineSize with:line startingAt:1.
-	    ] ifFalse:[
-		newLine := line copy.
-	    ]
-	]
+        (endCol > lineSize) ifTrue: [
+            aString isText ifTrue:[
+                newLine := aString species new:endCol.
+            ] ifFalse:[
+                newLine := line species new:endCol.
+            ].
+            newLine replaceFrom:1 to:lineSize with:line startingAt:1.
+        ] ifFalse: [
+            aString isText ifTrue:[
+                newLine := aString species new:line size.
+                newLine replaceFrom:1 to:lineSize with:line startingAt:1.
+            ] ifFalse:[
+                newLine := line copy.
+            ]
+        ]
     ].
     newLine replaceFrom:colNr with:aString.
     (aString includes:(Character tab)) ifTrue:[
-	newLine := self withTabsExpanded:newLine.
+        newLine := self withTabsExpanded:newLine.
     ].
     list at:lineNr put:newLine.
     widthOfWidestLine notNil ifTrue:[
-	widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
     ].
     self textChanged.
     shown ifTrue:[
-	self redrawLine:lineNr from:colNr
+        self redrawLine:lineNr from:colNr
     ]
 
     "Created: / 11.6.1998 / 10:38:32 / cg"
@@ -2939,52 +2938,52 @@
      srcY    "{ Class: SmallInteger }" |
 
     list isNil ifFalse:[
-	lineNr > (list size) ifFalse:[
-	    (colNr == 1) ifTrue:[
-		self insertLine:nil before:lineNr.
-		^ self
-	    ].
-	    line := list at:lineNr.
-	    line isNil ifFalse:[
-		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]
-	    ].
-	    list at:lineNr put:leftRest.
-	    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]
-	    ].
-	    widthOfWidestLine := nil. "/ unknown
-	    self textChanged.
-	]
+        lineNr > (list size) ifFalse:[
+            (colNr == 1) ifTrue:[
+                self insertLine:nil before:lineNr.
+                ^ self
+            ].
+            line := list at:lineNr.
+            line isNil ifFalse:[
+                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]
+            ].
+            list at:lineNr put:leftRest.
+            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]
+            ].
+            widthOfWidestLine := nil. "/ unknown
+            self textChanged.
+        ]
     ]
 
     "Modified: 29.1.1997 / 13:03:22 / cg"
@@ -3001,20 +3000,20 @@
 
     line := aString.
     line notNil ifTrue:[
-	line isString ifTrue:[
-	    line isBlank ifTrue:[
-		line := nil
-	    ] ifFalse:[
-		(line includes:(Character tab)) ifTrue:[
-		    line := self withTabsExpanded:line
-		]
-	    ]
-	]
+        line isString ifTrue:[
+            line isBlank ifTrue:[
+                line := nil
+            ] ifFalse:[
+                (line includes:(Character tab)) ifTrue:[
+                    line := self withTabsExpanded:line
+                ]
+            ]
+        ]
     ].
     list isNil ifTrue: [
-	list := StringCollection new:lineNr
+        list := StringCollection new:lineNr
     ] ifFalse: [
-	list grow:((list size + 1) max:lineNr)
+        list grow:((list size + 1) max:lineNr)
     ].
 
     "I have changed 'replaceFrom:to:with:startingAt:' to correctly handle 
@@ -3022,9 +3021,9 @@
 "
     index := list size.
     [index > lineNr] whileTrue: [
-	pIndex := index - 1.
-	list at:index put:(list at:pIndex).
-	index := pIndex
+        pIndex := index - 1.
+        list at:index put:(list at:pIndex).
+        index := pIndex
     ].
 "
     list replaceFrom:(lineNr + 1) to:(list size) with:list startingAt:lineNr.
@@ -3044,24 +3043,24 @@
     nLines := end - start + 1.
     newLines := Array new:(lines size).
     start to:end do:[:index |
-	newLine := lines at:index.
-	newLine notNil ifTrue:[
-	    newLine isString ifTrue:[
-		newLine isBlank ifTrue:[
-		    newLine := nil
-		] ifFalse:[
-		    (newLine includes:(Character tab)) ifTrue:[
-			newLine := self withTabsExpanded:newLine
-		    ]
-		]
-	    ]
-	].
-	newLines at:index put:newLine
+        newLine := lines at:index.
+        newLine notNil ifTrue:[
+            newLine isString ifTrue:[
+                newLine isBlank ifTrue:[
+                    newLine := nil
+                ] ifFalse:[
+                    (newLine includes:(Character tab)) ifTrue:[
+                        newLine := self withTabsExpanded:newLine
+                    ]
+                ]
+            ]
+        ].
+        newLines at:index put:newLine
     ].
     list isNil ifTrue: [
-	list := StringCollection new:(lineNr + nLines + 1)
+        list := StringCollection new:(lineNr + nLines + 1)
     ] ifFalse: [
-	list grow:((list size + nLines) max:(lineNr + nLines - 1))
+        list grow:((list size + nLines) max:(lineNr + nLines - 1))
     ].
 
     "I have changed 'replaceFrom:to:with:startingAt:' to correctly handle 
@@ -3069,9 +3068,9 @@
 "
     index := list size.
     [index > lineNr] whileTrue: [
-	pIndex := index - 1.
-	list at:index put:(list at:pIndex).
-	index := pIndex
+        pIndex := index - 1.
+        list at:index put:(list at:pIndex).
+        index := pIndex
     ].
 "
     list replaceFrom:(lineNr + nLines) to:(list size) with:list startingAt:lineNr.
@@ -3096,53 +3095,53 @@
     line       := list at:lineNr.
 
     line notNil ifTrue:[
-	lineSize := line size.
-	line bitsPerCharacter > aString bitsPerCharacter ifTrue:[
-	    stringType := line string species
-	].
-	line isText ifTrue:[ isText := true ]
+        lineSize := line size.
+        line bitsPerCharacter > aString bitsPerCharacter ifTrue:[
+            stringType := line string species
+        ].
+        line isText ifTrue:[ isText := true ]
 
     ] ifFalse:[
-	lineSize := 0
+        lineSize := 0
     ].
 
     ((colNr == 1) and:[lineSize == 0]) ifTrue: [
-	newLine := aString
+        newLine := aString
     ] ifFalse:[
-	(lineSize == 0 or:[colNr > lineSize]) ifTrue: [
-	    sz := colNr + strLen - 1
-	] ifFalse:[
-	    sz := lineSize + strLen
-	].
-
-	isText ifFalse:[
-	    newLine := stringType new:sz
-	] ifTrue:[
-	    newLine := Text string:(stringType new:sz)
-	].
-
-	(lineSize ~~ 0) ifTrue: [
-	    (colNr > lineSize) ifTrue: [
-		newLine replaceFrom:1 to:lineSize
-			       with:line startingAt:1
-	    ] ifFalse: [
-		newLine replaceFrom:1 to:(colNr - 1)
-			       with:line startingAt:1.
-		newLine replaceFrom:(colNr + strLen) to:(lineSize + strLen)
-			       with:line startingAt:colNr
-	    ]
-	].
-	newLine replaceFrom:colNr to:(colNr + strLen - 1)
-		       with:aString startingAt:1
+        (lineSize == 0 or:[colNr > lineSize]) ifTrue: [
+            sz := colNr + strLen - 1
+        ] ifFalse:[
+            sz := lineSize + strLen
+        ].
+
+        isText ifFalse:[
+            newLine := stringType new:sz
+        ] ifTrue:[
+            newLine := Text string:(stringType new:sz)
+        ].
+
+        (lineSize ~~ 0) ifTrue: [
+            (colNr > lineSize) ifTrue: [
+                newLine replaceFrom:1 to:lineSize
+                               with:line startingAt:1
+            ] ifFalse: [
+                newLine replaceFrom:1 to:(colNr - 1)
+                               with:line startingAt:1.
+                newLine replaceFrom:(colNr + strLen) to:(lineSize + strLen)
+                               with:line startingAt:colNr
+            ]
+        ].
+        newLine replaceFrom:colNr to:(colNr + strLen - 1)
+                       with:aString startingAt:1
     ].
 
     (aString includes:(Character tab)) ifTrue:[
-	newLine := self withTabsExpanded:newLine
+        newLine := self withTabsExpanded:newLine
     ].
 
     list at:lineNr put:newLine.
     widthOfWidestLine notNil ifTrue:[
-	widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
+        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
     ].
     self textChanged.
 
@@ -3156,15 +3155,15 @@
 
     hasKeyboardFocus := true.
     cursorShown ifTrue: [
-	self drawCursor
+        self drawCursor
     ].
 
     ((button == 1) or:[button == #select]) ifTrue:[
-	self hideCursor
+        self hideCursor
     ].
     (button == #paste) ifTrue:[
-	self pasteOrReplace.
-	^ self
+        self pasteOrReplace.
+        ^ self
     ].
     super buttonPress:button x:x y:y
 
@@ -3175,17 +3174,17 @@
     "move the cursor to the click-position of previous button press"
 
     ((button == 1) or:[button == #select]) ifTrue:[
-	typeOfSelection := nil. 
-	selectionStartLine isNil ifTrue:[
-	    clickCol notNil ifTrue:[
-		self cursorMovementAllowed ifTrue:[
-		    self cursorLine:clickLine col:clickCol
-		]
-	    ]
-	] ifFalse:[
-	    lastString := nil. "new selection invalidates remembered string"
-	].
-	self showCursor
+        typeOfSelection := nil. 
+        selectionStartLine isNil ifTrue:[
+            clickCol notNil ifTrue:[
+                self cursorMovementAllowed ifTrue:[
+                    self cursorLine:clickLine col:clickCol
+                ]
+            ]
+        ] ifFalse:[
+            lastString := nil. "new selection invalidates remembered string"
+        ].
+        self showCursor
     ].
     super buttonRelease:button x:x y:y
 
@@ -3695,7 +3694,7 @@
     cv := cursorVisibleLine.
     super sizeChanged:how.
     cv notNil ifTrue:[
-	self makeLineVisible:cursorLine
+        self makeLineVisible:cursorLine
     ]
 ! !
 
@@ -3737,7 +3736,7 @@
     and:[(styleSheet at:#'editText.requestFocusOnPointerEnter' default:true)
     and:[self enabled 
     and:[readOnly not]]]) ifTrue:[
-	^ true
+        ^ true
     ].
 
     ^ false
@@ -3757,7 +3756,7 @@
     start := selectionStartLine.
     end := selectionEndLine.
     (selectionEndCol == 0) ifTrue:[
-	end := end - 1
+        end := end - 1
     ].
     self unselect.
     self indentFromLine:start toLine:end
@@ -3776,34 +3775,34 @@
     delta := leftStart - (self leftIndentOfLine:start).
     (delta == 0) ifTrue:[^ self].
     (delta > 0) ifTrue:[
-	spaces := String new:delta
+        spaces := String new:delta
     ].
     start to:end do:[:lineNr |
-	line := self listAt:lineNr.
-	line notNil ifTrue:[
-	    line isBlank ifTrue:[
-		list at:lineNr put:nil
-	    ] ifFalse:[
-		(delta > 0) ifTrue:[
-		    line := spaces , line.
-		    widthOfWidestLine notNil ifTrue:[
-			widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
-		    ]
-		] ifFalse:[
-		    "check if deletion is ok"
-		    d := delta negated + 1.
-
-		    line size > d ifTrue:[
-			(line copyTo:(d - 1)) withoutSeparators isEmpty ifTrue:[
-			    line := line copyFrom:d
-			]
-		    ].
-		    widthOfWidestLine := nil
-		].
-		list at:lineNr put:line.
-		self textChanged.
-	    ]
-	]
+        line := self listAt:lineNr.
+        line notNil ifTrue:[
+            line isBlank ifTrue:[
+                list at:lineNr put:nil
+            ] ifFalse:[
+                (delta > 0) ifTrue:[
+                    line := spaces , line.
+                    widthOfWidestLine notNil ifTrue:[
+                        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
+                    ]
+                ] ifFalse:[
+                    "check if deletion is ok"
+                    d := delta negated + 1.
+
+                    line size > d ifTrue:[
+                        (line copyTo:(d - 1)) withoutSeparators isEmpty ifTrue:[
+                            line := line copyFrom:d
+                        ]
+                    ].
+                    widthOfWidestLine := nil
+                ].
+                list at:lineNr put:line.
+                self textChanged.
+            ]
+        ]
     ].
     self redrawFromLine:start to:end
 
@@ -3822,15 +3821,15 @@
     lnr := lineNr.
 
     [lnr ~~ 1] whileTrue:[
-	lnr  := lnr - 1.
-	line := self listAt:lnr.
-
-	line notNil ifTrue:[
-	    indent := line indexOfNonSeparatorStartingAt:1.
-	    indent ~~ 0 ifTrue:[
-		^ indent - 1
-	    ]
-	]
+        lnr  := lnr - 1.
+        line := self listAt:lnr.
+
+        line notNil ifTrue:[
+            indent := line indexOfNonSeparatorStartingAt:1.
+            indent ~~ 0 ifTrue:[
+                ^ indent - 1
+            ]
+        ]
     ].
     ^ 0
 
@@ -3972,7 +3971,7 @@
     "return a default value to show in the gotoLine box"
 
     cursorLine notNil ifTrue:[
-	^ cursorLine
+        ^ cursorLine
     ].
     ^ super defaultForGotoLine
 !
@@ -4061,14 +4060,14 @@
     |sel|
 
     self checkModificationsAllowed ifFalse:[
-	self flash.
-	^ self
+        self flash.
+        ^ self
     ].
 
     sel := self getTextSelection.
     self unselect.  
     sel notNil ifTrue:[
-	self paste:sel.
+        self paste:sel.
     ]
 
     "Modified: / 5.4.1998 / 16:55:02 / cg"
@@ -4124,13 +4123,13 @@
     |sel|
 
     self checkModificationsAllowed ifFalse:[
-	self flash.
-	^ self
+        self flash.
+        ^ self
     ].
 
     sel := self getTextSelection.
     sel notNil ifTrue:[
-	self pasteOrReplace:sel.
+        self pasteOrReplace:sel.
     ].
 
     "Modified: / 5.4.1998 / 16:55:16 / cg"
@@ -4160,7 +4159,7 @@
 
     sel := self getTextSelection.
     sel notNil ifTrue:[
-	self replace:sel
+        self replace:sel
     ]
 
     "Modified: / 5.4.1998 / 16:55:24 / cg"
@@ -4273,13 +4272,13 @@
      and may show a warnBox or whatever."
 
     self isReadOnly ifTrue: [
-	exceptionBlock isNil ifTrue:[
-	    ^ false
-	].
-
-	(exceptionBlock value:'Text may not be modified') ~~ true ifTrue:[
-	    ^ false
-	]
+        exceptionBlock isNil ifTrue:[
+            ^ false
+        ].
+
+        (exceptionBlock value:'Text may not be modified') ~~ true ifTrue:[
+            ^ false
+        ]
     ].
     ^ true
 
@@ -4364,8 +4363,8 @@
 
     w := super widthOfContents.
     (dev := device) isNil ifTrue:[
-	"/ really dont know ...
-	dev := Screen current
+        "/ really dont know ...
+        dev := Screen current
     ].
     ^ w + (font widthOn:dev)
 
@@ -4393,11 +4392,11 @@
     "redraw the cursor, if it sits in a line range"
 
     cursorShown ifTrue:[
-	cursorVisibleLine notNil ifTrue:[
-	    (cursorVisibleLine between:startVisLine and:endVisLine) ifTrue:[
-		self drawCursorCharacter
-	    ]
-	]
+        cursorVisibleLine notNil ifTrue:[
+            (cursorVisibleLine between:startVisLine and:endVisLine) ifTrue:[
+                self drawCursorCharacter
+            ]
+        ]
     ]
 !
 
@@ -4405,9 +4404,9 @@
     "redraw the cursor, if it sits in visible line"
 
     cursorShown ifTrue:[
-	(visLine == cursorVisibleLine) ifTrue:[
-	    self drawCursorCharacter
-	]
+        (visLine == cursorVisibleLine) ifTrue:[
+            self drawCursorCharacter
+        ]
     ]
 !
 
@@ -4429,12 +4428,12 @@
     "redraw the single character in visibleline at colNr"
 
     cursorShown ifTrue:[
-	(visLine == cursorVisibleLine) ifTrue:[
-	    (colNr == cursorCol) ifTrue:[
-		self drawCursorCharacter.
-		^ self
-	    ]
-	]
+        (visLine == cursorVisibleLine) ifTrue:[
+            (colNr == cursorCol) ifTrue:[
+                self drawCursorCharacter.
+                ^ self
+            ]
+        ]
     ].
     super redrawVisibleLine:visLine col:colNr
 !
@@ -4496,7 +4495,7 @@
     "
     cursorVisibleLine := self listLineToVisibleLine:cursorLine.
     prevCursorState ifTrue:[
-	self showCursor
+        self showCursor
     ]
 
     "Modified: / 17.6.1998 / 16:13:24 / cg"
@@ -4508,7 +4507,7 @@
     prevCursorState := cursorShown.
     "/ cursorShown := false.
     cursorShown ifTrue:[
-	self hideCursor
+        self hideCursor
     ]
 
     "Modified: / 6.7.1998 / 13:07:23 / cg"
@@ -4545,21 +4544,21 @@
 
     cursorLine isNil ifTrue:[^ self].
     selectionStartLine notNil ifTrue:[
-	startLine := selectionStartLine.
-	startCol := selectionStartCol
+        startLine := selectionStartLine.
+        startCol := selectionStartCol
     ] ifFalse:[
-	startLine := cursorLine min:list size.
-	startCol := cursorCol
+        startLine := cursorLine min:list size.
+        startCol := cursorCol
     ].
     self 
-	searchBackwardFor:pattern 
-	startingAtLine:startLine col:startCol
-	ifFound:[:line :col |
-	    self cursorLine:line col:col.
-	    self showMatch:pattern atLine:line col:col.
+        searchBackwardFor:pattern 
+        startingAtLine:startLine col:startCol
+        ifFound:[:line :col |
+            self cursorLine:line col:col.
+            self showMatch:pattern atLine:line col:col.
 "/            self makeLineVisible:cursorLine
-	    typeOfSelection := #search] 
-	ifAbsent:aBlock
+            typeOfSelection := #search] 
+        ifAbsent:aBlock
 
     "Modified: 9.10.1997 / 13:02:04 / cg"
 !
@@ -4571,22 +4570,22 @@
 
     cursorLine isNil ifTrue:[^ self].
     selectionStartLine notNil ifTrue:[
-	startLine := selectionStartLine.
-	startCol := selectionStartCol
+        startLine := selectionStartLine.
+        startCol := selectionStartCol
     ] ifFalse:[
-	startLine := cursorLine min:list size.
-	startCol := cursorCol
+        startLine := cursorLine min:list size.
+        startCol := cursorCol
     ].
     self 
-	searchBackwardFor:pattern
-	ignoreCase:ign
-	startingAtLine:startLine col:startCol
-	ifFound:[:line :col |
-	    self cursorLine:line col:col.
-	    self showMatch:pattern atLine:line col:col.
+        searchBackwardFor:pattern
+        ignoreCase:ign
+        startingAtLine:startLine col:startCol
+        ifFound:[:line :col |
+            self cursorLine:line col:col.
+            self showMatch:pattern atLine:line col:col.
 "/            self makeLineVisible:cursorLine
-	    typeOfSelection := #search] 
-	ifAbsent:aBlock
+            typeOfSelection := #search] 
+        ifAbsent:aBlock
 
     "Modified: 9.10.1997 / 13:02:13 / cg"
 !
@@ -4595,12 +4594,12 @@
     "select characters enclosed by matching parenthesis if one is under cusor"
 
     self 
-	searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
-	ifFound:[:line :col | 
-		  self selectFromLine:cursorLine col:cursorCol
-			       toLine:line col:col]
-	ifNotFound:[self showNotFound]
-	onError:[self beep]
+        searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
+        ifFound:[:line :col | 
+                  self selectFromLine:cursorLine col:cursorCol
+                               toLine:line col:col]
+        ifNotFound:[self showNotFound]
+        onError:[self beep]
 
     "Modified: 9.10.1997 / 12:57:34 / cg"
 !
@@ -4612,10 +4611,10 @@
      Positions the cursor if found, peeps if not"
 
      self 
-	searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
-	ifFound:[:line :col | self cursorLine:line col:col]
-	ifNotFound:[self showNotFound]
-	onError:[self beep]
+        searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
+        ifFound:[:line :col | self cursorLine:line col:col]
+        ifNotFound:[self showNotFound]
+        onError:[self beep]
 
     "Modified: 9.10.1997 / 12:56:30 / cg"
 !
@@ -4629,15 +4628,15 @@
     "/ assume its the first search and do not skip the very first match
     startCol := cursorCol.
     self hasSelection ifFalse:[
-	(cursorLine == 1 and:[cursorCol == 1]) ifTrue:[
-	    startCol := 0
-	]
+        (cursorLine == 1 and:[cursorCol == 1]) ifTrue:[
+            startCol := 0
+        ]
     ].
 
     self 
-	searchFwd:pattern 
-	startingAtLine:cursorLine col:startCol 
-	ifAbsent:aBlock
+        searchFwd:pattern 
+        startingAtLine:cursorLine col:startCol 
+        ifAbsent:aBlock
 
     "Modified: 9.10.1997 / 12:58:59 / cg"
 !
@@ -4651,16 +4650,16 @@
     "/ assume its the first search and do not skip the very first match
     startCol := cursorCol.
     self hasSelection ifFalse:[
-	(cursorLine == 1 and:[cursorCol == 1]) ifTrue:[
-	    startCol := 0
-	]
+        (cursorLine == 1 and:[cursorCol == 1]) ifTrue:[
+            startCol := 0
+        ]
     ].
 
     self 
-	searchFwd:pattern
-	ignoreCase:ign
-	startingAtLine:cursorLine col:startCol 
-	ifAbsent:aBlock
+        searchFwd:pattern
+        ignoreCase:ign
+        startingAtLine:cursorLine col:startCol 
+        ifAbsent:aBlock
 
     "Modified: 9.10.1997 / 12:58:59 / cg"
     "Created: 9.10.1997 / 13:04:10 / cg"
@@ -4671,15 +4670,15 @@
 
     cursorLine isNil ifTrue:[^ self].
     self 
-	searchForwardFor:pattern 
-	ignoreCase:ign
-	startingAtLine:startLine col:startCol
-	ifFound:[:line :col |
-	    self cursorLine:line col:col.
-	    self showMatch:pattern atLine:line col:col.
+        searchForwardFor:pattern 
+        ignoreCase:ign
+        startingAtLine:startLine col:startCol
+        ifFound:[:line :col |
+            self cursorLine:line col:col.
+            self showMatch:pattern atLine:line col:col.
 "/            self makeLineVisible:cursorLine
-	    typeOfSelection := #search]
-	ifAbsent:aBlock
+            typeOfSelection := #search]
+        ifAbsent:aBlock
 
     "Modified: 9.10.1997 / 12:57:47 / cg"
     "Created: 9.10.1997 / 13:01:12 / cg"
@@ -4689,13 +4688,13 @@
     "do a forward search"
 
     self 
-	searchForwardFor:pattern 
-	startingAtLine:startLine col:startCol
-	ifFound:[:line :col |
-	    self cursorLine:line col:col.
-	    self showMatch:pattern atLine:line col:col.
-	    typeOfSelection := #search]
-	ifAbsent:aBlock
+        searchForwardFor:pattern 
+        startingAtLine:startLine col:startCol
+        ifFound:[:line :col |
+            self cursorLine:line col:col.
+            self showMatch:pattern atLine:line col:col.
+            typeOfSelection := #search]
+        ifAbsent:aBlock
 
     "Modified: 9.10.1997 / 13:07:52 / cg"
 !
@@ -4753,10 +4752,10 @@
      cursor to be moved in this case."
 
     list isNil ifTrue:[
-	self unselect
+        self unselect
     ] ifFalse:[
-	super selectFromLine:1 col:1 toLine:(list size + 1) col:0.
-	typeOfSelection := nil
+        super selectFromLine:1 col:1 toLine:(list size + 1) col:0.
+        typeOfSelection := nil
     ]
 
     "Modified: 28.2.1997 / 19:14:54 / cg"
@@ -4772,8 +4771,8 @@
     "select cursorline up to cursor position"
 
     cursorCol > 1 ifTrue:[
-	self selectFromLine:cursorLine col:1
-		     toLine:cursorLine col:(cursorCol-1)
+        self selectFromLine:cursorLine col:1
+                     toLine:cursorLine col:(cursorCol-1)
     ]
 
     "Modified: 16.8.1996 / 19:14:14 / cg"
@@ -4783,11 +4782,11 @@
     "expand selection by one line or select cursorline"
 
     selectionStartLine isNil ifTrue:[
-	self selectCursorLine
+        self selectCursorLine
     ] ifFalse:[
-	self selectFromLine:selectionStartLine col:selectionStartCol
-		     toLine:cursorLine+1 col:0.
-	self makeLineVisible:selectionEndLine
+        self selectFromLine:selectionStartLine col:selectionStartCol
+                     toLine:cursorLine+1 col:0.
+        self makeLineVisible:selectionEndLine
     ]
 !
 
@@ -4797,15 +4796,15 @@
     |col|
 
     list isNil ifTrue:[
-	self unselect
+        self unselect
     ] ifFalse:[
-	cursorCol == 0 ifTrue:[
-	    col := 0
-	] ifFalse:[
-	    col := cursorCol - 1
-	].
-	super selectFromLine:1 col:1 toLine:cursorLine col:col.
-	typeOfSelection := nil
+        cursorCol == 0 ifTrue:[
+            col := 0
+        ] ifFalse:[
+            col := cursorCol - 1
+        ].
+        super selectFromLine:1 col:1 toLine:cursorLine col:col.
+        typeOfSelection := nil
     ]
 !
 
@@ -4815,7 +4814,7 @@
 
     super selectFromLine:startLine col:startCol toLine:endLine col:endCol.
     (selectionEndLine notNil and:[self autoMoveCursorToEndOfSelection]) ifTrue:[
-	self cursorLine:selectionEndLine col:(selectionEndCol + 1).
+        self cursorLine:selectionEndLine col:(selectionEndCol + 1).
     ].
     typeOfSelection := nil
 !
@@ -4824,10 +4823,10 @@
     "select the text from the current cursor position to the end."
 
     list isNil ifTrue:[
-	self unselect
+        self unselect
     ] ifFalse:[
-	super selectFromLine:cursorLine col:cursorCol toLine:(list size + 1) col:0.
-	typeOfSelection := nil
+        super selectFromLine:cursorLine col:cursorCol toLine:(list size + 1) col:0.
+        typeOfSelection := nil
     ]
 !
 
@@ -4931,13 +4930,13 @@
     "currently not implemented"
 
     undoAction notNil ifTrue:[
-	undoAction value.
-	undoAction := nil.
+        undoAction value.
+        undoAction := nil.
     ]
 ! !
 
 !EditTextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.246 2001-04-26 10:12:03 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.247 2001-04-26 12:24:21 cg Exp $'
 ! !