TextView.st
changeset 5677 fa9074e87571
parent 5676 20a8f1c87323
child 5678 9cbcdd21ea39
child 5713 83f67e5544b8
--- a/TextView.st	Thu Apr 21 17:38:25 2016 +0200
+++ b/TextView.st	Thu Apr 21 17:39:04 2016 +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
@@ -14,26 +14,26 @@
 "{ NameSpace: Smalltalk }"
 
 ListView subclass:#TextView
-        instanceVariableNames:'selectionStartLine selectionStartCol selectionEndLine
-                selectionEndCol clickPos clickStartLine clickStartCol clickLine
-                clickCol clickCount expandingTop wordStartCol wordStartLine
-                wordEndCol wordEndLine selectionFgColor selectionBgColor
-                selectStyle directoryForFileDialog defaultFileNameForFileDialog
-                externalEncoding contentsWasSaved searchAction lastSearchPattern
-                lastSearchWasMatch lastSearchIgnoredCase lastSearchDirection
-                lastSearchWasVariableSearch parenthesisSpecification dropSource
-                dragIsActive saveAction st80SelectMode searchBarActionBlock'
-        classVariableNames:'DefaultViewBackground DefaultSelectionForegroundColor
-                DefaultSelectionBackgroundColor
-                DefaultAlternativeSelectionForegroundColor
-                DefaultAlternativeSelectionBackgroundColor MatchDelayTime
-                WordSelectCatchesBlanks LastSearchPatterns
-                NumRememberedSearchPatterns LastSearchIgnoredCase
-                LastSearchWasMatch DefaultParenthesisSpecification
-                LastSearchWasMatchWithRegex LastSearchWasWrapAtEndOfText
-                LastSearchWasReplace LastSearchReplacedString'
-        poolDictionaries:''
-        category:'Views-Text'
+	instanceVariableNames:'selectionStartLine selectionStartCol selectionEndLine
+		selectionEndCol clickPos clickStartLine clickStartCol clickLine
+		clickCol clickCount expandingTop wordStartCol wordStartLine
+		wordEndCol wordEndLine selectionFgColor selectionBgColor
+		selectStyle directoryForFileDialog defaultFileNameForFileDialog
+		externalEncoding contentsWasSaved searchAction lastSearchPattern
+		lastSearchWasMatch lastSearchIgnoredCase lastSearchDirection
+		lastSearchWasVariableSearch parenthesisSpecification dropSource
+		dragIsActive saveAction st80SelectMode searchBarActionBlock'
+	classVariableNames:'DefaultViewBackground DefaultSelectionForegroundColor
+		DefaultSelectionBackgroundColor
+		DefaultAlternativeSelectionForegroundColor
+		DefaultAlternativeSelectionBackgroundColor MatchDelayTime
+		WordSelectCatchesBlanks LastSearchPatterns
+		NumRememberedSearchPatterns LastSearchIgnoredCase
+		LastSearchWasMatch DefaultParenthesisSpecification
+		LastSearchWasMatchWithRegex LastSearchWasWrapAtEndOfText
+		LastSearchWasReplace LastSearchReplacedString'
+	poolDictionaries:''
+	category:'Views-Text'
 !
 
 !TextView class methodsFor:'documentation'!
@@ -41,7 +41,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
@@ -84,27 +84,27 @@
       contentsWasSaved        <Boolean>               set to true, whenever saved in a file
 
       externalEncoding        <Symbol|nil>            external encoding, used when text is saved to
-                                                      a file. Usually something like
-                                                      #jis7, #euc, #sjis etc.
-                                                      (currently only passed down from the
-                                                       fileBrowser)
+						      a file. Usually something like
+						      #jis7, #euc, #sjis etc.
+						      (currently only passed down from the
+						       fileBrowser)
 
       dropSource              <DropSource>            drag operation descriptor or nil (dragging disabled)
       dragIsActive            <Boolean>               true, drag operation is activated
 
       searchAction            <Block>                 an autosearch action; typically set by the browser.
-                                                      Will be used as default when searchFwd/searchBwd is
-                                                      pressed. If the searchPattern is changed, no autosearch
-                                                      action will be executed.
+						      Will be used as default when searchFwd/searchBwd is
+						      pressed. If the searchPattern is changed, no autosearch
+						      action will be executed.
 
       searchBarActionBlock    <Block>                 search action block for embedded search
-                                                      panel. Used as second chance for searchFwd/bwd
+						      panel. Used as second chance for searchFwd/bwd
 
     [class variables:]
-        ST80Selections        <Boolean>               enables ST80 style doubleclick behavior
-                                                      (right after opening parenthesis, right before
-                                                       closing parenthesis, at begin of a line
-                                                       at begin of text)
+	ST80Selections        <Boolean>               enables ST80 style doubleclick behavior
+						      (right after opening parenthesis, right before
+						       closing parenthesis, at begin of a line
+						       at begin of text)
 
     [StyleSheet parameters:]
 
@@ -117,14 +117,14 @@
       text.selectionBackgroundColor             defaults to textForegroundColor
 
       text.alternativeSelectionForegroundColor  pasted text (i.e. paste will not replace)
-                                                defaults to selectionForegroundColor
+						defaults to selectionForegroundColor
       text.alternativeSelectionBackgroundColor  pasted text (i.e. paste will not replace)
-                                                defaults to selectionBackgroundColor
+						defaults to selectionBackgroundColor
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        EditTextView CodeView Workspace
+	EditTextView CodeView Workspace
 "
 !
 
@@ -135,18 +135,18 @@
     they may also be opened as a textEditor;
 
     open a (readonly) textView on some information text:
-                                                        [exBegin]
-        TextView
-            openWith:'read this'
-            title:'demonstration'
-                                                        [exEnd]
+							[exBegin]
+	TextView
+	    openWith:'read this'
+	    title:'demonstration'
+							[exEnd]
 
     the same, but open it modal:
-                                                        [exBegin]
-        TextView
-            openModalWith:'read this first'
-            title:'demonstration'
-                                                        [exEnd]
+							[exBegin]
+	TextView
+	    openModalWith:'read this first'
+	    title:'demonstration'
+							[exEnd]
 
 
     open it modal (but editable) on some text:
@@ -157,26 +157,26 @@
     However, usually an applicationModel is installed as the
     editor-topViews application. This would get a closeRequest,
     where it could handle things.
-                                                        [exBegin]
-        |m textView|
-
-        m := 'read this first' asValue.
-        textView := EditTextView openModalOnModel:m.
-        textView modified ifTrue:[
-            (self confirm:'text was not accepted - do it now ?')
-            ifTrue:[
-                m value:textView contents
-            ]
-        ].
-
-        Transcript showCR:m value.
-                                                        [exEnd]
+							[exBegin]
+	|m textView|
+
+	m := 'read this first' asValue.
+	textView := EditTextView openModalOnModel:m.
+	textView modified ifTrue:[
+	    (self confirm:'text was not accepted - do it now ?')
+	    ifTrue:[
+		m value:textView contents
+	    ]
+	].
+
+	Transcript showCR:m value.
+							[exEnd]
 
 
     open a textEditor on some file:
-                                                        [exBegin]
-        EditTextView openOn:'Makefile'
-                                                        [exEnd]
+							[exBegin]
+	EditTextView openOn:'Makefile'
+							[exEnd]
 
 "
 
@@ -188,28 +188,28 @@
     "for ST-80 compatibility"
 
     ^ (self new)
-        on:aModel
-        aspect:aspect
-        list:aspect
-        change:change
-        menu:menu
-        initialSelection:initial
+	on:aModel
+	aspect:aspect
+	list:aspect
+	change:change
+	menu:menu
+	initialSelection:initial
 !
 
 with:someText
     ^ (self new)
-        contents:someText
+	contents:someText
 ! !
 
 !TextView class methodsFor:'class initialization'!
 
 initialize
     DefaultParenthesisSpecification isNil ifTrue:[
-        DefaultParenthesisSpecification := IdentityDictionary new.
-        DefaultParenthesisSpecification at:#open        put:#( $( $[ ${ "$> $<") .
-        DefaultParenthesisSpecification at:#close       put:#( $) $] $} "$> $<").
-        DefaultParenthesisSpecification at:#ignore      put:#( $' $" '$[' '$]' '${' '$)' ).
-        DefaultParenthesisSpecification at:#eolComment  put:'"/'.     "/ sigh - must be 2 characters
+	DefaultParenthesisSpecification := IdentityDictionary new.
+	DefaultParenthesisSpecification at:#open        put:#( $( $[ ${ "$> $<") .
+	DefaultParenthesisSpecification at:#close       put:#( $) $] $} "$> $<").
+	DefaultParenthesisSpecification at:#ignore      put:#( $' $" '$[' '$]' '${' '$)' ).
+	DefaultParenthesisSpecification at:#eolComment  put:'"/'.     "/ sigh - must be 2 characters
     ].
 ! !
 
@@ -225,11 +225,11 @@
 
     i := self classResources at:'ICON' default:nil.
     i isNil ifTrue:[
-        nm := ClassResources at:'ICON_FILE' default:'Editor.xbm'.
-        i := Smalltalk imageFromFileNamed:nm forClass:self.
+	nm := ClassResources at:'ICON_FILE' default:'Editor.xbm'.
+	i := Smalltalk imageFromFileNamed:nm forClass:self.
     ].
     i notNil ifTrue:[
-        i := i onDevice:Display
+	i := i onDevice:Display
     ].
     ^ i
 
