TextView.st
changeset 59 450ce95a72a4
parent 53 b587b15eafab
child 60 f3c738c24ce6
--- a/TextView.st	Tue Aug 30 00:54:47 1994 +0200
+++ b/TextView.st	Mon Oct 10 04:03:47 1994 +0100
@@ -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
@@ -12,27 +12,29 @@
 
 ListView subclass:#TextView
        instanceVariableNames:'selectionStartLine selectionStartCol
-                              selectionEndLine selectionEndCol
-                              clickStartLine clickStartCol
-                              clickLine clickCol clickCount
-                              wordStartCol wordStartLine wordEndCol wordEndLine
-                              selectionFgColor selectionBgColor
-                              fileBox searchBox lineNumberBox
-                              selectStyle 
-                              directoryForFileDialog
-                              contentsWasSaved'
+			      selectionEndLine selectionEndCol
+			      clickStartLine clickStartCol
+			      clickLine clickCol clickCount
+			      wordStartCol wordStartLine wordEndCol wordEndLine
+			      selectionFgColor selectionBgColor
+			      fileBox searchBox lineNumberBox
+			      selectStyle 
+			      directoryForFileDialog
+			      contentsWasSaved'
        classVariableNames:'MyFontPanel
-                           DefaultSelectionForegroundColor
-                           DefaultSelectionBackgroundColor'
+			   DefaultFont
+			   DefaultViewBackground
+			   DefaultSelectionForegroundColor
+			   DefaultSelectionBackgroundColor'
        poolDictionaries:''
        category:'Views-Text'
 !
 
 TextView comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
-             All Rights Reserved
+	     All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.9 1994-08-23 23:39:35 claus Exp $
+$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.10 1994-10-10 03:03:11 claus Exp $
 '!
 
 !TextView class methodsFor:'documentation'!
@@ -40,7 +42,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
@@ -53,7 +55,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.9 1994-08-23 23:39:35 claus Exp $
+$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.10 1994-10-10 03:03:11 claus Exp $
 "
 !
 
@@ -86,15 +88,20 @@
 !TextView class methodsFor:'startup'!
 
 setupEmpty
-    "create a textview - a helper for startWith: and startOn:"
+    "create a textview in a topview, with horizontal and
+     vertical scrollbars - a helper for #startWith: and #startOn:"
 
     |top frame label|
 
     label := 'unnamed'.
-    top := StandardSystemView label:label
-                               icon:(Form fromFile:'Editor.xbm' resolution:100).
+    top := StandardSystemView 
+		label:label
+		 icon:(Form fromFile:'Editor.xbm' resolution:100).
 
-    frame := ScrollableView for:self in:top.
+    frame := HVScrollableView 
+		for:self 
+		miniScrollerH:true miniScrollerV:false
+		in:top.
     frame origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
     ^ frame scrolledView
 !
@@ -113,14 +120,16 @@
     textView := self setupEmpty.
     top := textView topView.
     aString notNil ifTrue:[
-        textView contents:aString
+	textView contents:aString
     ].
 
     top open.
     ^ textView
 
-    "TextView openWith:'some text'"
-    "EditTextView openWith:'some text'"
+    "
+     TextView openWith:'some text'
+     EditTextView openWith:'some text'
+    "
 !
 
 openOn:aFileName
@@ -131,24 +140,29 @@
     textView := self setupEmpty.
     top := textView topView.
     aFileName notNil ifTrue:[
-        top label:(OperatingSystem baseNameOf:aFileName).
-        textView contents:(aFileName asFilename readStream contents)
+	top label:(OperatingSystem baseNameOf:aFileName).
+	textView contents:(aFileName asFilename readStream contents)
     ].
 
     top open.
     ^ textView
 
-    "TextView openOn:'../doc/info.doc'"
-    "EditTextView openOn:'../doc/info.doc'"
+    "
+     TextView openOn:'../doc/info.doc'
+     EditTextView openOn:'../doc/info.doc'
+    "
 ! !
 
-!TextView class methodsFor:'flushing cached resources'!
+!TextView class methodsFor:'defaults'!
 
-updateClassResources
-    "sent on style changes ..."
-
-    DefaultSelectionForegroundColor := nil.
-    super updateClassResources.
+updateStyleCache
+    DefaultViewBackground := StyleSheet at:'textViewBackground' default:White.
+    DefaultSelectionForegroundColor := StyleSheet at:'textSelectionForegroundColor'.
+    DefaultSelectionBackgroundColor := StyleSheet at:'textSelectionBackgroundColor'.
+    DefaultFont := StyleSheet at:'textFont'.
+    DefaultFont notNil ifTrue:[
+	DefaultFont := DefaultFont on:Display
+    ].
 ! !
 
 !TextView methodsFor:'initialize & release'!
@@ -159,35 +173,32 @@
 !
 
 initStyle
-    |defFg defBg|
-
     super initStyle.
 
-    viewBackground := White.
-
-    DefaultSelectionForegroundColor isNil ifTrue:[
-        "
-         if running on a color display, we hilight by drawing black on green
-         (looks like a text-marker) otherwise, we draw reverse.
-        "
-
-        device hasColors ifTrue:[
-            defFg := fgColor.
-            defBg := Color red:0 green:100 blue:0
-        ] ifFalse:[
-            device hasGreyscales ifTrue:[
-                defFg := fgColor.
-                defBg := Color lightGrey 
-            ] ifFalse:[
-                defFg := bgColor.
-                defBg := fgColor
-            ]
-        ].
-        DefaultSelectionForegroundColor := resources at:'SELECTION_FOREGROUND_COLOR' default:defFg.
-        DefaultSelectionBackgroundColor := resources at:'SELECTION_BACKGROUND_COLOR' default:defBg.
+    DefaultFont notNil ifTrue:[
+	font := DefaultFont on:device
     ].
+    viewBackground := DefaultViewBackground.
     selectionFgColor := DefaultSelectionForegroundColor.
+    selectionFgColor isNil ifTrue:[selectionFgColor := bgColor].
     selectionBgColor := DefaultSelectionBackgroundColor.
+    selectionBgColor isNil ifTrue:[
+	device hasColors ifTrue:[
+	    DefaultSelectionForegroundColor isNil ifTrue:[
+		selectionFgColor := fgColor
+	    ].
+	    selectionBgColor := Color green
+	] ifFalse:[
+	    device hasGreyscales ifTrue:[
+		DefaultSelectionForegroundColor isNil ifTrue:[
+		    selectionFgColor := fgColor
+		].
+		selectionBgColor := Color grey
+	    ] ifFalse:[
+		selectionBgColor := fgColor
+	    ]
+	]
+    ].
 !
 
 initEvents
@@ -200,45 +211,45 @@
     |labels|
 
     labels := resources array:#(
-                                       'copy'
-                                       '-'
-                                       'font ...'
-                                       '-'
-                                       'search ...'
-                                       'goto ...'
-                                       '-'
-                                       'save as ...'
-                                       'print').
+				       'copy'
+				       '-'
+				       'font ...'
+				       '-'
+				       'search ...'
+				       'goto ...'
+				       '-'
+				       'save as ...'
+				       'print').
 
     self middleButtonMenu:(PopUpMenu
-                                labels:labels
-                             selectors:#(copySelection
-                                         nil
-                                         changeFont
-                                         nil
-                                         search
-                                         gotoLine
-                                         nil
-                                         save
-                                         print)
-                                receiver:self
-                                     for:self).
+				labels:labels
+			     selectors:#(copySelection
+					 nil
+					 changeFont
+					 nil
+					 search
+					 gotoLine
+					 nil
+					 save
+					 print)
+				receiver:self
+				     for:self).
 
     self enableOrDisableSelectionMenuEntries
 !
 
 destroy
     fileBox notNil ifTrue:[
-        fileBox destroy.
-        fileBox := nil
+	fileBox destroy.
+	fileBox := nil
     ].
     searchBox notNil ifTrue:[
-        searchBox destroy.
-        searchBox := nil
+	searchBox destroy.
+	searchBox := nil
     ].
     lineNumberBox notNil ifTrue:[
-        lineNumberBox destroy.
-        lineNumberBox := nil
+	lineNumberBox destroy.
+	lineNumberBox := nil
     ].
     super destroy
 ! !
@@ -251,7 +262,7 @@
     selectionFgColor := color1 on:device.
     selectionBgColor := color2 on:device.
     shown ifTrue:[
-        self redraw
+	self redraw
     ]
 !
 
@@ -280,12 +291,12 @@
     |line|
 
     list notNil ifTrue:[
-        line := self listAt:lineNr.
-        line notNil ifTrue:[
-            (line size >= colNr) ifTrue:[
-                ^ line at:colNr
-            ]
-        ]
+	line := self listAt:lineNr.
+	line notNil ifTrue:[
+	    (line size >= colNr) ifTrue:[
+		^ line at:colNr
+	    ]
+	]
     ].
     ^ Character space
 !
@@ -295,7 +306,7 @@
 
     selectionStartLine isNil ifTrue:[^ 1].
     ^ self characterPositionOfLine:selectionStartLine
-                               col:selectionStartCol
+			       col:selectionStartCol
 !
 
 directoryForFileDialog:aDirectory
@@ -321,39 +332,51 @@
 !TextView methodsFor:'private'!
 
 fileOutContentsOn:aStream
-    "save contents on a stream"
+    "save contents on a stream, replacing leading spaces by tab-characters."
+
+    self fileOutContentsOn:aStream compressTabs:true
+!
+
+fileOutContentsOn:aStream compressTabs:compressTabs
+    "save contents on a stream. If compressTabs is true,
+     leading spaces will be replaced by tab-characters in the output."
 
     |startNr nLines string|
 
     "on some systems, writing linewise is very slow (via NFS)
-     therefore we convert to a string and write it in chunks
-     to avoid creating huge strings, we do it in blocks of 1000 lines
+     therefore we convert to a string and write it in big chunks.
+     To avoid creating huge strings, we do it in blocks of 1000 lines,
+     limiting temporary string creation to about 50-80k.
     "
     startNr := 1.
     nLines := list size.
     [startNr <= nLines] whileTrue:[
-        string := list asStringFrom:startNr to:((startNr + 1000) min:nLines).
-        aStream nextPutAll:string.
-        startNr := startNr + 1000 + 1.
+	string := list asStringFrom:startNr 
+				 to:((startNr + 1000) min:nLines)
+		       compressTabs:compressTabs.
+	aStream nextPutAll:string.
+	startNr := startNr + 1000 + 1.
     ].
 
-"/    list do:[:aLine |
-"/      aLine notNil ifTrue:[
-"/          aStream nextPutAll:aLine.
-"/      ].
-"/      aStream cr
-"/  ]
+"the old (obsolete) code:
+    list do:[:aLine |
+      aLine notNil ifTrue:[
+	  aStream nextPutAll:aLine.
+      ].
+      aStream cr
+  ]
+"
 !
 
 widthForScrollBetween:firstLine and:lastLine
     "return the width in pixels for a scroll between firstLine and lastLine"
 
     selectionStartLine notNil ifTrue:[
-        (lastLine < selectionStartLine) ifFalse:[
-            (firstLine > selectionEndLine) ifFalse:[
-                ^ width
-            ]
-        ]
+	(lastLine < selectionStartLine) ifFalse:[
+	    (firstLine > selectionEndLine) ifFalse:[
+		^ width
+	    ]
+	]
     ].
     ^ super widthForScrollBetween:firstLine and:lastLine
 !
@@ -373,7 +396,7 @@
     selectionStartLine := firstLineShown.
     selectionStartCol := 1.
     selectionStartLine to:prevStartLine do:[:lineNr |
-        self redrawLine:lineNr
+	self redrawLine:lineNr
     ].
     Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
 !
@@ -393,7 +416,7 @@
     selectionEndLine := firstLineShown + nFullLinesShown.
     selectionEndCol := 0.
     prevEndLine to:selectionEndLine do:[:lineNr |
-        self redrawLine:lineNr
+	self redrawLine:lineNr
     ].
     Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
 !
@@ -402,13 +425,46 @@
     "stop auto scroll; deinstall timed-block"
 
     autoScrollBlock notNil ifTrue:[
-        Processor removeTimedBlock:autoScrollBlock.
-        self compressMotionEvents:true.
-        autoScrollBlock := nil.
-        autoScrollDeltaT := nil
+	Processor removeTimedBlock:autoScrollBlock.
+	self compressMotionEvents:true.
+	autoScrollBlock := nil.
+	autoScrollDeltaT := nil
     ]
+!
+
+scrollSelectLeft
+    "auto scroll action; scroll and reinstall timed-block"
+
+    |prevStartLine|
+
+    "just to make certain ..."
+    selectionStartLine isNil ifTrue:[^ self].
+    selectionStartCol isNil ifTrue:[^ self].
+
+    "make new selection immediately visible"
+    prevStartLine := selectionStartLine.
+    selectionStartCol := selectionStartCol - 1 max:1.
+    self scrollLeft.
+
+    Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
+!
+
+scrollSelectRight
+    "auto scroll action; scroll and reinstall timed-block"
+
+    |prevEndCol|
+
+    "just to make certain ..."
+    selectionEndCol isNil ifTrue:[^ self].
+
+    prevEndCol := selectionEndCol.
+    selectionEndCol := selectionEndCol + 1.
+    self scrollRight.
+
+    Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
 ! !
 
+
 !TextView methodsFor:'menu actions'!
 
 print
@@ -419,8 +475,8 @@
     list isNil ifTrue:[^ self].
     printStream := Printer new.
     printStream notNil ifTrue:[
-        self fileOutContentsOn:printStream.
-        printStream close
+	self fileOutContentsOn:printStream.
+	printStream close
     ]
 !
 
@@ -431,12 +487,12 @@
 
     aStream := FileStream newFileNamed:fileName.
     aStream isNil ifTrue:[
-        msg := resources string:'cannot write file %1 !!' with:fileName.
-        self warn:(msg , '\\(' , OperatingSystem lastErrorString , ')' ) withCRs
+	msg := resources string:'cannot write file %1 !!' with:fileName.
+	self warn:(msg , '\\(' , FileStream lastErrorString , ')' ) withCRs
     ] ifFalse:[
-        self fileOutContentsOn:aStream.
-        aStream close.
-        contentsWasSaved := true
+	self fileOutContentsOn:aStream.
+	aStream close.
+	contentsWasSaved := true
     ]
 !
 
@@ -447,12 +503,12 @@
 
     aStream := FileStream appendingOldFileNamed:fileName.
     aStream isNil ifTrue:[
-        msg := resources string:'cannot append to file %1 !!' with:fileName.
-        self warn:(msg , '\\(' , OperatingSystem lastErrorString , ')' ) withCRs
+	msg := resources string:'cannot append to file %1 !!' with:fileName.
+	self warn:(msg , '\\(' , FileStream lastErrorString , ')' ) withCRs
     ] ifFalse:[
-        self fileOutContentsOn:aStream.
-        aStream close.
-        contentsWasSaved := true
+	self fileOutContentsOn:aStream.
+	aStream close.
+	contentsWasSaved := true
     ]
 !
 