@@ -293,13 +293,13 @@
     "extract values from the styleSheet and cache them in class variables"
 
     <resource: #style (#'textView.background'
-                       #'text.selectionForegroundColor'
-                       #'text.selectionBackgroundColor'
-                       #'text.alternativeSelectionForegroundColor'
-                       #'text.alternativeSelectionBackgroundColor'
-                       #'textView.font'
-                       #'text.wordSelectCatchesBlanks'
-                       #'text.st80Selections')>
+		       #'text.selectionForegroundColor'
+		       #'text.selectionBackgroundColor'
+		       #'text.alternativeSelectionForegroundColor'
+		       #'text.alternativeSelectionBackgroundColor'
+		       #'textView.font'
+		       #'text.wordSelectCatchesBlanks'
+		       #'text.st80Selections')>
 
     DefaultViewBackground := StyleSheet colorAt:'textView.background' default:White.
     DefaultSelectionForegroundColor := StyleSheet colorAt:'text.selectionForegroundColor'.
@@ -780,9 +780,9 @@
     top := StandardSystemView label:label icon:self defaultIcon.
 
     frame := HVScrollableView
-                for:self
-                miniScrollerH:true miniScrollerV:false
-                in:top.
+		for:self
+		miniScrollerH:true miniScrollerV:false
+		in:top.
     frame origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
     ^ frame scrolledView
 
@@ -796,7 +796,7 @@
 
     textView := self setupEmpty.
     aFileName notNil ifTrue:[
-        textView setupForFile:aFileName.
+	textView setupForFile:aFileName.
     ].
 
     ^ textView
@@ -827,7 +827,7 @@
     aTitle notNil ifTrue:[top label:aTitle].
 
     aStringOrStringCollection notNil ifTrue:[
-        textView contents:aStringOrStringCollection
+	textView contents:aStringOrStringCollection
     ].
 
     ^ textView
@@ -891,7 +891,7 @@
 
     selectionStartLine isNil ifTrue:[^ 0].
     ^ self characterPositionOfLine:selectionStartLine
-                               col:selectionStartCol
+			       col:selectionStartCol
 
     "Modified: 14.8.1997 / 16:35:37 / cg"
 !
@@ -902,7 +902,7 @@
 
     selectionStartLine isNil ifTrue:[^ 0].
     ^ self characterPositionOfLine:selectionEndLine
-                               col:selectionEndCol
+			       col:selectionEndCol
 
     "Created: 14.8.1997 / 16:35:24 / cg"
     "Modified: 14.8.1997 / 16:35:45 / cg"
@@ -1006,11 +1006,11 @@
 contents:newContents selected:selectedBoolean
     self contents:newContents.
     selectedBoolean ifTrue:[
-        list size == 1 ifTrue:[
-            self selectFromLine:1 col:1 toLine:1 col:(list at:1) size
-        ] ifFalse:[
-            self selectAll
-        ]
+	list size == 1 ifTrue:[
+	    self selectFromLine:1 col:1 toLine:1 col:(list at:1) size
+	] ifFalse:[
+	    self selectAll
+	]
     ]
 
     "
@@ -1066,10 +1066,10 @@
     super setContents:something.
 
     selStartLine notNil ifTrue:[
-        self
-            selectFromLine:selStartLine col:selStartCol
-            toLine:selEndLine col:selEndCol.
-        selectStyle := selStyle
+	self
+	    selectFromLine:selStartLine col:selStartCol
+	    toLine:selEndLine col:selEndCol.
+	selectStyle := selStyle
     ].
 
 
@@ -1092,9 +1092,9 @@
 
     self loadTextFile:aFileName.
     aFileName notNil ifTrue:[
-        baseName := aFileName asFilename baseName.
-        self topView label:baseName.
-        self defaultFileNameForFileDialog:baseName.
+	baseName := aFileName asFilename baseName.
+	self topView label:baseName.
+	self defaultFileNameForFileDialog:baseName.
     ].
 
     "Created: / 25-10-2006 / 14:47:13 / cg"