@@ -461,15 +517,15 @@
      - ask user for filename using a fileSelectionBox."
 
     fileBox isNil ifTrue:[
-        fileBox := FileSaveBox
-                        title:(resources string:'save contents in:')
-                        okText:(resources string:'save')
-                        abortText:(resources string:'cancel')
-                        action:[:fileName | self saveAs:fileName].
-        fileBox appendAction:[:fileName | self appendTo:fileName].
+	fileBox := FileSaveBox
+			title:(resources string:'save contents in:')
+			okText:(resources string:'save')
+			abortText:(resources string:'cancel')
+			action:[:fileName | self saveAs:fileName].
+	fileBox appendAction:[:fileName | self appendTo:fileName].
     ].
     directoryForFileDialog notNil ifTrue:[
-        fileBox directory:directoryForFileDialog
+	fileBox directory:directoryForFileDialog
     ].
     fileBox showAtPointer
 !
@@ -481,8 +537,8 @@
 
     text := self selection.
     text notNil ifTrue:[
-        Smalltalk at:#CopyBuffer put:text.
-        self unselect
+	Smalltalk at:#CopyBuffer put:text.
+	self unselect
     ]
 !
 
@@ -490,30 +546,42 @@
     "pop up a fontPanel to change font"
 
     MyFontPanel isNil ifTrue:[
-        MyFontPanel := FontPanel new
+	MyFontPanel := FontPanel new
     ].
     MyFontPanel action:[:family :face :style :size |
-        self font:(Font family:family
-                          face:face
-                         style:style
-                          size:size)
+	self font:(Font family:family
+			  face:face
+			 style:style
+			  size:size)
     ].
     MyFontPanel initialFont:font.
     MyFontPanel showAtPointer
 !
 
+defaultForGotoLine
+    "return a default value to show in the gotoLine box"
+
+    ^ nil
+!
+
 gotoLine
     "show a box to enter lineNumber for positioning"
 
+    |l|
+
     lineNumberBox isNil ifTrue:[
-        lineNumberBox :=
-            EnterBox
-               title:(resources string:'line number:')
-              okText:(resources string:'goto')
-           abortText:(resources string:'cancel')
-              action:[:l | self gotoLine:(Number readFromString:l)]
+	lineNumberBox :=
+	    EnterBox
+	       title:(resources string:'line number:')
+	      okText:(resources string:'goto')
+	   abortText:(resources string:'cancel')
+	      action:[:l | self gotoLine:(Number readFromString:l)]
     ].
-    lineNumberBox initialText:''.
+    l := self defaultForGotoLine.
+    l notNil ifTrue:[
+	l := l printString
+    ].
+    lineNumberBox initialText:l .
     lineNumberBox showAtPointer
 ! !
 
@@ -524,9 +592,9 @@
      update menu entries"
 
     selectionStartLine isNil ifTrue:[
-        self disableSelectionMenuEntries
+	self disableSelectionMenuEntries
     ] ifFalse:[
-        self enableSelectionMenuEntries
+	self enableSelectionMenuEntries
     ]
 !
 
@@ -536,7 +604,7 @@
      but do NOT forget a super disableSelectionMenuEntries there."
 
     middleButtonMenu notNil ifTrue:[
-        middleButtonMenu disable:#copySelection
+	middleButtonMenu disable:#copySelection
     ]
 !
 
@@ -546,7 +614,7 @@
      but do NOT forget a super enableSelectionMenuEntries there."
 
     middleButtonMenu notNil ifTrue:[
-        middleButtonMenu enable:#copySelection
+	middleButtonMenu enable:#copySelection
     ]
 !
 
@@ -565,31 +633,31 @@
     |startLine endLine startVisLine endVisLine|
 
     selectionStartLine notNil ifTrue:[
-        startLine := selectionStartLine.
-        endLine := selectionEndLine.
-        selectionStartLine := nil.
+	startLine := selectionStartLine.
+	endLine := selectionEndLine.
+	selectionStartLine := nil.
 
-        "if selection is not visible, we are done"
-        startLine >= (firstLineShown + nLinesShown) ifTrue:[^ self].
-        endLine < firstLineShown ifTrue:[^ self].
+	"if selection is not visible, we are done"
+	startLine >= (firstLineShown + nLinesShown) ifTrue:[^ self].
+	endLine < firstLineShown ifTrue:[^ self].
 
-        startLine < firstLineShown ifTrue:[
-            startVisLine := 1
-        ] ifFalse:[
-            startVisLine := self listLineToVisibleLine:startLine
-        ].
-        endLine >= (firstLineShown + nLinesShown) ifTrue:[
-            endVisLine := nLinesShown
-        ] ifFalse:[
-            endVisLine := self listLineToVisibleLine:endLine
-        ].
-        "if its only part of a line, just redraw what has to be"
-        (startVisLine == endVisLine) ifTrue:[
-            super redrawVisibleLine:startVisLine from:selectionStartCol to:selectionEndCol
-        ] ifFalse:[
-            super redrawFromVisibleLine:startVisLine to:endVisLine
-        ].
-        self unselectWithoutRedraw
+	startLine < firstLineShown ifTrue:[
+	    startVisLine := 1
+	] ifFalse:[
+	    startVisLine := self listLineToVisibleLine:startLine
+	].
+	endLine >= (firstLineShown + nLinesShown) ifTrue:[
+	    endVisLine := nLinesShown
+	] ifFalse:[
+	    endVisLine := self listLineToVisibleLine:endLine
+	].
+	"if its only part of a line, just redraw what has to be"
+	(startVisLine == endVisLine) ifTrue:[
+	    super redrawVisibleLine:startVisLine from:selectionStartCol to:selectionEndCol
+	] ifFalse:[
+	    super redrawFromVisibleLine:startVisLine to:endVisLine
+	].
+	self unselectWithoutRedraw
     ].
     selectStyle := nil
 !
@@ -599,31 +667,31 @@
 
     self unselect.
     startLine notNil ifTrue:[
-        "new:"
-        endLine < startLine ifTrue:[
-            ^ self selectFromLine:endLine col:endCol toLine:startLine col:startCol
-        ].
-        (endLine == startLine and:[endCol < startCol]) ifTrue:[
-            ^ self selectFromLine:endLine col:endCol toLine:startLine col:startCol
-        ].
+	"new:"
+	endLine < startLine ifTrue:[
+	    ^ self selectFromLine:endLine col:endCol toLine:startLine col:startCol
+	].
+	(endLine == startLine and:[endCol < startCol]) ifTrue:[
+	    ^ self selectFromLine:endLine col:endCol toLine:startLine col:startCol
+	].
 
 " old:
-        endLine < startLine ifTrue:[^ self].
-        (startLine == endLine and:[endCol < startCol]) ifTrue:[^ self].
+	endLine < startLine ifTrue:[^ self].
+	(startLine == endLine and:[endCol < startCol]) ifTrue:[^ self].
 "
-        selectionStartLine := startLine.
-        selectionStartCol := startCol.
-        selectionEndLine := endLine.
-        selectionEndCol := endCol.
-        (startLine == endLine) ifTrue:[
-            self redrawLine:startLine from:startCol to:endCol
-        ] ifFalse:[
-            startLine to:endLine do:[:lineNr |
-                self redrawLine:lineNr
-            ]
-        ].
-        selectStyle := nil.
-        self enableSelectionMenuEntries
+	selectionStartLine := startLine.
+	selectionStartCol := startCol.
+	selectionEndLine := endLine.
+	selectionEndCol := endCol.
+	(startLine == endLine) ifTrue:[
+	    self redrawLine:startLine from:startCol to:endCol
+	] ifFalse:[
+	    startLine to:endLine do:[:lineNr |
+		self redrawLine:lineNr
+	    ]
+	].
+	selectStyle := nil.
+	self enableSelectionMenuEntries
     ]
 !
 
@@ -659,8 +727,9 @@
     self selectFromLine:line1 col:col1 toLine:line2 col:col2
 !
 
-selectWordAtLine:selectLine col:selectCol
-    "select the word at given line/col"
+wordAtLine:selectLine col:selectCol do:aFiveArgBlock
+    "find word boundaries, evaluate the block argument with those.
+     A helper for nextWord and selectWord functions."
 
     |beginCol endCol endLine thisCharacter flag len|
 
@@ -673,29 +742,43 @@
     beginCol := self findBeginOfWordAtLine:selectLine col:selectCol.
     endCol := self findEndOfWordAtLine:selectLine col:selectCol.
     endCol == 0 ifTrue:[
-        endLine := selectLine + 1
+	endLine := selectLine + 1
     ].
 
     "is the initial acharacter within a word ?"
     (wordCheck value:thisCharacter) ifTrue:[
-        "
-         try to catch a blank ...
-        "
-        ((beginCol == 1)
-        or:[(self characterAtLine:selectLine col:(beginCol - 1))
-             ~~ Character space]) ifTrue:[
-            ((self characterAtLine:selectLine col:(endCol + 1))
-              == Character space) ifTrue:[
-                endCol := endCol + 1.
-                flag := #wordRight
-            ]
-        ] ifFalse:[
-            beginCol := beginCol - 1.
-            flag := #wordLeft
-        ].
+	"
+	 try to catch a blank ...
+	"
+	((beginCol == 1)
+	or:[(self characterAtLine:selectLine col:(beginCol - 1))
+	     ~~ Character space]) ifTrue:[
+	    ((self characterAtLine:selectLine col:(endCol + 1))
+	      == Character space) ifTrue:[
+		endCol := endCol + 1.
+		flag := #wordRight
+	    ]
+	] ifFalse:[
+	    beginCol := beginCol - 1.
+	    flag := #wordLeft
+	].
     ].
-    self selectFromLine:selectLine col:beginCol toLine:endLine col:endCol.
-    selectStyle := flag
+    aFiveArgBlock value:selectLine 
+		  value:beginCol 
+		  value:endLine 
+		  value:endCol
+		  value:flag
+!
+
+selectWordAtLine:line col:col
+    "select the word at given line/col"
+
+    self wordAtLine:line col:col do:[
+	:beginLine :beginCol :endLine :endCol :style |
+
+	self selectFromLine:beginLine col:beginCol toLine:endLine col:endCol.
+	selectStyle := style
+    ]
 !
 
 selectWordAtX:x y:y
@@ -707,8 +790,8 @@
     selectVisibleLine := self visibleLineOfY:y.
     selectLine := self visibleLineToListLine:selectVisibleLine.
     selectLine notNil ifTrue:[
-        selectCol := self colOfX:x inVisibleLine:selectLine.
-        self selectWordAtLine:selectLine col:selectCol
+	selectCol := self colOfX:x inVisibleLine:selectLine.
+	self selectWordAtLine:selectLine col:selectCol
     ]
 !
 
@@ -720,7 +803,7 @@
     selectVisibleLine := self visibleLineOfY:y.
     selectLine := self visibleLineToListLine:selectVisibleLine.
     selectLine notNil ifTrue:[
-        self selectLine:selectLine
+	self selectLine:selectLine
     ]
 !
 
@@ -743,23 +826,27 @@
 
     selectionStartLine isNil ifTrue:[^ nil].
     (selectionStartLine == selectionEndLine) ifTrue:[
-        "part of a line"
-        ^ Text with:(self listAt:selectionStartLine
-                            from:selectionStartCol
-                              to:selectionEndCol)
+	"part of a line"
+	^ Text with:(self listAt:selectionStartLine
+			    from:selectionStartCol
+			      to:selectionEndCol)
     ].
     sz := selectionEndLine - selectionStartLine + 1.
     text := Text new:sz.
 
     "get 1st and last (possibly) partial lines"
     text at:1 put:(self listAt:selectionStartLine from:selectionStartCol).
+selectionEndCol == 0 ifTrue:[
+    text at:sz put:''
+] ifFalse:[
     text at:sz put:(self listAt:selectionEndLine to:selectionEndCol).
+].
 
     "get bulk of text"
     index := 2.
     (selectionStartLine + 1) to:(selectionEndLine - 1) do:[:lineNr |
-        text at:index put:(self listAt:lineNr).
-        index := index + 1
+	text at:index put:(self listAt:lineNr).
+	index := index + 1
     ].
     ^ text
 !
@@ -768,7 +855,7 @@
     "scroll to make selection visible"
 
     selectionStartLine notNil ifTrue:[
-        self makeLineVisible:selectionStartLine
+	self makeLineVisible:selectionStartLine
     ]
 ! !
 
@@ -779,17 +866,17 @@
      - currently no regular expressions are handled."
 
     searchBox isNil ifTrue:[
-        searchBox :=
-            EnterBox2
-               title:(resources at:'searchPattern:')
-             okText1:(resources at:'prev')
-             okText2:(resources at:'next')
-           abortText:(resources at:'cancel')
-             action1:[:pattern | self searchBwd:(pattern withoutSeparators)]
-             action2:[:pattern | self searchFwd:(pattern withoutSeparators)]
+	searchBox :=
+	    EnterBox2
+	       title:(resources at:'searchPattern:')
+	     okText1:(resources at:'prev')
+	     okText2:(resources at:'next')
+	   abortText:(resources at:'cancel')
+	     action1:[:pattern | self searchBwd:(pattern withoutSeparators)]
+	     action2:[:pattern | self searchFwd:(pattern withoutSeparators)]
     ].
     searchPattern notNil ifTrue:[
-        searchBox initialText:searchPattern
+	searchBox initialText:searchPattern
     ].
     searchBox showAtPointer
 !
@@ -801,7 +888,7 @@
 
     sel := self selection.
     sel notNil ifTrue:[
-        searchPattern := sel asString withoutSeparators
+	searchPattern := sel asString withoutSeparators
     ]
 !
 
@@ -830,7 +917,7 @@
 
     self setSearchPattern.
     searchPattern notNil ifTrue:[
-        self searchFwd:searchPattern
+	self searchFwd:searchPattern
     ]
 !
 
@@ -839,7 +926,7 @@
 
     self setSearchPattern.
     searchPattern notNil ifTrue:[
-        self searchBwd:searchPattern
+	self searchBwd:searchPattern
     ]
 !
 