@@ -1123,35 +1123,35 @@
     beginCol := self findBeginOfWordAtLine:selectLine col:selectCol.
     endCol := self findEndOfWordAtLine:selectLine col:selectCol.
     endCol == 0 ifTrue:[
-        endLine := selectLine + 1
+	endLine := selectLine + 1
     ].
 
     "is the initial character within a word ?"
     (wordCheck value:thisCharacter) ifTrue:[
-        "
-         try to catch a blank ...
-        "
-
-        WordSelectCatchesBlanks ifTrue:[
-            ((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 ...
+	"
+
+	WordSelectCatchesBlanks ifTrue:[
+	    ((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
+	    ].
+	].
     ].
     aFiveArgBlock value:selectLine
-                  value:beginCol
-                  value:endLine
-                  value:endCol
-                  value:flag
+		  value:beginCol
+		  value:endLine
+		  value:endCol
+		  value:flag
 
     "Modified: 18.3.1996 / 17:31:04 / cg"
 ! !
@@ -1178,7 +1178,7 @@
     selectionFgColor := color1 onDevice:device.
     selectionBgColor := color2 onDevice:device.
     self hasSelection ifTrue:[
-        self invalidate
+	self invalidate
     ]
 
     "Modified: 29.5.1996 / 16:22:15 / cg"
@@ -1191,7 +1191,7 @@
      and selection. Added for ST-80 compatibility"
 
     aspectSym notNil ifTrue:[aspectMsg := aspectSym.
-                             listMsg isNil ifTrue:[listMsg := aspectSym]].
+			     listMsg isNil ifTrue:[listMsg := aspectSym]].
     changeSym notNil ifTrue:[changeMsg := changeSym].
     listSym notNil ifTrue:[listMsg := listSym].
     menuSym notNil ifTrue:[menuMsg := menuSym].
@@ -1208,15 +1208,15 @@
     "enable/disable dragging support
     "
     aBoolean ifFalse:[
-        dropSource := nil.
+	dropSource := nil.
     ] ifTrue:[
-        dropSource isNil ifTrue:[
-            dropSource := DropSource
-                            receiver:self
-                            argument:nil
-                            dropObjectSelector:#collectionOfDragObjects
-                            displayObjectSelector:nil
-        ]
+	dropSource isNil ifTrue:[
+	    dropSource := DropSource
+			    receiver:self
+			    argument:nil
+			    dropObjectSelector:#collectionOfDragObjects
+			    displayObjectSelector:nil
+	]
     ].
 !
 
@@ -1407,27 +1407,27 @@
     "multi-mouse-click - select word under pointer"
 
     (button == 1) ifTrue:[
-        clickPos := x @ y.
-
-        "/ The searchAction is mantained until a cut/replace or a search with a user selection is done
+	clickPos := x @ y.
+
+	"/ The searchAction is mantained until a cut/replace or a search with a user selection is done
 "/        self clearSearchAction.
 
-        clickCount notNil ifTrue:[
-            clickCount := clickCount + 1.
-            (clickCount == 2) ifTrue:[
-                self doubleClickX:x y:y
-            ] ifFalse:[
-                (clickCount == 3) ifTrue:[
-                    self tripleClickX:x y:y
-                ] ifFalse:[
-                    (clickCount == 4) ifTrue:[
-                        self quadClickX:x y:y
-                    ]
-                ]
-            ]
-        ]
+	clickCount notNil ifTrue:[
+	    clickCount := clickCount + 1.
+	    (clickCount == 2) ifTrue:[
+		self doubleClickX:x y:y
+	    ] ifFalse:[
+		(clickCount == 3) ifTrue:[
+		    self tripleClickX:x y:y
+		] ifFalse:[
+		    (clickCount == 4) ifTrue:[
+			self quadClickX:x y:y
+		    ]
+		]
+	    ]
+	]
     ] ifFalse:[
-        super buttonMultiPress:button x:x y:y
+	super buttonMultiPress:button x:x y:y
     ]
 
     "Modified: 11.9.1997 / 04:15:35 / cg"
@@ -1442,30 +1442,30 @@
     sensor       := self sensor.
 
     (button == 1) ifTrue:[
-        sensor shiftDown ifTrue:[
-            "mouse-click with shift - adding to selection"
-            self extendSelectionToX:x y:y.
-            ^ self
-        ].
-
-        clickVisibleLine := self visibleLineOfY:y.
-        clickPos := x @ y.
-        clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
-        clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
-        clickStartLine := clickLine.
-        clickStartCol := clickCol.
-
-        (self canDrag
-        and:[(self isInSelection:clickLine col:clickCol)
-        and:[UserPreferences current startTextDragWithControl not
-             or:[sensor ctrlDown]]]) ifTrue:[
-            dragIsActive := true
-        ] ifFalse:[
-            self unselect.
-        ].
-        clickCount := 1
+	sensor shiftDown ifTrue:[
+	    "mouse-click with shift - adding to selection"
+	    self extendSelectionToX:x y:y.
+	    ^ self
+	].
+
+	clickVisibleLine := self visibleLineOfY:y.
+	clickPos := x @ y.
+	clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
+	clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
+	clickStartLine := clickLine.
+	clickStartCol := clickCol.
+
+	(self canDrag
+	and:[(self isInSelection:clickLine col:clickCol)
+	and:[UserPreferences current startTextDragWithControl not
+	     or:[sensor ctrlDown]]]) ifTrue:[
+	    dragIsActive := true
+	] ifFalse:[
+	    self unselect.
+	].
+	clickCount := 1
     ] ifFalse:[
-        super buttonPress:button x:x y:y
+	super buttonPress:button x:x y:y
     ]
 
     "Modified: / 20.5.1999 / 17:02:45 / cg"
@@ -1858,8 +1858,8 @@
     "handle some keyboard input (there is not much to be done here)"
 
     <resource: #keyboard (#Find #Copy #FindNext #FindPrev #FindAgain
-                          #GotoLine #SelectAll #SaveAs #Print
-                          #'F*' #'f*' #ZoomIn #ZoomOut)>
+			  #GotoLine #SelectAll #SaveAs #Print
+			  #'F*' #'f*' #ZoomIn #ZoomOut)>
 
     (key == #Find) ifTrue:[self search. ^self].
     (key == #Copy) ifTrue:[self copySelection. ^self].
@@ -1884,14 +1884,14 @@
      (see EditTextView>>keyPress:x:y and Workspace>>keyPress:x:y)
     "
     (key size > 1 and:[(key at:1) asLowercase == $f]) ifTrue:[
-        (('[fF][0-9]' match:key)
-        or:['[fF][0-9][0-9]' match:key]) ifTrue:[
-            self sensor shiftDown ifTrue:[
-                UserPreferences current functionKeySequences
-                    at:key put:(self selection)
-            ].
-            ^ self
-        ].
+	(('[fF][0-9]' match:key)
+	or:['[fF][0-9][0-9]' match:key]) ifTrue:[
+	    self sensor shiftDown ifTrue:[
+		UserPreferences current functionKeySequences
+		    at:key put:(self selection)
+	    ].
+	    ^ self
+	].
     ].
 
     super keyPress:key x:x y:y
@@ -2001,22 +2001,22 @@
     filename := aFileName asFilename.
 
     (FileStream userInitiatedFileSaveQuerySignal queryWith:filename) ifFalse:[
-        msg := resources string:'Refused to append to file ''%1'' !!' with:filename name.
-        self warn:(msg , '\\(ST/X internal permission check)' ) withCRs.
-        ^ self
+	msg := resources string:'Refused to append to file ''%1'' !!' with:filename name.
+	self warn:(msg , '\\(ST/X internal permission check)' ) withCRs.
+	^ self
     ].
 
     [
-        aStream := filename appendingWriteStream.
-        [
-            self fileOutContentsOn:aStream compressTabs:true encoding:externalEncoding.
-        ] ensure:[
-            aStream close.
-        ].
-        contentsWasSaved := true
+	aStream := filename appendingWriteStream.
+	[
+	    self fileOutContentsOn:aStream compressTabs:true encoding:externalEncoding.
+	] ensure:[
+	    aStream close.
+	].
+	contentsWasSaved := true
     ] on:FileStream openErrorSignal do:[:ex|
-        msg := resources string:'cannot append to file %1 !!' with:filename name.
-        self warn:(msg , '\\(' , FileStream lastErrorString , ')' ) withCRs
+	msg := resources string:'cannot append to file %1 !!' with:filename name.
+	self warn:(msg , '\\(' , FileStream lastErrorString , ')' ) withCRs
     ]
 
     "Modified: / 27-07-2012 / 09:41:18 / cg"
@@ -2043,7 +2043,7 @@
             
             TextView defaultFont:newFont.
             fontPrefs at:#Text put:(newFont storeString).
-            newPrefs notNil ifTrue:[ userPrefs fontPreferences:newPrefs ].
+            newFontPrefs notNil ifTrue:[ userPrefs fontPreferences:newFontPrefs ].
             userPrefs beModified.
             DebugView newDebugger.
             TextView allSubInstances do:[:v |
@@ -2062,11 +2062,11 @@
 
     text := self selection.
     text notNil ifTrue:[
-        self unselect.
-
-        "/ forget any emphasis ...
-        text := text collect:[:l | l isNil ifTrue:[l] ifFalse:[l string]].
-        self setClipboardText:text.
+	self unselect.
+
+	"/ forget any emphasis ...
+	text := text collect:[:l | l isNil ifTrue:[l] ifFalse:[l string]].
+	self setClipboardText:text.
     ]
 
     "Modified: 17.5.1996 / 08:57:54 / cg"
@@ -2088,19 +2088,19 @@
     list isNil ifTrue:[^ self].
 
     self withWaitCursorDo:[
-        printStream := Printer new.
-        printStream supportsContext ifTrue:[
-            printStream printerContext font:(self font).
-        ].
-
-        Printer writeErrorSignal handle:[:ex |
-            self warn:('error while printing:\\'
-                        , ex description
-                        , '\\(printing with: ' , (Printer printCommand) , ')') withCRs
-        ] do:[
-            self fileOutContentsOn:printStream.
-        ].
-        printStream close
+	printStream := Printer new.
+	printStream supportsContext ifTrue:[
+	    printStream printerContext font:(self font).
+	].
+
+	Printer writeErrorSignal handle:[:ex |
+	    self warn:('error while printing:\\'
+			, ex description
+			, '\\(printing with: ' , (Printer printCommand) , ')') withCRs
+	] do:[
+	    self fileOutContentsOn:printStream.
+	].
+	printStream close
     ].
 
     "Created: / 06-05-1996 / 16:11:26 / cg"
@@ -2116,21 +2116,21 @@
     |items m|
 
     items := #(
-                        ('Copy'          copySelection  Copy)
-                        ('-'             nil            )
-                        ('Search...'     search         Find)
-                        ('Goto Line...'  gotoLine       GotoLine)
-                        ('-'             nil            )
-                        ('Font...'       changeFont     )
-                        ('-'             nil            )
-                        ('Save As...'    save           SaveAs)
-                        ('Print'         doPrint        Print)
-                ).
+			('Copy'          copySelection  Copy)
+			('-'             nil            )
+			('Search...'     search         Find)
+			('Goto Line...'  gotoLine       GotoLine)
+			('-'             nil            )
+			('Font...'       changeFont     )
+			('-'             nil            )
+			('Save As...'    save           SaveAs)
+			('Print'         doPrint        Print)
+		).
 
     m := PopUpMenu itemList:items resources:resources.
 
     self hasSelectionForCopy ifFalse:[
-        m disable:#copySelection.
+	m disable:#copySelection.
     ].
     ^ m
 
@@ -2165,41 +2165,41 @@
     |l lineNumberBox input lineToGo relative|
 
     lineNumberBox :=
-        EnterBox
-           title:(resources string:'Line number (or +/- relativeNr):')
-           okText:(resources string:'Goto')
-           abortText:(resources string:'Cancel')
-           action:[:l | input := l].
+	EnterBox
+	   title:(resources string:'Line number (or +/- relativeNr):')
+	   okText:(resources string:'Goto')
+	   abortText:(resources string:'Cancel')
+	   action:[:l | input := l].
 
     l := self defaultForGotoLine.
     l notNil ifTrue:[
-        l := l printString
+	l := l printString
     ].
     lineNumberBox initialText:l .
     lineNumberBox label:(resources string:'Goto Line').
     lineNumberBox showAtPointer.
 
     input size > 0 ifTrue:[
-        input := input withoutSpaces.
-        input size > 0 ifTrue:[
-            (input startsWith:$+) ifTrue:[
-                relative := 1.
-            ] ifFalse:[
-                (input startsWith:$-) ifTrue:[
-                    relative := -1.
-                ].
-            ].
-            relative notNil ifTrue:[
-                input := input copyFrom:2.
-            ].
-            lineToGo := Integer readFromString:input onError:nil.
-            lineToGo notNil ifTrue:[
-                relative notNil ifTrue:[
-                    lineToGo := self currentLine + (lineToGo * relative)
-                ].
-                self gotoLine:lineToGo
-            ]
-        ]
+	input := input withoutSpaces.
+	input size > 0 ifTrue:[
+	    (input startsWith:$+) ifTrue:[
+		relative := 1.
+	    ] ifFalse:[
+		(input startsWith:$-) ifTrue:[
+		    relative := -1.
+		].
+	    ].
+	    relative notNil ifTrue:[
+		input := input copyFrom:2.
+	    ].
+	    lineToGo := Integer readFromString:input onError:nil.
+	    lineToGo notNil ifTrue:[
+		relative notNil ifTrue:[
+		    lineToGo := self currentLine + (lineToGo * relative)
+		].
+		self gotoLine:lineToGo
+	    ]
+	]
     ].
 
     "Modified: / 17.5.1998 / 20:07:59 / cg"
@@ -2210,11 +2210,11 @@
      and save contents into that file."
 
     Dialog
-        requestSaveFileName:(resources string:'Save contents in:')
-        default:defaultFileNameForFileDialog
-        fromDirectory:directoryForFileDialog
-        action:[:fileName | self saveAs:fileName]
-        appendAction:[:fileName | self appendTo:fileName]
+	requestSaveFileName:(resources string:'Save contents in:')
+	default:defaultFileNameForFileDialog
+	fromDirectory:directoryForFileDialog
+	action:[:fileName | self saveAs:fileName]
+	appendAction:[:fileName | self appendTo:fileName]
 !
 
 openSearchBoxAndSearch
@@ -2599,16 +2599,16 @@
 
     pattern := patternArg string.
     pattern notEmpty ifTrue:[
-        self rememberSearchPattern:pattern.
-        "/ LastSearchIgnoredCase := lastSearchIgnoredCase := ign.
-        "/ LastSearchWasMatch := match.
-        fwd ifFalse:[
-            lastSearchDirection := #backward.
-            self searchBwd:pattern ignoreCase:ign match: match.          "    backward search with match is not yet available  "
-        ] ifTrue:[
-            lastSearchDirection := #forward.
-            self searchFwd:pattern ignoreCase:ign match: match.
-        ]
+	self rememberSearchPattern:pattern.
+	"/ LastSearchIgnoredCase := lastSearchIgnoredCase := ign.
+	"/ LastSearchWasMatch := match.
+	fwd ifFalse:[
+	    lastSearchDirection := #backward.
+	    self searchBwd:pattern ignoreCase:ign match: match.          "    backward search with match is not yet available  "
+	] ifTrue:[
+	    lastSearchDirection := #forward.
+	    self searchFwd:pattern ignoreCase:ign match: match.
+	]
     ]
 
     "Created: / 11-07-2006 / 11:18:04 / fm"
@@ -2620,11 +2620,11 @@
     "/ LastSearchIgnoredCase := lastSearchIgnoredCase := ign.
     "/ LastSearchWasMatch := match.
     aSearchSpec forward ifFalse:[
-        lastSearchDirection := #backward.
-        self searchBwdUsingSpec:aSearchSpec
+	lastSearchDirection := #backward.
+	self searchBwdUsingSpec:aSearchSpec
     ] ifTrue:[
-        lastSearchDirection := #forward.
-        self searchFwdUsingSpec:aSearchSpec
+	lastSearchDirection := #forward.
+	self searchFwdUsingSpec:aSearchSpec
     ]
 
     "Created: / 11-07-2006 / 11:18:04 / fm"
@@ -2648,25 +2648,25 @@
 
     lastSearchWasVariableSearch := true.
     el := fwd
-        ifTrue:[syntaxElementForVariable nextElement]
-        ifFalse:[syntaxElementForVariable previousElement].
+	ifTrue:[syntaxElementForVariable nextElement]
+	ifFalse:[syntaxElementForVariable previousElement].
 
     el notNil ifTrue:[
-        "bug workaround"
-        (el start = syntaxElementForVariable start) ifTrue:[
-            el2 := fwd
-                ifTrue:[el nextElement]
-                ifFalse:[el previousElement].
-            el2 notNil ifTrue:[
-                el := el2
-            ]
-        ].
+	"bug workaround"
+	(el start = syntaxElementForVariable start) ifTrue:[
+	    el2 := fwd
+		ifTrue:[el nextElement]
+		ifFalse:[el previousElement].
+	    el2 notNil ifTrue:[
+		el := el2
+	    ]
+	].
     ].
     el notNil ifTrue:[
-        self selectFromCharacterPosition:el start to:el stop.
-        self makeLineVisible:(self lineOfCharacterPosition:el start).
+	self selectFromCharacterPosition:el start to:el stop.
+	self makeLineVisible:(self lineOfCharacterPosition:el start).
     ] ifFalse:[
-        self showNotFound
+	self showNotFound
     ].
 
     "Created: / 08-03-2012 / 14:08:20 / cg"
@@ -2714,8 +2714,8 @@
     "save contents on a stream, replacing leading spaces by tab-characters."
 
     self
-        fileOutContentsOn:aStream
-        compressTabs:true
+	fileOutContentsOn:aStream
+	compressTabs:true
 !
 
 fileOutContentsOn:aStream compressTabs:compressTabs
@@ -2723,9 +2723,9 @@
      leading spaces will be replaced by tab-characters in the output."
 
     self
-        fileOutContentsOn:aStream
-        compressTabs:compressTabs
-        encoding:nil
+	fileOutContentsOn:aStream
+	compressTabs:compressTabs
+	encoding:nil
 !
 
 fileOutContentsOn:aStream compressTabs:compressTabs encoding:encodingSymOrNil
@@ -2867,15 +2867,15 @@
     nRemembered := NumRememberedSearchPatterns ? 20.
 
     LastSearchPatterns isNil ifTrue:[
-        LastSearchPatterns := OrderedCollection new.
+	LastSearchPatterns := OrderedCollection new.
     ].
     "/ move to top or addFirst
     (LastSearchPatterns includes:patternString) ifTrue:[
-        LastSearchPatterns remove:patternString.
+	LastSearchPatterns remove:patternString.
     ] ifFalse:[
-        LastSearchPatterns size > nRemembered ifTrue:[
-            LastSearchPatterns removeLast
-        ]
+	LastSearchPatterns size > nRemembered ifTrue:[
+	    LastSearchPatterns removeLast
+	]
     ].
     LastSearchPatterns addFirst:patternString.
 
@@ -2885,12 +2885,12 @@
 removeTrailingWhitespace
     list isNil ifTrue:[^self].
     list keysAndValuesDo:[:lineNR :line |
-        |l|
-
-        line notNil ifTrue:[
-            l := line withoutTrailingSeparators.
-            list at:lineNR put:l.
-        ]
+	|l|
+
+	line notNil ifTrue:[
+	    l := line withoutTrailingSeparators.
+	    list at:lineNR put:l.
+	]
     ].
 !
 
@@ -2994,10 +2994,10 @@
     "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
     ]
 !
 
@@ -3014,14 +3014,14 @@
     "return the width in pixels for a scroll between firstLine and lastLine"
 
     selectionStartLine notNil ifTrue:[
-        "/ if there is a selection which covers multiple lines,
-        "/ we have to scroll the whole width (to include the selection-rectangle)
-
-        (lastLine < selectionStartLine) ifFalse:[
-            (firstLine > selectionEndLine) ifFalse:[
-                ^ width
-            ]
-        ].
+	"/ if there is a selection which covers multiple lines,
+	"/ we have to scroll the whole width (to include the selection-rectangle)
+
+	(lastLine < selectionStartLine) ifFalse:[
+	    (firstLine > selectionEndLine) ifFalse:[
+		^ width
+	    ]
+	].
     ].
     ^ super widthForScrollBetween:firstLine and:lastLine
 ! !
@@ -3063,39 +3063,39 @@
 
 drawSelectedFromVisibleLine:startVisLineNr to:endVisLineNr
     startVisLineNr to:endVisLineNr do:[:visLine |
-        self drawVisibleLineSelected:visLine
+	self drawVisibleLineSelected:visLine
     ]
 !
 
 drawVisibleLineSelected:visLineNr
     self
-        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
-        inVisible:visLineNr
-        with:self currentSelectionFgColor and:self currentSelectionBgColor
+	drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
+	inVisible:visLineNr
+	with:self currentSelectionFgColor and:self currentSelectionBgColor
 !
 
 drawVisibleLineSelected:visLineNr col:col
     self
-        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
-        inVisible:visLineNr
-        col:col
-        with:self currentSelectionFgColor and:self currentSelectionBgColor
+	drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
+	inVisible:visLineNr
+	col:col
+	with:self currentSelectionFgColor and:self currentSelectionBgColor
 !
 
 drawVisibleLineSelected:visLineNr from:selectionStartCol
     self
-        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
-        inVisible:visLineNr
-        from:selectionStartCol
-        with:self currentSelectionFgColor and:self currentSelectionBgColor.
+	drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
+	inVisible:visLineNr
+	from:selectionStartCol
+	with:self currentSelectionFgColor and:self currentSelectionBgColor.
 !
 
 drawVisibleLineSelected:visLineNr from:startCol to:endCol
     self
-        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
-        inVisible:visLineNr
-        from:startCol to:endCol
-        with:self currentSelectionFgColor and:self currentSelectionBgColor.
+	drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
+	inVisible:visLineNr
+	from:startCol to:endCol
+	with:self currentSelectionFgColor and:self currentSelectionBgColor.
 !
 
 redrawFromVisibleLine:startVisLineNr to:endVisLineNr
@@ -3107,70 +3107,70 @@
 
     end := endVisLineNr.
     (end > nLinesShown) ifTrue:[
-        end := nLinesShown
+	end := nLinesShown
     ].
 
     selectionEndLine isNil ifTrue:[
-        selectionStartLine := nil
+	selectionStartLine := nil
     ].
 
     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 drawSelectedFromVisibleLine:startVisLineNr to:end.
-        ^ self
+	self drawSelectedFromVisibleLine:startVisLineNr to:end.
+	^ self
     ].
 
     (selectionStartLine >= firstLineShown) ifTrue:[
-        "draw unselected top part"
-
-        selVisStart := self listLineToVisibleLine:selectionStartLine.
-        super redrawFromVisibleLine:startVisLineNr to:(selVisStart - 1).
-
-        "and first partial selected line"
-        self redrawVisibleLine:selVisStart.
-
-        "rest starts after this one"
-        line1 := selVisStart + 1
+	"draw unselected top part"
+
+	selVisStart := self listLineToVisibleLine:selectionStartLine.
+	super redrawFromVisibleLine:startVisLineNr to:(selVisStart - 1).
+
+	"and first partial selected line"
+	self redrawVisibleLine:selVisStart.
+
+	"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 drawSelectedFromVisibleLine:line1 to:line2.
@@ -3181,7 +3181,7 @@
     self redrawVisibleLine:(line2 + 1).
 
     ((line2 + 2) <= end) ifTrue:[
-        super redrawFromVisibleLine:(line2 + 2) to:end
+	super redrawFromVisibleLine:(line2 + 2) to:end
     ]
 !
 
@@ -3277,22 +3277,22 @@
 
     col := startCol.
     col == 0 ifTrue:[
-        col := 1.
+	col := 1.
     ].
 
     (selectionStartLine notNil and:[selectionEndLine notNil]) ifTrue:[
-        line := self visibleLineToAbsoluteLine:visLine.
-        (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 drawVisibleLineSelected:visLine from:col.
-            ^ self
-        ]
+	line := self visibleLineToAbsoluteLine:visLine.
+	(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 drawVisibleLineSelected:visLine from:col.
+	    ^ self
+	]
     ].
     super redrawVisibleLine:visLine from:col
 
@@ -3416,8 +3416,8 @@
 !
 
 scanFor:aCharacter fromLine:startLine col:startCol forward:forward
-                     ifFound:foundBlock
-                  ifNotFound:notFoundBlock
+		     ifFound:foundBlock
+		  ifNotFound:notFoundBlock
     "search for a character in the direction given by forward.
      Performs foundBlock with line/col as argument if found, notFoundBlock if not."
 
@@ -3433,9 +3433,9 @@
     col := startCol.
     line := startLine.
     forward ifTrue:[
-        delta := 1.
+	delta := 1.
     ] ifFalse:[
-        delta := -1.
+	delta := -1.
     ].
 
     lineString := list at:line.
@@ -3443,30 +3443,30 @@
 
     col := col + delta.
     [true] whileTrue:[
-        lineString notNil ifTrue:[
-            forward ifTrue:[
-                endCol := lineString size.
-            ] ifFalse:[
-                endCol := 1
-            ].
-
-            col to:endCol by:delta do:[:rCol |
-                cc := lineString at:rCol.
-                cc == aCharacter ifTrue:[
-                    ^ foundBlock value:line value:rCol.
-                ]
-            ].
-        ].
-        line := line + delta.
-        (line < 1 or:[line > maxLine]) ifTrue:[
-            ^ notFoundBlock value
-        ].
-        lineString := list at:line.
-        forward ifTrue:[
-            col := 1
-        ] ifFalse:[
-            col := lineString size
-        ]
+	lineString notNil ifTrue:[
+	    forward ifTrue:[
+		endCol := lineString size.
+	    ] ifFalse:[
+		endCol := 1
+	    ].
+
+	    col to:endCol by:delta do:[:rCol |
+		cc := lineString at:rCol.
+		cc == aCharacter ifTrue:[
+		    ^ foundBlock value:line value:rCol.
+		]
+	    ].
+	].
+	line := line + delta.
+	(line < 1 or:[line > maxLine]) ifTrue:[
+	    ^ notFoundBlock value
+	].
+	lineString := list at:line.
+	forward ifTrue:[
+	    col := 1
+	] ifFalse:[
+	    col := lineString size
+	]
     ].
     "not reached"
 
@@ -3488,8 +3488,8 @@
     |ign match|
 
     searchBarActionBlock notNil ifTrue:[
-        searchBarActionBlock value:#forward value:self.
-        ^ self
+	searchBarActionBlock value:#forward value:self.
+	^ self
     ].
 
     ign := lastSearchIgnoredCase ? LastSearchIgnoredCase ? true.
@@ -3497,17 +3497,17 @@
 
     self setSearchPatternWithMatchEscapes: match.
     lastSearchPattern notNil ifTrue:[
-        lastSearchDirection == #backward ifTrue:[
-            self
-                searchBwd:lastSearchPattern
-                ignoreCase:ign
-                match: match
-        ] ifFalse:[
-            self
-                searchFwd:lastSearchPattern
-                ignoreCase:ign
-                match: match
-        ]
+	lastSearchDirection == #backward ifTrue:[
+	    self
+		searchBwd:lastSearchPattern
+		ignoreCase:ign
+		match: match
+	] ifFalse:[
+	    self
+		searchFwd:lastSearchPattern
+		ignoreCase:ign
+		match: match
+	]
     ]
 
     "Created: / 03-05-1999 / 15:02:16 / cg"
@@ -3521,43 +3521,43 @@
     |ign selectedVariable|
 
     searchAction notNil ifTrue:[
-        "/autosearch is cleared whenever there is search with user selection
-        (self hasSelection and:[self hasSearchActionSelection not]) ifTrue: [self clearSearchAction].
+	"/autosearch is cleared whenever there is search with user selection
+	(self hasSelection and:[self hasSearchActionSelection not]) ifTrue: [self clearSearchAction].
     ].
 
     searchAction notNil ifTrue:[
-        "/confusing: this is for autosearch of variables (browse variable uses, for example)
-        self searchUsingSearchAction:#backward.
-        ^ self.
+	"/confusing: this is for autosearch of variables (browse variable uses, for example)
+	self searchUsingSearchAction:#backward.
+	^ self.
     ].
     searchBarActionBlock notNil ifTrue:[
-        searchBarActionBlock value:#backward value:self.
-        ^ self
+	searchBarActionBlock value:#backward value:self.
+	^ self
     ].
     lastSearchWasVariableSearch ifTrue:[
-        selectedVariable := self syntaxElementForSelectedVariable.
-        selectedVariable notNil ifTrue:[
-            self searchVariableWithSyntaxElement:selectedVariable forward:false.
-            ^ self.
-        ].
-        lastSearchWasVariableSearch := false.
+	selectedVariable := self syntaxElementForSelectedVariable.
+	selectedVariable notNil ifTrue:[
+	    self searchVariableWithSyntaxElement:selectedVariable forward:false.
+	    ^ self.
+	].
+	lastSearchWasVariableSearch := false.
     ].
 
     ign := lastSearchIgnoredCase ? LastSearchIgnoredCase ? true.
 
     self setSearchPatternWithMatchEscapes: false.
     lastSearchPattern isNil ifTrue:[
-        LastSearchPatterns size > 0 ifTrue:[
-            lastSearchPattern := LastSearchPatterns first
-        ]
+	LastSearchPatterns size > 0 ifTrue:[
+	    lastSearchPattern := LastSearchPatterns first
+	]
     ].
 
     lastSearchPattern notNil ifTrue:[
-        lastSearchDirection := #backward.
-        self rememberSearchPattern:lastSearchPattern.
-        self
-            searchBwd:lastSearchPattern
-            ignoreCase:ign
+	lastSearchDirection := #backward.
+	self rememberSearchPattern:lastSearchPattern.
+	self
+	    searchBwd:lastSearchPattern
+	    ignoreCase:ign
     ]
 
     "Modified: / 08-03-2012 / 14:26:25 / cg"
@@ -3577,9 +3577,9 @@
     "do a backward search"
 
     self
-        searchBwdUsingSpec:(ListView::SearchSpec new
-                                        pattern:pattern)
-        ifAbsent:aBlock
+	searchBwdUsingSpec:(ListView::SearchSpec new
+					pattern:pattern)
+	ifAbsent:aBlock
 
     "Modified: 13.9.1997 / 01:05:49 / cg"
 !
@@ -3588,12 +3588,12 @@
     "do a backward search"
 
     self
-        searchBwd:pattern
-        ignoreCase:ign
-        ifAbsent:[
-                    self sensor compressKeyPressEventsWithKey:#FindPrev.
-                    self showNotFound
-                 ].
+	searchBwd:pattern
+	ignoreCase:ign
+	ifAbsent:[
+		    self sensor compressKeyPressEventsWithKey:#FindPrev.
+		    self showNotFound
+		 ].
     "/ lastSearchIgnoredCase := ign.
     lastSearchPattern := pattern string
 
@@ -3605,10 +3605,10 @@
     "do a backward search"
 
     self
-        searchBwdUsingSpec:(ListView::SearchSpec new
-                                        pattern:pattern
-                                        ignoreCase:ign)
-        ifAbsent:aBlock
+	searchBwdUsingSpec:(ListView::SearchSpec new
+					pattern:pattern
+					ignoreCase:ign)
+	ifAbsent:aBlock
 
     "Modified: 13.9.1997 / 01:05:49 / cg"
     "Created: 13.9.1997 / 06:18:41 / cg"
@@ -3628,8 +3628,8 @@
     "do a backward search"
 
     self
-        searchBwdUsingSpec:searchSpec
-        ifAbsent:[self showNotFound].
+	searchBwdUsingSpec:searchSpec
+	ifAbsent:[self showNotFound].
 
 "/    lastSearchIgnoredCase := false.
     lastSearchPattern := searchSpec pattern string
@@ -3647,30 +3647,30 @@
     startCol := pos x.
 
     self
-        searchBackwardUsingSpec:searchSpec
-        startingAtLine:startLine col:startCol
-        ifFound:[:line :col | self showMatch:searchSpec pattern isMatch:searchSpec match atLine:line col:col]
-        ifAbsent:aBlock
+	searchBackwardUsingSpec:searchSpec
+	startingAtLine:startLine col:startCol
+	ifFound:[:line :col | self showMatch:searchSpec pattern isMatch:searchSpec match atLine:line col:col]
+	ifAbsent:aBlock
 !
 
 searchForAndSelectMatchingParenthesisFromLine:startLine col:startCol
     "select characters enclosed by matching parenthesis if one is under startLine/Col"
 
     self
-        searchForMatchingParenthesisFromLine:startLine col:startCol
-        ifFound:[:line :col |
-                  self selectFromLine:startLine col:startCol
-                               toLine:line col:col]
-        ifNotFound:[self showNotFound]
-        onError:[self beep]
+	searchForMatchingParenthesisFromLine:startLine col:startCol
+	ifFound:[:line :col |
+		  self selectFromLine:startLine col:startCol
+			       toLine:line col:col]
+	ifNotFound:[self showNotFound]
+	onError:[self beep]
 
     "Modified: 9.10.1997 / 12:57:34 / cg"
 !
 
 searchForMatchingParenthesisFromLine:startLine col:startCol
-                     ifFound:foundBlock
-                  ifNotFound:notFoundBlock
-                     onError:failBlock
+		     ifFound:foundBlock
+		  ifNotFound:notFoundBlock
+		     onError:failBlock
 
     "search for a matching parenthesis; start search with character at startLine/startCol.
      Search for the corresponding character is done forward if its an opening,
@@ -3679,20 +3679,20 @@
      If there is a nesting error, evaluate failBlock."
 
     ^ self
-        searchForMatchingParenthesisFromLine:startLine col:startCol
-        ifFound:foundBlock
-        ifNotFound:notFoundBlock
-        onError:failBlock
-        ignoring:(parenthesisSpecification at:#ignore ifAbsent:#()) "/ #( $' $" '$[' '$]' '${' '$)' )
+	searchForMatchingParenthesisFromLine:startLine col:startCol
+	ifFound:foundBlock
+	ifNotFound:notFoundBlock
+	onError:failBlock
+	ignoring:(parenthesisSpecification at:#ignore ifAbsent:#()) "/ #( $' $" '$[' '$]' '${' '$)' )
 
     "Modified: / 12-04-2007 / 11:24:24 / cg"
 !
 
 searchForMatchingParenthesisFromLine:startLine col:startCol
-                     ifFound:foundBlock
-                  ifNotFound:notFoundBlock
-                     onError:failBlock
-                    ignoring:ignoreSet
+		     ifFound:foundBlock
+		  ifNotFound:notFoundBlock
+		     onError:failBlock
+		    ignoring:ignoreSet
 
     "search for a matching parenthesis; start search with character at startLine/startCol.
      Search for the corresponding character is done forward if its an opening,
@@ -3701,14 +3701,14 @@
      If there is a nesting error, evaluate failBlock."
 
     ^ self
-        searchForMatchingParenthesisFromLine:startLine col:startCol
-        ifFound:foundBlock
-        ifNotFound:notFoundBlock
-        onError:failBlock
-        openingCharacters: (parenthesisSpecification at:#open)  "/ #( $( $[ ${ "$> $<")
-        closingCharacters: (parenthesisSpecification at:#close) "/ #( $) $] $} "$> $<")
-        ignoredCharacters: ignoreSet
-        specialEOLComment: (parenthesisSpecification at:#eolComment ifAbsent:#()) "/
+	searchForMatchingParenthesisFromLine:startLine col:startCol
+	ifFound:foundBlock
+	ifNotFound:notFoundBlock
+	onError:failBlock
+	openingCharacters: (parenthesisSpecification at:#open)  "/ #( $( $[ ${ "$> $<")
+	closingCharacters: (parenthesisSpecification at:#close) "/ #( $) $] $} "$> $<")
+	ignoredCharacters: ignoreSet
+	specialEOLComment: (parenthesisSpecification at:#eolComment ifAbsent:#()) "/
 
 "/    |i direction lineString
 "/     parChar charSet  closingChar
@@ -3858,11 +3858,11 @@
 !
 
 searchForMatchingParenthesisFromLine:startLine col:startCol
-                     ifFound:foundBlock
-                  ifNotFound:notFoundBlock
-                     onError:failBlock
-           openingCharacters:openingCharacters
-           closingCharacters:closingCharacters
+		     ifFound:foundBlock
+		  ifNotFound:notFoundBlock
+		     onError:failBlock
+	   openingCharacters:openingCharacters
+	   closingCharacters:closingCharacters
 
     "search for a matching parenthesis; start search with character at startLine/startCol.
      Search for the corresponding character is done forward if its an opening,
@@ -3871,14 +3871,14 @@
      If there is a nesting error, evaluate failBlock."
 
     ^ self
-        searchForMatchingParenthesisFromLine:startLine col:startCol
-        ifFound:foundBlock
-        ifNotFound:notFoundBlock
-        onError:failBlock
-        openingCharacters: openingCharacters
-        closingCharacters: closingCharacters
-        ignoredCharacters: (parenthesisSpecification at:#ignore ifAbsent:#())
-        specialEOLComment: (parenthesisSpecification at:#eolComment ifAbsent:#()) "/
+	searchForMatchingParenthesisFromLine:startLine col:startCol
+	ifFound:foundBlock
+	ifNotFound:notFoundBlock
+	onError:failBlock
+	openingCharacters: openingCharacters
+	closingCharacters: closingCharacters
+	ignoredCharacters: (parenthesisSpecification at:#ignore ifAbsent:#())
+	specialEOLComment: (parenthesisSpecification at:#eolComment ifAbsent:#()) "/
 
 "/    |i direction lineString
 "/     parChar charSet  closingChar
@@ -4028,13 +4028,13 @@
 !
 
 searchForMatchingParenthesisFromLine:startLine col:startCol
-                     ifFound:foundBlock
-                  ifNotFound:notFoundBlock
-                     onError:failBlock
-           openingCharacters:openingCharacters
-           closingCharacters:closingCharacters
-           ignoredCharacters:ignoreSet
-          specialEOLComment:eolCommentSequence
+		     ifFound:foundBlock
+		  ifNotFound:notFoundBlock
+		     onError:failBlock
+	   openingCharacters:openingCharacters
+	   closingCharacters:closingCharacters
+	   ignoredCharacters:ignoreSet
+	  specialEOLComment:eolCommentSequence
 
     "search for a matching parenthesis; start search with character at startLine/startCol.
      Search for the corresponding character is done forward if its an opening,
@@ -4063,7 +4063,7 @@
     parChar := self characterAtLine:startLine col:startCol.
     i := charSet indexOf:parChar.
     i == 0 ifTrue:[
-        ^ failBlock value   "not a parenthesis"
+	^ failBlock value   "not a parenthesis"
     ].
 
     direction := (i <= openingCharacters size) ifTrue:[#fwd] ifFalse:[#bwd].
@@ -4075,13 +4075,13 @@
     col := startCol.
     line := startLine.
     direction == #fwd ifTrue:[
-        delta := 1.
-        incSet := openingCharacters.
-        decSet := closingCharacters.
+	delta := 1.
+	incSet := openingCharacters.
+	decSet := closingCharacters.
     ] ifFalse:[
-        delta := -1.
-        incSet := closingCharacters.
-        decSet := openingCharacters.
+	delta := -1.
+	incSet := closingCharacters.
+	decSet := openingCharacters.
     ].
     anySet := Set new.
     anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
@@ -4094,101 +4094,101 @@
 
     col := col + delta.
     [nesting ~~ 0] whileTrue:[
-        (lineString notNil
-        and:[lineString includesAny:anySet]) ifTrue:[
-            direction == #fwd ifTrue:[
-                endCol := lineString size.
-            ] ifFalse:[
-                endCol := 1
-            ].
-
-            col to:endCol by:delta do:[:rCol |
-                runCol := rCol.
-
-                cc := lineString at:runCol.
-                runCol < lineString size ifTrue:[
-                    nextCC := lineString at:runCol+1
-                ] ifFalse:[
-                    nextCC := nil
-                ].
-                runCol > 1 ifTrue:[
-                    prevCC := lineString at:runCol-1
-                ] ifFalse:[
-                    prevCC := nil
-                ].
-
-                ign := skip := false.
-
-                "/ check for comments.
-
-                ((cc == eol1 and:[nextCC == eol2])
-                or:[prevCC == $$ ]) ifTrue:[
-                    "/ do nothing
-
-                    skip := true.
-                ] ifFalse:[
-                    ignoreSet do:[:ignore |
-                        ignore == cc ifTrue:[
-                            ign := true
-                        ] ifFalse:[
-                            ignore isString ifTrue:[
-                                cc == (ignore at:2) ifTrue:[
-                                    runCol > 1 ifTrue:[
-                                        (lineString at:(runCol-1)) == (ignore at:1) ifTrue:[
-                                            skip := true
-                                        ]
-                                    ]
-                                ] ifFalse:[
-                                    cc == (ignore at:1) ifTrue:[
-                                        runCol < lineString size ifTrue:[
-                                            (lineString at:(runCol+1)) == (ignore at:2) ifTrue:[
-                                                skip := true
-                                            ]
-                                        ]
-                                    ]
-                                ]
-                            ]
-                        ]
-                    ]
-                ].
-
-                ign ifTrue:[
-                    ignoring := ignoring not
-                ].
-
-                ignoring ifFalse:[
-                    skip ifFalse:[
-                        (incSet includes:cc) ifTrue:[
-                            nesting := nesting + 1
-                        ] ifFalse:[
-                            (decSet includes:cc) ifTrue:[
-                                nesting := nesting - 1
-                            ]
-                        ]
-                    ]
-                ].
-
-                nesting == 0 ifTrue:[
-                    "check if legal"
-                    skip ifFalse:[
-                        cc == closingChar ifFalse:[
-                            ^ failBlock value
-                        ].
-                        ^ foundBlock value:line value:runCol.
-                    ]
-                ]
-            ].
-        ].
-        line := line + delta.
-        (line < 1 or:[line > maxLine]) ifTrue:[
-            ^ failBlock value
-        ].
-        lineString := list at:line.
-        direction == #fwd ifTrue:[
-            col := 1
-        ] ifFalse:[
-            col := lineString size
-        ]
+	(lineString notNil
+	and:[lineString includesAny:anySet]) ifTrue:[
+	    direction == #fwd ifTrue:[
+		endCol := lineString size.
+	    ] ifFalse:[
+		endCol := 1
+	    ].
+
+	    col to:endCol by:delta do:[:rCol |
+		runCol := rCol.
+
+		cc := lineString at:runCol.
+		runCol < lineString size ifTrue:[
+		    nextCC := lineString at:runCol+1
+		] ifFalse:[
+		    nextCC := nil
+		].
+		runCol > 1 ifTrue:[
+		    prevCC := lineString at:runCol-1
+		] ifFalse:[
+		    prevCC := nil
+		].
+
+		ign := skip := false.
+
+		"/ check for comments.
+
+		((cc == eol1 and:[nextCC == eol2])
+		or:[prevCC == $$ ]) ifTrue:[
+		    "/ do nothing
+
+		    skip := true.
+		] ifFalse:[
+		    ignoreSet do:[:ignore |
+			ignore == cc ifTrue:[
+			    ign := true
+			] ifFalse:[
+			    ignore isString ifTrue:[
+				cc == (ignore at:2) ifTrue:[
+				    runCol > 1 ifTrue:[
+					(lineString at:(runCol-1)) == (ignore at:1) ifTrue:[
+					    skip := true
+					]
+				    ]
+				] ifFalse:[
+				    cc == (ignore at:1) ifTrue:[
+					runCol < lineString size ifTrue:[
+					    (lineString at:(runCol+1)) == (ignore at:2) ifTrue:[
+						skip := true
+					    ]
+					]
+				    ]
+				]
+			    ]
+			]
+		    ]
+		].
+
+		ign ifTrue:[
+		    ignoring := ignoring not
+		].
+
+		ignoring ifFalse:[
+		    skip ifFalse:[
+			(incSet includes:cc) ifTrue:[
+			    nesting := nesting + 1
+			] ifFalse:[
+			    (decSet includes:cc) ifTrue:[
+				nesting := nesting - 1
+			    ]
+			]
+		    ]
+		].
+
+		nesting == 0 ifTrue:[
+		    "check if legal"
+		    skip ifFalse:[
+			cc == closingChar ifFalse:[
+			    ^ failBlock value
+			].
+			^ foundBlock value:line value:runCol.
+		    ]
+		]
+	    ].
+	].
+	line := line + delta.
+	(line < 1 or:[line > maxLine]) ifTrue:[
+	    ^ failBlock value
+	].
+	lineString := list at:line.
+	direction == #fwd ifTrue:[
+	    col := 1
+	] ifFalse:[
+	    col := lineString size
+	]
     ].
     ^ notFoundBlock value
 
@@ -4201,55 +4201,55 @@
     |ign match variable|
 
     searchAction notNil ifTrue:[
-        "/ autosearch is cleared whenever there is search with user selection
-        (self hasSelection and:[self hasSearchActionSelection not]) ifTrue: [self clearSearchAction].
+	"/ autosearch is cleared whenever there is search with user selection
+	(self hasSelection and:[self hasSearchActionSelection not]) ifTrue: [self clearSearchAction].
     ].
 
     searchAction notNil ifTrue:[
-        "/ confusing: this is for autosearch of variables (browse variable uses, for example)
-        self searchUsingSearchAction:#forward.
-        ^ self.
+	"/ confusing: this is for autosearch of variables (browse variable uses, for example)
+	self searchUsingSearchAction:#forward.
+	^ self.
     ].
     searchBarActionBlock notNil ifTrue:[
-        searchBarActionBlock value:#forward value:self.
-        ^ self
+	searchBarActionBlock value:#forward value:self.
+	^ self
     ].
     lastSearchWasVariableSearch ifTrue:[
-        variable := self syntaxElementForSelectedVariable.
-        variable notNil ifTrue:[
-            self searchVariableWithSyntaxElement:variable forward:true.
-            ^ self.
-        ].
-        lastSearchWasVariableSearch := false.
+	variable := self syntaxElementForSelectedVariable.
+	variable notNil ifTrue:[
+	    self searchVariableWithSyntaxElement:variable forward:true.
+	    ^ self.
+	].
+	lastSearchWasVariableSearch := false.
     ].
 
     ign := lastSearchIgnoredCase ? LastSearchIgnoredCase ? true.
     match := lastSearchWasMatch ? LastSearchWasMatch ? false.
 
     selectStyle == #wordLeft ifTrue:[
-        "
-         remove the space from the selection
-        "
-        selectionStartCol := selectionStartCol + 1.
-        super redrawLine:selectionStartLine from:selectionStartCol-1 to:selectionStartCol-1.
-        selectStyle := #word.
-        self selectionChanged.
+	"
+	 remove the space from the selection
+	"
+	selectionStartCol := selectionStartCol + 1.
+	super redrawLine:selectionStartLine from:selectionStartCol-1 to:selectionStartCol-1.
+	selectStyle := #word.
+	self selectionChanged.
     ].
     self setSearchPatternWithMatchEscapes: match.
 
     lastSearchPattern isNil ifTrue:[
-        LastSearchPatterns size > 0 ifTrue:[
-            lastSearchPattern := LastSearchPatterns first
-        ]
+	LastSearchPatterns size > 0 ifTrue:[
+	    lastSearchPattern := LastSearchPatterns first
+	]
     ].
 
     lastSearchPattern notNil ifTrue:[
-        self rememberSearchPattern:lastSearchPattern.
-        lastSearchDirection := #forward.
-        self
-            searchFwd:lastSearchPattern
-            ignoreCase:ign
-            match: match
+	self rememberSearchPattern:lastSearchPattern.
+	lastSearchDirection := #forward.
+	self
+	    searchFwd:lastSearchPattern
+	    ignoreCase:ign
+	    match: match
     ]
 
     "Modified: / 08-03-2012 / 14:25:42 / cg"
@@ -4269,9 +4269,9 @@
     "do a forward search"
 
     self
-        searchFwdUsingSpec:(ListView::SearchSpec new
-                                pattern:pattern)
-        ifAbsent:aBlock
+	searchFwdUsingSpec:(ListView::SearchSpec new
+				pattern:pattern)
+	ifAbsent:aBlock
 
     "Modified: / 21-09-2006 / 16:51:28 / cg"
 !
@@ -4280,13 +4280,13 @@
     "do a forward search"
 
     self
-        searchFwdUsingSpec:(ListView::SearchSpec new
-                                pattern:pattern
-                                ignoreCase:ign)
-        ifAbsent:[
-                    self sensor compressKeyPressEventsWithKey:#FindNext.
-                    self showNotFound
-                 ].
+	searchFwdUsingSpec:(ListView::SearchSpec new
+				pattern:pattern
+				ignoreCase:ign)
+	ifAbsent:[
+		    self sensor compressKeyPressEventsWithKey:#FindNext.
+		    self showNotFound
+		 ].
     "/ lastSearchIgnoredCase := ign.
     lastSearchPattern := pattern string
 
@@ -4298,10 +4298,10 @@
     "do a forward search"
 
     self
-        searchFwdUsingSpec:(ListView::SearchSpec new
-                                pattern:pattern
-                                ignoreCase:ign)
-        ifAbsent:aBlock
+	searchFwdUsingSpec:(ListView::SearchSpec new
+				pattern:pattern
+				ignoreCase:ign)
+	ifAbsent:aBlock
 
     "Modified: 13.9.1997 / 01:05:35 / cg"
     "Created: 13.9.1997 / 06:18:27 / cg"
@@ -4311,14 +4311,14 @@
     "do a forward search"
 
     self
-        searchFwdUsingSpec:(ListView::SearchSpec new
-                                pattern:pattern
-                                ignoreCase:ign
-                                match:match)
-        ifAbsent:[
-                    self sensor compressKeyPressEventsWithKey:#FindNext.
-                    self showNotFound
-                 ].
+	searchFwdUsingSpec:(ListView::SearchSpec new
+				pattern:pattern
+				ignoreCase:ign
+				match:match)
+	ifAbsent:[
+		    self sensor compressKeyPressEventsWithKey:#FindNext.
+		    self showNotFound
+		 ].
     "/ lastSearchIgnoredCase := ign.
     "/ lastSearchWasMatch := match.
     lastSearchPattern := pattern string
@@ -4331,11 +4331,11 @@
     "do a forward search"
 
     self
-        searchFwdUsingSpec:(ListView::SearchSpec new
-                                pattern:pattern
-                                ignoreCase:ign
-                                match:match)
-        ifAbsent:aBlock
+	searchFwdUsingSpec:(ListView::SearchSpec new
+				pattern:pattern
+				ignoreCase:ign
+				match:match)
+	ifAbsent:aBlock
 
     "Modified: 13.9.1997 / 01:05:35 / cg"
     "Created: 13.9.1997 / 06:18:27 / cg"
@@ -4345,20 +4345,20 @@
     "do a forward search"
 
     self
-        searchFwdUsingSpec:(ListView::SearchSpec new
-                                pattern:pattern
-                                ignoreCase:ign
-                                match:match)
-        startingAtLine:startLine col:startCol
-        ifAbsent:aBlock
+	searchFwdUsingSpec:(ListView::SearchSpec new
+				pattern:pattern
+				ignoreCase:ign
+				match:match)
+	startingAtLine:startLine col:startCol
+	ifAbsent:aBlock
 !
 
 searchFwdUsingSpec:searchSpec
     "do a forward search"
 
     self
-        searchFwdUsingSpec:searchSpec
-        ifAbsent:[self showNotFound].
+	searchFwdUsingSpec:searchSpec
+	ifAbsent:[self showNotFound].
 
 "/    lastSearchIgnoredCase := false.
     lastSearchPattern := searchSpec pattern string
@@ -4376,9 +4376,9 @@
     startCol := pos x.
 
     self
-        searchFwdUsingSpec:searchSpec
-        startingAtLine:startLine col:startCol
-        ifAbsent:aBlock
+	searchFwdUsingSpec:searchSpec
+	startingAtLine:startLine col:startCol
+	ifAbsent:aBlock
 
     "Modified: 13.9.1997 / 01:05:35 / cg"
     "Created: 13.9.1997 / 06:18:27 / cg"
@@ -4404,32 +4404,32 @@
 
 searchUsingSearchAction:direction
     self
-        searchUsingSearchAction:direction
-        ifAbsent:[
-                    self sensor compressKeyPressEventsWithKey:#FindNext.
-                    self showNotFound
-                 ]
+	searchUsingSearchAction:direction
+	ifAbsent:[
+		    self sensor compressKeyPressEventsWithKey:#FindNext.
+		    self showNotFound
+		 ]
 !
 
 searchUsingSearchAction:direction ifAbsent:notFoundAction
     |pos startLine startCol|
 
     pos :=  direction == #backward
-                ifTrue:[self startPositionForSearchBackward]
-                ifFalse:[self startPositionForSearchForward].
+		ifTrue:[self startPositionForSearchBackward]
+		ifFalse:[self startPositionForSearchForward].
     startLine := pos y.
     startCol := pos x.
 
     searchAction notNil ifTrue:[
-        searchAction
-            value:direction
-            value:startLine
-            value:startCol
-            value:[:line :col | self selectFromLine:line toLine:line]
-            value:notFoundAction.
-        self hasSelection ifTrue: [
-            self changeTypeOfSelectionTo: #searchAction.
-        ].
+	searchAction
+	    value:direction
+	    value:startLine
+	    value:startCol
+	    value:[:line :col | self selectFromLine:line toLine:line]
+	    value:notFoundAction.
+	self hasSelection ifTrue: [
+	    self changeTypeOfSelectionTo: #searchAction.
+	].
     ].
 !
 
@@ -4468,9 +4468,9 @@
 
     sel := self selection.
     sel notNil ifTrue:[
-        searchPattern := sel asString.
-        match ifTrue:[searchPattern := searchPattern withMatchEscapes].
-        self setSearchPattern:searchPattern.
+	searchPattern := sel asString.
+	match ifTrue:[searchPattern := searchPattern withMatchEscapes].
+	self setSearchPattern:searchPattern.
     ]
 
     "Modified: / 6.3.1999 / 23:48:04 / cg"
@@ -4528,11 +4528,11 @@
     |startLine startCol|
 
     selectionStartLine notNil ifTrue:[
-        startLine := selectionStartLine.
-        startCol := selectionStartCol
+	startLine := selectionStartLine.
+	startCol := selectionStartCol
     ] ifFalse:[
-        startLine := 1.
-        startCol := 1
+	startLine := 1.
+	startCol := 1
     ].
 
     ^ startCol @ startLine
@@ -4546,11 +4546,11 @@
     |startLine startCol|
 
     selectionStartLine notNil ifTrue:[
-        startLine := selectionStartLine.
-        startCol := selectionStartCol
+	startLine := selectionStartLine.
+	startCol := selectionStartCol
     ] ifFalse:[
-        startLine := 1.
-        startCol := 1
+	startLine := 1.
+	startCol := 1
     ].
 
     ^ startCol @ startLine
@@ -4746,15 +4746,15 @@
     selectionEndLine   isNil ifTrue:[^ false].
 
     (line between:selectionStartLine and:selectionEndLine) ifFalse:[
-        ^ false
+	^ false
     ].
 
     line == selectionStartLine ifTrue:[
-        aColNr < selectionStartCol ifTrue:[^ false]
+	aColNr < selectionStartCol ifTrue:[^ false]
     ].
 
     line == selectionEndLine ifTrue:[
-        (selectionEndCol ~~ 0 and:[selectionEndCol < aColNr]) ifTrue:[^ false]
+	(selectionEndCol ~~ 0 and:[selectionEndCol < aColNr]) ifTrue:[^ false]
     ].
     ^ true
 !
@@ -4765,15 +4765,15 @@
     |line col|
 
     selectionStartLine notNil ifTrue:[
-        expandingTop == true ifTrue:[
-            line := selectionStartLine.
-            col := selectionStartCol.
-        ] ifFalse:[
-            line := selectionEndLine.
-            col := selectionEndCol.
-        ].
-        self makeLineVisible:line.
-        self makeColVisible:col inLine:line.
+	expandingTop == true ifTrue:[
+	    line := selectionStartLine.
+	    col := selectionStartCol.
+	] ifFalse:[
+	    line := selectionEndLine.
+	    col := selectionEndCol.
+	].
+	self makeLineVisible:line.
+	self makeColVisible:col inLine:line.
     ]
 
     "Modified: 6.3.1996 / 13:53:45 / cg"
@@ -4913,7 +4913,7 @@
 
     selectLine := self lineAtY:y. "/ self visibleLineToListLine:(self visibleLineOfY:y).
     selectLine notNil ifTrue:[
-        self selectLine:selectLine
+	self selectLine:selectLine
     ]
 !
 
@@ -4930,12 +4930,12 @@
     "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
-        ]
+	wordAtLine:line col:col do:[
+	    :beginLine :beginCol :endLine :endCol :style |
+
+	    self selectFromLine:beginLine col:beginCol toLine:endLine col:endCol.
+	    selectStyle := style
+	]
 
     "Modified: 18.3.1996 / 17:30:38 / cg"
 !
@@ -4949,8 +4949,8 @@
     selectVisibleLine := self visibleLineOfY:y.
     selectLine := self visibleLineToListLine:selectVisibleLine.
     selectLine notNil ifTrue:[
-        selectCol := self colOfX:x inVisibleLine:selectVisibleLine.
-        self selectWordAtLine:selectLine col:selectCol
+	selectCol := self colOfX:x inVisibleLine:selectVisibleLine.
+	self selectWordAtLine:selectLine col:selectCol
     ]
 
     "Modified: / 8.9.1998 / 21:22:46 / cg"
@@ -5022,9 +5022,9 @@
     "can be redefined for notification or special actions"
 
     device notNil ifTrue:[
-        "On X11, be nice and set the PRIMARY selection.
-         (#setPrimaryText:ownerView: is void in DeviceWorkstation)"
-        device setPrimaryText: self selectionAsString ownerView: self.
+	"On X11, be nice and set the PRIMARY selection.
+	 (#setPrimaryText:ownerView: is void in DeviceWorkstation)"
+	device setPrimaryText: self selectionAsString ownerView: self.
     ].
 
     "Created: / 17-04-2012 / 20:59:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -5047,34 +5047,34 @@
     |startLine endLine startVisLine endVisLine|
 
     selectionStartLine notNil ifTrue:[
-        startLine := selectionStartLine.
-        endLine := selectionEndLine.
-
-        self unselectWithoutRedraw.
-
-        "/ if the 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
-
-        (startLine == endLine) ifTrue:[
-            super redrawVisibleLine:startVisLine from:selectionStartCol to:selectionEndCol
-        ] ifFalse:[
-            self redrawFromVisibleLine:startVisLine to:endVisLine
-        ].
+	startLine := selectionStartLine.
+	endLine := selectionEndLine.
+
+	self unselectWithoutRedraw.
+
+	"/ if the 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
+
+	(startLine == endLine) ifTrue:[
+	    super redrawVisibleLine:startVisLine from:selectionStartCol to:selectionEndCol
+	] ifFalse:[
+	    self redrawFromVisibleLine:startVisLine to:endVisLine
+	].
     ].
     selectStyle := nil