@@ -849,19 +936,19 @@
     |startLine startCol|
 
     selectionStartLine notNil ifTrue:[
-        startLine := selectionStartLine.
-        startCol := selectionStartCol
+	startLine := selectionStartLine.
+	startCol := selectionStartCol
     ] ifFalse:[
-        startLine := 1.
-        startCol := 1
+	startLine := 1.
+	startCol := 1
     ].
     self searchForwardFor:pattern startingAtLine:startLine col:startCol
     ifFound:[:line :col |
-        self selectFromLine:line col:col
-                     toLine:line col:(col + pattern size - 1).
-        self makeLineVisible:line
+	self selectFromLine:line col:col
+		     toLine:line col:(col + pattern size - 1).
+	self makeLineVisible:line
     ] else:[
-        self showNotFound
+	self showNotFound
     ]
 !
 
@@ -871,19 +958,19 @@
     |startLine startCol|
 
     selectionStartLine notNil ifTrue:[
-        startLine := selectionStartLine.
-        startCol := selectionStartCol
+	startLine := selectionStartLine.
+	startCol := selectionStartCol
     ] ifFalse:[
-        startLine := 1.
-        startCol := 1
+	startLine := 1.
+	startCol := 1
     ].
     self searchBackwardFor:pattern startingAtLine:startLine col:startCol
     ifFound:[:line :col |
-        self selectFromLine:line col:col
-                     toLine:line col:(col + pattern size - 1).
-        self makeLineVisible:line
+	self selectFromLine:line col:col
+		     toLine:line col:(col + pattern size - 1).
+	self makeLineVisible:line
     ] else:[
-        self showNotFound
+	self showNotFound
     ]
 ! !
 
@@ -893,11 +980,11 @@
     "if there is a margin, clear it - a helper for selection drawing"
 
     (leftMargin ~~ 0) ifTrue:[
-        self paint:color.
-        self fillRectangleX:margin
-                          y:(self yOfLine:visLine)
-                      width:leftMargin
-                     height:fontHeight
+	self paint:color.
+	self fillRectangleX:margin
+			  y:(self yOfVisibleLine:visLine)
+		      width:leftMargin
+		     height:fontHeight
     ]
 !
 
@@ -908,18 +995,18 @@
 
     line := self visibleLineToAbsoluteLine:visLine.
     selectionStartLine notNil ifTrue:[
-        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
-            ((line == selectionStartLine)
-            and: [col < selectionStartCol]) ifFalse:[
-                ((line == selectionEndLine)
-                and: [col > selectionEndCol]) ifFalse:[
-                    "its in the selection"
-                    self drawVisibleLine:visLine col:col with:selectionFgColor
-                                                          and:selectionBgColor.
-                    ^ self
-                ]
-            ]
-        ]
+	(line between:selectionStartLine and:selectionEndLine) ifTrue:[
+	    ((line == selectionStartLine)
+	    and: [col < selectionStartCol]) ifFalse:[
+		((line == selectionEndLine)
+		and: [col > selectionEndCol]) ifFalse:[
+		    "its in the selection"
+		    self drawVisibleLine:visLine col:col with:selectionFgColor
+							  and:selectionBgColor.
+		    ^ self
+		]
+	    ]
+	]
     ].
     super redrawVisibleLine:visLine col:col
 !
@@ -933,71 +1020,71 @@
 
     end := endVisLineNr.
     (end > nLinesShown) ifTrue:[
-        end := nLinesShown
+	end := nLinesShown
     ].
 
     selectionStartLine isNil ifTrue:[
-        specialCare := false
+	specialCare := false
     ] ifFalse:[
-        startLine := self visibleLineToAbsoluteLine:startVisLineNr.
-        (startLine > selectionEndLine) ifTrue:[
-            specialCare := false
-        ] ifFalse:[
-            endLine := self visibleLineToAbsoluteLine:end.
-            (endLine < selectionStartLine) ifTrue:[
-                specialCare := false
-            ] ifFalse:[
-                specialCare := true
-            ]
-        ]
+	startLine := self visibleLineToAbsoluteLine:startVisLineNr.
+	(startLine > selectionEndLine) ifTrue:[
+	    specialCare := false
+	] ifFalse:[
+	    endLine := self visibleLineToAbsoluteLine:end.
+	    (endLine < selectionStartLine) ifTrue:[
+		specialCare := false
+	    ] ifFalse:[
+		specialCare := true
+	    ]
+	]
     ].
 
     "easy: nothing is selected"
     specialCare ifFalse:[
-        super redrawFromVisibleLine:startVisLineNr to:end.
-        ^ self
+	super redrawFromVisibleLine:startVisLineNr to:end.
+	^ self
     ].
 
     "easy: all is selected"
     ((selectionStartLine < startLine) and:[selectionEndLine > endLine]) ifTrue:[
-        self drawFromVisibleLine:startVisLineNr to:end with:selectionFgColor
-                                                        and:selectionBgColor.
-        ^ self
+	self drawFromVisibleLine:startVisLineNr to:end with:selectionFgColor
+							and:selectionBgColor.
+	^ self
     ].
 
     (selectionStartLine >= firstLineShown) ifTrue:[
-        "draw unselected top part"
+	"draw unselected top part"
 
-        selVisStart := self listLineToVisibleLine:selectionStartLine.
-        super redrawFromVisibleLine:startVisLineNr to:(selVisStart - 1).
+	selVisStart := self listLineToVisibleLine:selectionStartLine.
+	super redrawFromVisibleLine:startVisLineNr to:(selVisStart - 1).
 
-        "and first partial selected line"
-        self redrawVisibleLine:selVisStart.
+	"and first partial selected line"
+	self redrawVisibleLine:selVisStart.
 
-        "rest starts after this one"
-        line1 := selVisStart + 1
+	"rest starts after this one"
+	line1 := selVisStart + 1
     ] ifFalse:[
-        line1 := 1
+	line1 := 1
     ].
 
     (line1 > end) ifTrue:[^ self].
     (line1 < startVisLineNr) ifTrue:[
-        line1 := startVisLineNr
+	line1 := startVisLineNr
     ].
 
     "draw middle part of selection"
 
     (selectionEndLine >= (firstLineShown + nLinesShown)) ifTrue:[
-        line2 := nLinesShown
+	line2 := nLinesShown
     ] ifFalse:[
-        line2 := (self listLineToVisibleLine:selectionEndLine) - 1
+	line2 := (self listLineToVisibleLine:selectionEndLine) - 1
     ].
     (line2 > end) ifTrue:[
-        line2 := end
+	line2 := end
     ].
 
     self drawFromVisibleLine:line1 to:line2 with:selectionFgColor
-                                             and:selectionBgColor.
+					     and:selectionBgColor.
 
     (line2 >= end) ifTrue:[^ self].
 
@@ -1005,7 +1092,7 @@
     self redrawVisibleLine:(line2 + 1).
 
     ((line2 + 2) <= end) ifTrue:[
-        super redrawFromVisibleLine:(line2 + 2) to:end
+	super redrawFromVisibleLine:(line2 + 2) to:end
     ]
 !
 
@@ -1015,58 +1102,58 @@
     |len line l|
 
     selectionStartLine notNil ifTrue:[
-        line := self visibleLineToAbsoluteLine:visLine.
-        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
-            (line == selectionStartLine) ifTrue:[
-                (line == selectionEndLine) ifTrue:[
-                    "its part-of-single-line selection"
-                    self clearMarginOfVisible:visLine with:bgColor.
-                    (selectionStartCol > 1) ifTrue:[
-                        super redrawVisibleLine:visLine
-                                           from:1
-                                             to:(selectionStartCol - 1)
-                    ].
-                    self drawVisibleLine:visLine from:selectionStartCol
-                                                   to:selectionEndCol
-                                                 with:selectionFgColor
-                                                  and:selectionBgColor.
-                    super redrawVisibleLine:visLine
-                                       from:(selectionEndCol + 1).
-                    ^ self
-                ].
+	line := self visibleLineToAbsoluteLine:visLine.
+	(line between:selectionStartLine and:selectionEndLine) ifTrue:[
+	    (line == selectionStartLine) ifTrue:[
+		(line == selectionEndLine) ifTrue:[
+		    "its part-of-single-line selection"
+		    self clearMarginOfVisible:visLine with:bgColor.
+		    (selectionStartCol > 1) ifTrue:[
+			super redrawVisibleLine:visLine
+					   from:1
+					     to:(selectionStartCol - 1)
+		    ].
+		    self drawVisibleLine:visLine from:selectionStartCol
+						   to:selectionEndCol
+						 with:selectionFgColor
+						  and:selectionBgColor.
+		    super redrawVisibleLine:visLine
+				       from:(selectionEndCol + 1).
+		    ^ self
+		].
 
-                "its the first line of a multi-line selection"
-                (selectionStartCol ~~ 1) ifTrue:[
-                    self clearMarginOfVisible:visLine with:bgColor.
-                    super redrawVisibleLine:visLine
-                                       from:1
-                                         to:(selectionStartCol - 1)
-                ].
-                self drawVisibleLine:visLine from:selectionStartCol
-                                with:selectionFgColor and:selectionBgColor.
-                ^ self
-            ].
+		"its the first line of a multi-line selection"
+		(selectionStartCol ~~ 1) ifTrue:[
+		    self clearMarginOfVisible:visLine with:bgColor.
+		    super redrawVisibleLine:visLine
+				       from:1
+					 to:(selectionStartCol - 1)
+		].
+		self drawVisibleLine:visLine from:selectionStartCol
+				with:selectionFgColor and:selectionBgColor.
+		^ self
+	    ].
 
-            (line == selectionEndLine) ifTrue:[
-                "its the last line of a multi-line selection"
-                (selectionEndCol == 0) ifTrue:[
-                    ^ super redrawVisibleLine:visLine
-                ].
-                l := self visibleAt:selectionEndLine.
-                len := l size.
+	    (line == selectionEndLine) ifTrue:[
+		"its the last line of a multi-line selection"
+		(selectionEndCol == 0) ifTrue:[
+		    ^ super redrawVisibleLine:visLine
+		].
+		l := self visibleAt:selectionEndLine.
+		len := l size.
 
-                self clearMarginOfVisible:visLine with:selectionBgColor.
-                self drawVisibleLine:visLine from:1 to:selectionEndCol
-                                with:selectionFgColor and:selectionBgColor.
-                super redrawVisibleLine:visLine from:(selectionEndCol + 1).
-                ^ self
-            ].
+		self clearMarginOfVisible:visLine with:selectionBgColor.
+		self drawVisibleLine:visLine from:1 to:selectionEndCol
+				with:selectionFgColor and:selectionBgColor.
+		super redrawVisibleLine:visLine from:(selectionEndCol + 1).
+		^ self
+	    ].
 
-            "its a full line in a multi-line selection"
-            self clearMarginOfVisible:visLine with:selectionBgColor.
-            self drawVisibleLine:visLine with:selectionFgColor and:selectionBgColor.
-            ^ self
-        ]
+	    "its a full line in a multi-line selection"
+	    self clearMarginOfVisible:visLine with:selectionBgColor.
+	    self drawVisibleLine:visLine with:selectionFgColor and:selectionBgColor.
+	    ^ self
+	]
     ].
     super redrawVisibleLine:visLine
 !
@@ -1078,18 +1165,18 @@
 
     line := self visibleLineToAbsoluteLine:visLine.
     selectionStartLine notNil ifTrue:[
-        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
-            ((line == selectionStartLine) 
-             or:[line == selectionEndLine]) ifTrue:[
-                "since I'm lazy, redraw full line"
-                self redrawVisibleLine:visLine.
-                ^ self
-            ].
-            "the line is fully within the selection"
-            self drawVisibleLine:visLine from:startCol with:selectionFgColor
-                                                        and:selectionBgColor.
-            ^ self
-        ]
+	(line between:selectionStartLine and:selectionEndLine) ifTrue:[
+	    ((line == selectionStartLine) 
+	     or:[line == selectionEndLine]) ifTrue:[
+		"since I'm lazy, redraw full line"
+		self redrawVisibleLine:visLine.
+		^ self
+	    ].
+	    "the line is fully within the selection"
+	    self drawVisibleLine:visLine from:startCol with:selectionFgColor
+							and:selectionBgColor.
+	    ^ self
+	]
     ].
     super redrawVisibleLine:visLine from:startCol
 !
@@ -1104,77 +1191,77 @@
     allIn := false.
     allOut := false.
     selectionStartLine isNil ifTrue:[
-        allOut := true
+	allOut := true
     ] ifFalse:[
-        (line between:selectionStartLine and:selectionEndLine) ifFalse:[
-            allOut := true
-        ] ifTrue:[
-            (selectionStartLine == selectionEndLine) ifTrue:[
-                ((endCol < selectionStartCol) 
-                or:[startCol > selectionEndCol]) ifTrue:[
-                    allOut := true
-                ] ifFalse:[
-                    ((startCol >= selectionStartCol) 
-                    and:[endCol <= selectionEndCol]) ifTrue:[
-                        allIn := true
-                    ]
-                ]
-            ] ifFalse:[
-                (line == selectionStartLine) ifTrue:[
-                    (endCol < selectionStartCol) ifTrue:[
-                        allOut := true
-                    ] ifFalse:[
-                        (startCol >= selectionStartCol) ifTrue:[
-                            allIn := true
-                        ]
-                    ]
-                ] ifFalse:[
-                    (line == selectionEndLine) ifTrue:[
-                        (startCol > selectionEndCol) ifTrue:[
-                            allOut := true
-                        ] ifFalse:[
-                            (endCol <= selectionEndCol) ifTrue:[
-                                allIn := true
-                            ]
-                        ]
-                    ] ifFalse:[
-                        allIn := true
-                    ]
-                ]
-            ]
-        ]
+	(line between:selectionStartLine and:selectionEndLine) ifFalse:[
+	    allOut := true
+	] ifTrue:[
+	    (selectionStartLine == selectionEndLine) ifTrue:[
+		((endCol < selectionStartCol) 
+		or:[startCol > selectionEndCol]) ifTrue:[
+		    allOut := true
+		] ifFalse:[
+		    ((startCol >= selectionStartCol) 
+		    and:[endCol <= selectionEndCol]) ifTrue:[
+			allIn := true
+		    ]
+		]
+	    ] ifFalse:[
+		(line == selectionStartLine) ifTrue:[
+		    (endCol < selectionStartCol) ifTrue:[
+			allOut := true
+		    ] ifFalse:[
+			(startCol >= selectionStartCol) ifTrue:[
+			    allIn := true
+			]
+		    ]
+		] ifFalse:[
+		    (line == selectionEndLine) ifTrue:[
+			(startCol > selectionEndCol) ifTrue:[
+			    allOut := true
+			] ifFalse:[
+			    (endCol <= selectionEndCol) ifTrue:[
+				allIn := true
+			    ]
+			]
+		    ] ifFalse:[
+			allIn := true
+		    ]
+		]
+	    ]
+	]
     ].
     allOut ifTrue:[
-        super redrawVisibleLine:visLine from:startCol to:endCol.
-        ^ self
+	super redrawVisibleLine:visLine from:startCol to:endCol.
+	^ self
     ].
 
     allIn ifTrue:[
-        self drawVisibleLine:visLine from:startCol to:endCol
-                        with:selectionFgColor and:selectionBgColor
+	self drawVisibleLine:visLine from:startCol to:endCol
+			with:selectionFgColor and:selectionBgColor
     ] ifFalse:[
-        "redraw part before selection"
-        ((line == selectionStartLine)
-         and:[startCol <= selectionStartCol]) ifTrue:[
-            super redrawVisibleLine:visLine from:startCol
-                                              to:(selectionStartCol - 1).
-            leftCol := selectionStartCol
-        ] ifFalse:[
-            leftCol := startCol
-        ].
-        "redraw selected part"
-        (selectionEndLine > line) ifTrue:[
-            rightCol := endCol
-        ] ifFalse:[
-            rightCol := selectionEndCol min:endCol
-        ].
-        self drawVisibleLine:visLine from:leftCol to:rightCol
-                        with:selectionFgColor and:selectionBgColor.
+	"redraw part before selection"
+	((line == selectionStartLine)
+	 and:[startCol <= selectionStartCol]) ifTrue:[
+	    super redrawVisibleLine:visLine from:startCol
+					      to:(selectionStartCol - 1).
+	    leftCol := selectionStartCol
+	] ifFalse:[
+	    leftCol := startCol
+	].
+	"redraw selected part"
+	(selectionEndLine > line) ifTrue:[
+	    rightCol := endCol
+	] ifFalse:[
+	    rightCol := selectionEndCol min:endCol
+	].
+	self drawVisibleLine:visLine from:leftCol to:rightCol
+			with:selectionFgColor and:selectionBgColor.
 
-        "redraw part after selection"
-        (rightCol < endCol) ifTrue:[
-            super redrawVisibleLine:visLine from:(rightCol + 1) to:endCol
-        ]
+	"redraw part after selection"
+	(rightCol < endCol) ifTrue:[
+	    super redrawVisibleLine:visLine from:(rightCol + 1) to:endCol
+	]
     ].
 
     "special care for first and last line of selection:
@@ -1184,14 +1271,14 @@
     and:[(startCol == 1)
     and:[selectionStartLine < selectionEndLine]])
     ifTrue:[
-        self clearMarginOfVisible:visLine with:selectionBgColor.
+	self clearMarginOfVisible:visLine with:selectionBgColor.
     ].
 
     ((line == selectionStartLine)
     and:[(startCol == 1)
     and:[selectionStartLine < selectionEndLine]])
     ifTrue:[
-        self clearMarginOfVisible:visLine with:bgColor.
+	self clearMarginOfVisible:visLine with:bgColor.
     ]
 ! !
 
@@ -1222,13 +1309,13 @@
      (see EditTextView>>keyPress:x:y and Workspace>>keyPress:x:y)
     "
     (#(F1 F2 F3 F4 F5 F6 F7 F8 F9) includes:key) ifTrue:[
-        device shiftDown ifTrue:[
-            (Smalltalk at:#FunctionKeySequences) isNil ifTrue:[
-                Smalltalk at:#FunctionKeySequences put:Dictionary new
-            ].
-            (Smalltalk at:#FunctionKeySequences) at:key put:(self selection)
-        ].
-        ^ self
+	device shiftDown ifTrue:[
+	    (Smalltalk at:#FunctionKeySequences) isNil ifTrue:[
+		Smalltalk at:#FunctionKeySequences put:Dictionary new
+	    ].
+	    (Smalltalk at:#FunctionKeySequences) at:key put:(self selection)
+	].
+	^ self
     ].
 
     super keyPress:key x:x y:y
@@ -1240,15 +1327,15 @@
     |clickVisibleLine|
 
     ((button == 1) or:[button == #select]) ifTrue:[
-        clickVisibleLine := self visibleLineOfY:y.
-        clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
-        clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
-        clickStartLine := clickLine.
-        clickStartCol := clickCol.
-        self unselect.
-        clickCount := 1
+	clickVisibleLine := self visibleLineOfY:y.
+	clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
+	clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
+	clickStartLine := clickLine.
+	clickStartCol := clickCol.
+	self unselect.
+	clickCount := 1
     ] ifFalse:[
-        super buttonPress:button x:x y:y
+	super buttonPress:button x:x y:y
     ]
 !
 
@@ -1263,38 +1350,38 @@
     "multi-mouse-click - select word under pointer"
 
     ((button == 1) or:[button == #select]) ifTrue:[
-        clickCount notNil ifTrue:[
-            clickCount := clickCount + 1.
-            (clickCount == 2) ifTrue:[
-                self selectWordAtX:x y:y.
-                "
-                 remember words position in case of a drag following
-                "
-                wordStartLine := selectionStartLine.
-                wordEndLine := selectionEndLine.
-                selectStyle == #wordLeft ifTrue:[
-                    wordStartCol := selectionStartCol + 1
-                ] ifFalse:[
-                    wordStartCol := selectionStartCol.
-                ].
-                selectStyle == #wordRight ifTrue:[
-                    wordEndCol := selectionEndCol - 1
-                ] ifFalse:[
-                    wordEndCol := selectionEndCol
-                ]
-            ] ifFalse:[
-                (clickCount == 3) ifTrue:[
-                    self selectLineAtY:y.
-                    selectStyle := #line
-                ] ifFalse:[
-                    (clickCount == 4) ifTrue:[
-                        self selectAll
-                    ]
-                ]
-            ]
-        ]
+	clickCount notNil ifTrue:[
+	    clickCount := clickCount + 1.
+	    (clickCount == 2) ifTrue:[
+		self selectWordAtX:x y:y.
+		"
+		 remember words position in case of a drag following
+		"
+		wordStartLine := selectionStartLine.
+		wordEndLine := selectionEndLine.
+		selectStyle == #wordLeft ifTrue:[
+		    wordStartCol := selectionStartCol + 1
+		] ifFalse:[
+		    wordStartCol := selectionStartCol.
+		].
+		selectStyle == #wordRight ifTrue:[
+		    wordEndCol := selectionEndCol - 1
+		] ifFalse:[
+		    wordEndCol := selectionEndCol
+		]
+	    ] ifFalse:[
+		(clickCount == 3) ifTrue:[
+		    self selectLineAtY:y.
+		    selectStyle := #line
+		] ifFalse:[
+		    (clickCount == 4) ifTrue:[
+			self selectAll
+		    ]
+		]
+	    ]
+	]
     ] ifFalse:[
-        super buttonMultiPress:button x:x y:y
+	super buttonMultiPress:button x:x y:y
     ]
 !
 
@@ -1311,40 +1398,50 @@
      check if its a button-1 motion
     "
     ((buttonMask bitAnd:(device button1MotionMask)) ~~ 0) ifFalse:[
-        ^ self
+	^ self
     ].
 
     "if moved outside of view, start autoscroll"
     (y < 0) ifTrue:[
-        self compressMotionEvents:false.
-        self startScrollUp:y.
-        ^ self
+	self compressMotionEvents:false.
+	self startAutoScrollUp:y.
+	^ self
     ].
     (y > height) ifTrue:[
-        self compressMotionEvents:false.
-        self startScrollDown:(y - height).
-        ^ self
+	self compressMotionEvents:false.
+	self startAutoScrollDown:(y - height).
+	^ self
+    ].
+    ((x < 0) and:[leftOffset ~~ 0]) ifTrue:[
+	self compressMotionEvents:false.
+	self startAutoScrollLeft:x.
+	^ self
+    ].
+    (x > width) ifTrue:[
+	self compressMotionEvents:false.
+	self startAutoScrollRight:(x - width).
+	^ self
     ].
 
     "move inside - stop autoscroll if any"
     autoScrollBlock notNil ifTrue:[
-        self stopScrollSelect
+	self stopScrollSelect
     ].
 
     movedVisibleLine := self visibleLineOfY:y.
     movedLine := self visibleLineToAbsoluteLine:movedVisibleLine.
     (x < leftMargin) ifTrue:[
-        movedCol := 0
+	movedCol := 0
     ] ifFalse:[
-        movedCol := self colOfX:x inVisibleLine:movedVisibleLine
+	movedCol := self colOfX:x inVisibleLine:movedVisibleLine
     ].
     ((movedLine == clickLine) and:[movedCol == clickCol]) ifTrue:[^ self].
 
     selectionStartLine isNil ifTrue:[
-        selectionStartLine := clickLine.
-        selectionStartCol := clickCol.
-        selectionEndLine := selectionStartLine.
-        selectionEndCol := selectionStartCol
+	selectionStartLine := clickLine.
+	selectionStartCol := clickCol.
+	selectionEndLine := selectionStartLine.
+	selectionEndCol := selectionStartCol
     ].
     oldStartLine := selectionStartLine.
     oldEndLine := selectionEndLine.
@@ -1355,84 +1452,84 @@
     "find out if we are before or after initial click"
     movedUp := false.
     (movedLine < clickStartLine) ifTrue:[
-        movedUp := true
+	movedUp := true
     ] ifFalse:[
-        (movedLine == clickStartLine) ifTrue:[
-            (movedCol < clickStartCol) ifTrue:[
-                movedUp := true
-            ]
-        ]
+	(movedLine == clickStartLine) ifTrue:[
+	    (movedCol < clickStartCol) ifTrue:[
+		movedUp := true
+	    ]
+	]
     ].
 
     movedUp ifTrue:[
-        "change selectionStart"
-        selectionStartCol := movedCol.
-        selectionStartLine := movedLine.
-        selectionEndCol := clickStartCol.
-        selectionEndLine := clickStartLine.
-        selectStyle notNil ifTrue:[
-            selectionEndCol := wordEndCol.
-            selectionEndLine := wordEndLine.
-        ]
+	"change selectionStart"
+	selectionStartCol := movedCol.
+	selectionStartLine := movedLine.
+	selectionEndCol := clickStartCol.
+	selectionEndLine := clickStartLine.
+	selectStyle notNil ifTrue:[
+	    selectionEndCol := wordEndCol.
+	    selectionEndLine := wordEndLine.
+	]
     ] ifFalse:[
-        "change selectionEnd"
-        selectionEndCol := movedCol.
-        selectionEndLine := movedLine.
-        selectionStartCol := clickStartCol.
-        selectionStartLine := clickStartLine.
-        selectStyle notNil ifTrue:[
-            selectionStartCol := wordStartCol.
-            selectionStartLine := wordStartLine.
-        ]
+	"change selectionEnd"
+	selectionEndCol := movedCol.
+	selectionEndLine := movedLine.
+	selectionStartCol := clickStartCol.
+	selectionStartLine := clickStartLine.
+	selectStyle notNil ifTrue:[
+	    selectionStartCol := wordStartCol.
+	    selectionStartLine := wordStartLine.
+	]
     ].
 
     (selectionStartCol == 0) ifTrue:[
-        selectionStartCol := 1
+	selectionStartCol := 1
     ].
 
     "
      if in word-select, just catch the rest of the word
     "
     (selectStyle notNil and:[selectStyle startsWith:'word']) ifTrue:[
-        movedUp ifTrue:[
-            selectionStartCol := self findBeginOfWordAtLine:selectionStartLine col:selectionStartCol
-        ] ifFalse:[
-            selectionEndCol := self findEndOfWordAtLine:selectionEndLine col:selectionEndCol.
-            selectionEndCol == 0 ifTrue:[
-                selectionEndLine := selectionEndLine + 1
-            ]
-        ].
+	movedUp ifTrue:[
+	    selectionStartCol := self findBeginOfWordAtLine:selectionStartLine col:selectionStartCol
+	] ifFalse:[
+	    selectionEndCol := self findEndOfWordAtLine:selectionEndLine col:selectionEndCol.
+	    selectionEndCol == 0 ifTrue:[
+		selectionEndLine := selectionEndLine + 1
+	    ]
+	].
     ].
 
     selectStyle == #line ifTrue:[
-        movedUp ifTrue:[
-            selectionStartCol := 1.
-        ] ifFalse:[
-            selectionEndCol := 0.
-            selectionEndLine := selectionEndLine + 1
-        ]
+	movedUp ifTrue:[
+	    selectionStartCol := 1.
+	] ifFalse:[
+	    selectionEndCol := 0.
+	    selectionEndLine := selectionEndLine + 1
+	]
     ].
 
     (oldStartLine == selectionStartLine) ifTrue:[
-        (oldStartCol ~~ selectionStartCol) ifTrue:[
-            self redrawLine:oldStartLine 
-                       from:((selectionStartCol min:oldStartCol) max:1)
-                         to:((selectionStartCol max:oldStartCol) max:1)
-        ]
+	(oldStartCol ~~ selectionStartCol) ifTrue:[
+	    self redrawLine:oldStartLine 
+		       from:((selectionStartCol min:oldStartCol) max:1)
+			 to:((selectionStartCol max:oldStartCol) max:1)
+	]
     ] ifFalse:[
-        self redrawFromLine:(oldStartLine min:selectionStartLine)
-                         to:(oldStartLine max:selectionStartLine)
+	self redrawFromLine:(oldStartLine min:selectionStartLine)
+			 to:(oldStartLine max:selectionStartLine)
     ].
 
     (oldEndLine == selectionEndLine) ifTrue:[
-        (oldEndCol ~~ selectionEndCol) ifTrue:[
-            self redrawLine:oldEndLine 
-                       from:((selectionEndCol min:oldEndCol) max:1)
-                         to:((selectionEndCol max:oldEndCol) max:1)
-        ]
+	(oldEndCol ~~ selectionEndCol) ifTrue:[
+	    self redrawLine:oldEndLine 
+		       from:((selectionEndCol min:oldEndCol) max:1)
+			 to:((selectionEndCol max:oldEndCol) max:1)
+	]
     ] ifFalse:[
-        self redrawFromLine:(oldEndLine min:selectionEndLine)
-                         to:(oldEndLine max:selectionEndLine)
+	self redrawFromLine:(oldEndLine min:selectionEndLine)
+			 to:(oldEndLine max:selectionEndLine)
     ].
     clickLine := movedLine.
     clickCol := movedCol
@@ -1442,11 +1539,11 @@
     "mouse- button release - turn off autoScroll if any"
 
     ((button == 1) or:[button == #select]) ifTrue:[
-        autoScrollBlock notNil ifTrue:[
-            self stopScrollSelect
-        ].
-        self enableOrDisableSelectionMenuEntries.
+	autoScrollBlock notNil ifTrue:[
+	    self stopScrollSelect
+	].
+	self enableOrDisableSelectionMenuEntries.
     ] ifFalse:[
-        super buttonRelease:button x:x y:y
+	super buttonRelease:button x:x y:y
     ]
 ! !