oops: licenceBox dependency was missing;
authorsr
Fri, 07 Aug 2009 12:50:41 +0200
changeset 3728 8858b3571313
parent 3727 03a3787770ed
child 3729 6f6cfc8bb8cf
oops: licenceBox dependency was missing; renderer renamed to listRenderer in ListModelView (instvar conflict with inherited)
HierarchicalListView.st
ListModelView.st
Make.proto
SelectionInListModelView.st
bc.mak
--- a/HierarchicalListView.st	Tue Aug 04 14:15:20 2009 +0200
+++ b/HierarchicalListView.st	Fri Aug 07 12:50:41 2009 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1999 by eXept Software AG
-              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
@@ -28,7 +28,7 @@
 copyright
 "
  COPYRIGHT (c) 1999 by eXept Software AG
-              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
@@ -49,61 +49,61 @@
     SelectionInTreeView, which generates a list internally).
 
     [Instance variables:]
-        textStartLeft       <Integer>              inset between icon and text 
-        imageInset          <Integer>              inset between left side and icon
-        imageWidth          <Integer>              width of widest icon
-        minLineHeight       <Integer>              minimum required line height
-                                                   including open/close indication ...
-        indicatorWidth      <Integer>              max. width  of indicator
-        indicatorHeight     <Integer>              max. height of indicator
+	textStartLeft       <Integer>              inset between icon and text
+	imageInset          <Integer>              inset between left side and icon
+	imageWidth          <Integer>              width of widest icon
+	minLineHeight       <Integer>              minimum required line height
+						   including open/close indication ...
+	indicatorWidth      <Integer>              max. width  of indicator
+	indicatorHeight     <Integer>              max. height of indicator
 
-        lineMask            <Form>                 line mask
-        lineColor           <Color>                line color
-        showRoot            <Boolean>              root element is shown or hidden
-                                                   derives from the hierachical list.
-        showLines           <Boolean>              show or hide lines
-        showIndicators      <Boolean>              show or hide indicators
-        useDefaultIcons     <Boolean>              use the default icons if no icon
-                                                   for an item is specified
-        icons               <IdentityDictionary>   list of registered icons;
-                                                   identifier := <key> value := <icon>
-        showLeftIndicators  <Boolean>              show or hide indicator for most left items
-        indicatorAction     <Block>                action evaluated if indicator is pressed (0/1/2 arguments)
-        openIndicator       <Icon, Image or Form>  expanded indicator      
-        closeIndicator      <Icon, Image or Form>  collapsed indicator
+	lineMask            <Form>                 line mask
+	lineColor           <Color>                line color
+	showRoot            <Boolean>              root element is shown or hidden
+						   derives from the hierachical list.
+	showLines           <Boolean>              show or hide lines
+	showIndicators      <Boolean>              show or hide indicators
+	useDefaultIcons     <Boolean>              use the default icons if no icon
+						   for an item is specified
+	icons               <IdentityDictionary>   list of registered icons;
+						   identifier := <key> value := <icon>
+	showLeftIndicators  <Boolean>              show or hide indicator for most left items
+	indicatorAction     <Block>                action evaluated if indicator is pressed (0/1/2 arguments)
+	openIndicator       <Icon, Image or Form>  expanded indicator
+	closeIndicator      <Icon, Image or Form>  collapsed indicator
 
-        alignTextRight      <Boolean>              enable disable of align the text right
-                                                   icon            text
-                                                        icon       text of child
-                                                   should be set after creation of the widget!!
-        alignTextRightX     <Integer>              left x position of aligned right text
-        maxWidthOfText      <Integer>              keeps the maximum width of a text label
+	alignTextRight      <Boolean>              enable disable of align the text right
+						   icon            text
+							icon       text of child
+						   should be set after creation of the widget!!
+	alignTextRightX     <Integer>              left x position of aligned right text
+	maxWidthOfText      <Integer>              keeps the maximum width of a text label
 
-        levelOfLastItem     <Integer>              keeps the level of the last item;
-                                                   in case of a delete last items from list
-                                                   we know were to redraw lines from
+	levelOfLastItem     <Integer>              keeps the level of the last item;
+						   in case of a delete last items from list
+						   we know were to redraw lines from
 
-        autoScrollHorizontal <Boolean>             true, than automatically scroll horizontal upto
-                                                   the text label of the current selected line.
+	autoScrollHorizontal <Boolean>             true, than automatically scroll horizontal upto
+						   the text label of the current selected line.
 
-        expandOnSelect      <Boolean>              true, than the item selected by a buttonPress
-                                                   event will be immediately expanded.
+	expandOnSelect      <Boolean>              true, than the item selected by a buttonPress
+						   event will be immediately expanded.
 
     [author:]
-        Claus Atzkern
+	Claus Atzkern
 
     [see also:]
-        ListModelView
-        SelectionInListModelView
-        HierarchicalList
-        HierarchicalItem
+	ListModelView
+	SelectionInListModelView
+	HierarchicalList
+	HierarchicalItem
 "
 !
 
 examples
 "
     show a hierarchical list
-                                                                        [exBegin]
+									[exBegin]
     |top sel list item|
 
     list := HierarchicalList new.
@@ -115,7 +115,7 @@
 
     top := StandardSystemView new; extent:300@300.
     sel := ScrollableView for:HierarchicalListView miniScrollerH:true
-                       origin:0.0@0.0 corner:1.0@1.0 in:top.
+		       origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     sel list:list.
     sel multipleSelectOk:true.
@@ -124,13 +124,13 @@
     sel   indicatorAction:[:i| (list at:i) toggleExpand ].
 
     top open.
-                                                                        [exEnd]
+									[exEnd]
 
 
     show a hierarchical list; open an editor on reselect a
     line with label is a string.
 
-                                                                        [exBegin]
+									[exBegin]
     |top sel list item|
 
     list := HierarchicalList new.
@@ -142,24 +142,24 @@
 
     top := StandardSystemView new; extent:300@300.
     sel := ScrollableView for:HierarchicalListView miniScrollerH:true
-                       origin:0.0@0.0 corner:1.0@1.0 in:top.
+		       origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     sel list:list.
 
     sel openEditorAction:[:ln :aGC| |field item|
-        item  := list at:ln.
+	item  := list at:ln.
 
-        item label isString ifFalse:[
-            field := nil
-        ] ifTrue:[
-            field := EditField new.
-            field level:0.
-            field acceptOnLostFocus:true.
-            field acceptAction:[:x| item label:(field contents) ].
-            field font:(aGC font).
-            field contents:(item label).
-        ].
-        field
+	item label isString ifFalse:[
+	    field := nil
+	] ifTrue:[
+	    field := EditField new.
+	    field level:0.
+	    field acceptOnLostFocus:true.
+	    field acceptAction:[:x| item label:(field contents) ].
+	    field font:(aGC font).
+	    field contents:(item label).
+	].
+	field
     ].
 
     sel multipleSelectOk:true.
@@ -168,9 +168,9 @@
     sel   indicatorAction:[:i| (list at:i) toggleExpand ].
 
     top open.
-                                                                        [exEnd]
+									[exEnd]
 
-                                                                        [exBegin]
+									[exBegin]
     |top sel list item|
 
     list := HierarchicalList new.
@@ -182,7 +182,7 @@
 
     top := StandardSystemView new; extent:300@300.
     sel := ScrollableView for:HierarchicalListView miniScrollerH:true
-                       origin:0.0@0.0 corner:1.0@1.0 in:top.
+		       origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     sel openIndicator:(ToolbarIconLibrary down22x22Icon).
     sel closeIndicator:(ToolbarIconLibrary downRight22x22Icon).
@@ -195,7 +195,7 @@
     sel   indicatorAction:[:i| (list at:i) toggleExpand ].
 
     top open.
-                                                                        [exBegin]
+									[exBegin]
 
 
 "
@@ -213,7 +213,7 @@
 
     top := StandardSystemView new; extent:300@300.
     sel := ScrollableView for:HierarchicalListView miniScrollerH:true
-                       origin:0.0@0.0 corner:1.0@1.0 in:top.
+		       origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     sel useDefaultIcons:false.
     sel list:list.
@@ -244,8 +244,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'HierarchicalListView class closeIndicator'
-        ifAbsentPut:[(Depth2Image new) width: 9; height: 9; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUU@Z*)@Z")@Z")@X@I-Z")@Z")KZ*)@UUU;') ; colorMapFromArray:#[0 0 0 128 128 128 255 255 255]; yourself]
+	constantNamed:#'HierarchicalListView class closeIndicator'
+	ifAbsentPut:[(Depth2Image new) width: 9; height: 9; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUU@Z*)@Z")@Z")@X@I-Z")@Z")KZ*)@UUU;') ; colorMapFromArray:#[0 0 0 128 128 128 255 255 255]; yourself]
 !
 
 collapsedIcon
@@ -264,8 +264,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'HierarchicalListView class collapsedIcon'
-        ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@UP@@@@@@@@EUUUPAUUUT@UUUU@EUUUPAUUUT@UUUU@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@O@A>@O?<??3??O?<??3??O?<??0@@@@@@@@b') ; yourself); yourself]
+	constantNamed:#'HierarchicalListView class collapsedIcon'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@UP@@@@@@@@EUUUPAUUUT@UUUU@EUUUPAUUUT@UUUU@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@O@A>@O?<??3??O?<??3??O?<??0@@@@@@@@b') ; yourself); yourself]
 !
 
 emptyIcon
@@ -284,8 +284,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'HierarchicalListView class emptyIcon'
-        ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@EUTP@AUUE@@UUP@@EUUU@AUUUP@UUUT@EUUU@AUUUP@UUUT@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@O?@?>C?<O?8??#?>O?8??#?>O?8?? @@@@@@@@b') ; yourself); yourself]
+	constantNamed:#'HierarchicalListView class emptyIcon'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@EUTP@AUUE@@UUP@@EUUU@AUUUP@UUUT@EUUU@AUUUP@UUUT@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@O?@?>C?<O?8??#?>O?8??#?>O?8?? @@@@@@@@b') ; yourself); yourself]
 !
 
 expandedIcon
@@ -304,8 +304,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'HierarchicalListView class expandedIcon'
-        ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@UP@@@UU@@@EUUUPA@@@@@R*** B***(@***(@****@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 179 179 179 255 255 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@O@A>@O?<??3???????;??/?<??0@@@@@@@@b') ; yourself); yourself]
+	constantNamed:#'HierarchicalListView class expandedIcon'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@UP@@@UU@@@EUUUPA@@@@@R*** B***(@***(@****@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 179 179 179 255 255 0]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@O@A>@O?<??3???????;??/?<??0@@@@@@@@b') ; yourself); yourself]
 !
 
 openIndicator
@@ -324,8 +324,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'HierarchicalListView class openIndicator'
-        ifAbsentPut:[(Depth2Image new) width: 9; height: 9; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUU@Z*)@Z*)(Z*)HX@I@Z*)@Z*)@Z*)@UUU.') ; colorMapFromArray:#[0 0 0 128 128 128 255 255 255]; yourself]
+	constantNamed:#'HierarchicalListView class openIndicator'
+	ifAbsentPut:[(Depth2Image new) width: 9; height: 9; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUU@Z*)@Z*)(Z*)HX@I@Z*)@Z*)@Z*)@UUU.') ; colorMapFromArray:#[0 0 0 128 128 128 255 255 255]; yourself]
 ! !
 
 !HierarchicalListView methodsFor:'accessing'!
@@ -337,20 +337,20 @@
     |root|
 
     (aFont isNil or:[aFont = font]) ifFalse:[
-        root := self root.
-        root notNil ifTrue:[ root fontChanged ].
-        super font:aFont
+	root := self root.
+	root notNil ifTrue:[ root fontChanged ].
+	super font:aFont
     ].
 !
 
 list:aList
     aList notNil ifTrue:[
-        aList isHierarchicalItem ifTrue:[
-            self list root:aList.
-            aList expand.
-            ^ self
-        ].
-        showRoot := aList showRoot.
+	aList isHierarchicalItem ifTrue:[
+	    self list root:aList.
+	    aList expand.
+	    ^ self
+	].
+	showRoot := aList showRoot.
     ].
     super list:aList
 !
@@ -374,11 +374,11 @@
 !HierarchicalListView methodsFor:'accessing-behavior'!
 
 autoScrollHorizontal
-    "returns true if automatic horizontal scrolling 
+    "returns true if automatic horizontal scrolling
      (upto the text label of the selected line)
      is allowed (the default is as specified in the styleSheet)."
 
-    ^ autoScrollHorizontal == true 
+    ^ autoScrollHorizontal == true
 !
 
 autoScrollHorizontal:aBoolean
@@ -414,12 +414,12 @@
     "set the color of the horizontal and vertical lines
     "
     (aColor notNil and:[aColor ~= lineColor]) ifTrue:[
-        lineColor := aColor.
+	lineColor := aColor.
 
-        shown ifTrue:[
-            lineColor := lineColor onDevice:device.
-            showLines ifTrue:[ self invalidate ]
-        ]
+	shown ifTrue:[
+	    lineColor := lineColor onDevice:device.
+	    showLines ifTrue:[ self invalidate ]
+	]
     ].
 ! !
 
@@ -447,35 +447,35 @@
     "set the minimum used text inset, if text is aligned right.
     "
     aNumber > 0 ifTrue:[
-        alignTextRightX := aNumber.
+	alignTextRightX := aNumber.
 
-        (alignTextRight and:[widthOfContents notNil]) ifTrue:[
-            widthOfContents := alignTextRightX + maxWidthOfText.
+	(alignTextRight and:[widthOfContents notNil]) ifTrue:[
+	    widthOfContents := alignTextRightX + maxWidthOfText.
 
-            shown ifTrue:[
-                self invalidate.
-                self contentsChanged.
-            ]
-        ]
+	    shown ifTrue:[
+		self invalidate.
+		self contentsChanged.
+	    ]
+	]
     ].
 !
 
 closeIndicator:anIconOrNil
     closeIndicator ~= anIconOrNil ifTrue:[
-        closeIndicator := self imageOnMyDevice:anIconOrNil.
-        self indicatorIconChanged.
+	closeIndicator := self imageOnMyDevice:anIconOrNil.
+	self indicatorIconChanged.
     ].
 !
 
 iconAlignment:aSymbol
     "alignment of the icons
-        #left       align icons left
-        #right      align icons right
-        #center     align icons center between left and right
+	#left       align icons left
+	#right      align icons right
+	#center     align icons center between left and right
     "
     aSymbol ~~ iconAlignment ifTrue:[
-        iconAlignment := aSymbol.
-        self invalidate.
+	iconAlignment := aSymbol.
+	self invalidate.
     ].
 !
 
@@ -493,7 +493,7 @@
     icon isNil ifTrue:[^ nil].
 
     realized ifTrue:[
-        icon := self imageOnMyDevice:icon
+	icon := self imageOnMyDevice:icon
     ].
     icons at:aKey put:icon.
     ^ icon
@@ -505,8 +505,8 @@
 
 openIndicator:anIconOrNil
     openIndicator ~= anIconOrNil ifTrue:[
-        openIndicator := self imageOnMyDevice:anIconOrNil.
-        self indicatorIconChanged.
+	openIndicator := self imageOnMyDevice:anIconOrNil.
+	self indicatorIconChanged.
     ].
 !
 
@@ -516,15 +516,15 @@
     |image|
 
     (aDictionary isEmptyOrNil) ifTrue:[
-        ^ self
+	^ self
     ].
 
     aDictionary keysAndValuesDo:[:aKey :anImage|
-        (image := self imageOnMyDevice:anImage) notNil ifTrue:[
-            icons at:aKey put:image
-        ] ifFalse:[
-            icons removeKey:aKey ifAbsent:nil
-        ]
+	(image := self imageOnMyDevice:anImage) notNil ifTrue:[
+	    icons at:aKey put:image
+	] ifFalse:[
+	    icons removeKey:aKey ifAbsent:nil
+	]
     ]
 !
 
@@ -538,8 +538,8 @@
     "true if indicators are shown
     "
     showIndicators ~~ aBoolean ifTrue:[
-        showIndicators := aBoolean.
-        self invalidate.
+	showIndicators := aBoolean.
+	self invalidate.
     ].
 !
 
@@ -558,8 +558,8 @@
     aBoolean == showLeftIndicators ifTrue:[ ^ self ].
 
     (widthOfContents isNil or:[self size == 0]) ifTrue:[
-        showLeftIndicators := aBoolean.
-        ^ self
+	showLeftIndicators := aBoolean.
+	^ self
     ].
 
     oldInset := self xVisibleOfIconAtLevel:3.
@@ -567,13 +567,13 @@
     newInset := self xVisibleOfIconAtLevel:3.
 
     newInset ~~ oldInset ifTrue:[
-        widthOfContents := widthOfContents + (newInset - oldInset).
+	widthOfContents := widthOfContents + (newInset - oldInset).
     ].
 
     self invalidate.
 
     newInset ~~ oldInset ifTrue:[
-        self contentsChanged
+	self contentsChanged
     ].
 !
 
@@ -587,8 +587,8 @@
     "show or hide lines
     "
     aBoolean ~~ showLines ifTrue:[
-        showLines := aBoolean.
-        self invalidate.
+	showLines := aBoolean.
+	self invalidate.
     ].
 !
 
@@ -602,9 +602,9 @@
     "true if the root is shown
     "
     showRoot ~~ aBoolean ifTrue:[
-        showRoot := aBoolean.
-        self list showRoot:showRoot.
-        self invalidate
+	showRoot := aBoolean.
+	self list showRoot:showRoot.
+	self invalidate
     ].
 !
 
@@ -620,8 +620,8 @@
      ** default: true
     "
     useDefaultIcons ~~ aBoolean ifTrue:[
-        useDefaultIcons := aBoolean.
-        self invalidate.
+	useDefaultIcons := aBoolean.
+	self invalidate.
     ]
 ! !
 
@@ -632,9 +632,9 @@
      if indicators are shown a default action is performed (toggle expand item).
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     index
-        -  2 argument     index, self
+	- no argument
+	-  1 argument     index
+	-  2 argument     index, self
     "
     ^ indicatorAction
 !
@@ -644,9 +644,9 @@
      if indicators are shown a default action is performed (toggle expand item).
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     index
-        -  2 argument     index, self
+	- no argument
+	-  1 argument     index
+	-  2 argument     index, self
     "
     indicatorAction := anAction.
 ! !
@@ -659,21 +659,21 @@
     w := h := 9.
 
     openIndicator notNil ifTrue:[
-        w := w max:(openIndicator width).
-        h := h max:(openIndicator height).
+	w := w max:(openIndicator width).
+	h := h max:(openIndicator height).
     ].
     closeIndicator notNil ifTrue:[
-        w := w max:(closeIndicator width).
-        h := h max:(closeIndicator height).
+	w := w max:(closeIndicator width).
+	h := h max:(closeIndicator height).
     ].
 
     (w == indicatorWidth and:[h == indicatorHeight]) ifTrue:[
-        self invalidate.
+	self invalidate.
     ] ifFalse:[
-        indicatorWidth  := w.
-        indicatorHeight := h.
+	indicatorWidth  := w.
+	indicatorHeight := h.
 
-        self lostSynchronisation.   "/ must recompute all
+	self lostSynchronisation.   "/ must recompute all
     ].
 !
 
@@ -694,26 +694,26 @@
     expanded := item isExpanded.
 
     indicatorAction notNil ifTrue:[
-        indicatorAction valueWithOptionalArgument:aLnNr and:self.
+	indicatorAction valueWithOptionalArgument:aLnNr and:self.
     ] ifFalse:[
-        |sensor|
+	|sensor|
 
-        sensor := self sensor.
-        (sensor ctrlDown or:[sensor shiftDown]) ifTrue:[
-            item recursiveToggleExpand
-        ] ifFalse:[
-            item toggleExpand
-        ].
+	sensor := self sensor.
+	(sensor ctrlDown or:[sensor shiftDown]) ifTrue:[
+	    item recursiveToggleExpand
+	] ifFalse:[
+	    item toggleExpand
+	].
     ].
 
     (expanded or:[item isExpanded not]) ifTrue:[^ self].
 
     (self yVisibleOfLine:aLnNr+1) > self height ifTrue:[
-        dl := (self yVisibleOfLine:aLnNr+1) - (self yVisibleOfLine:aLnNr).
-        self scrollTo:(viewOrigin x @ (viewOrigin y + dl)).
+	dl := (self yVisibleOfLine:aLnNr+1) - (self yVisibleOfLine:aLnNr).
+	self scrollTo:(viewOrigin x @ (viewOrigin y + dl)).
     ].
 
-"/    numChildren := item numberOfVisibleChildren.      
+"/    numChildren := item numberOfVisibleChildren.
 "/    numChildren == 0 ifTrue:[
 "/        ^ self
 "/    ].
@@ -751,38 +751,38 @@
     item isNil ifTrue:[^ self].
 
     (arg == #icon or:[arg == #hierarchy]) ifFalse:[
-        super lineChangedAt:aLnNr with:arg.
+	super lineChangedAt:aLnNr with:arg.
 
-        (arg ~~ #redraw and:[widthOfContents notNil]) ifTrue:[
-            x0 := (self xVisibleOfTextAtLevel:(item level))
-                + (renderer widthFor:item)
-                + (viewOrigin x).
+	(arg ~~ #redraw and:[widthOfContents notNil]) ifTrue:[
+	    x0 := (self xVisibleOfTextAtLevel:(item level))
+		+ (listRenderer widthFor:item)
+		+ (viewOrigin x).
 
-            x0 > widthOfContents ifTrue:[
-                widthOfContents := x0.
-                self contentsChanged.
-            ]
-        ].
-        ^ self
+	    x0 > widthOfContents ifTrue:[
+		widthOfContents := x0.
+		self contentsChanged.
+	    ]
+	].
+	^ self
     ].
     level := item level.
 
     (alignTextRight and:[arg == #hierarchy]) ifTrue:[
-        "/ must test whether alignTextRightX is enough
-        (item isExpanded and:[item hasChildren]) ifTrue:[        
-            x0 := self xVisibleOfIconAtLevel:(level + 2).
+	"/ must test whether alignTextRightX is enough
+	(item isExpanded and:[item hasChildren]) ifTrue:[
+	    x0 := self xVisibleOfIconAtLevel:(level + 2).
 
-            alignTextRightX < x0 ifTrue:[
-                alignTextRightX := x0.
-                self invalidate.
+	    alignTextRightX < x0 ifTrue:[
+		alignTextRightX := x0.
+		self invalidate.
 
-                widthOfContents notNil ifTrue:[
-                    widthOfContents := alignTextRightX + maxWidthOfText.
-                    self contentsChanged.
-                ].
-                ^ self.
-            ]
-        ]
+		widthOfContents notNil ifTrue:[
+		    widthOfContents := alignTextRightX + maxWidthOfText.
+		    self contentsChanged.
+		].
+		^ self.
+	    ]
+	]
     ].
     shown ifFalse:[^ self].
 
@@ -800,8 +800,8 @@
     x1 := x1 min:(width - margin).
 
     x0 < x1 ifTrue:[
-        self invalidate:(Rectangle left:x0 top:y0 width:(x1 - x0) height:(y1 - y0)) 
-              repairNow:false.
+	self invalidate:(Rectangle left:x0 top:y0 width:(x1 - x0) height:(y1 - y0))
+	      repairNow:false.
     ].
 !
 
@@ -822,30 +822,30 @@
      and:[(item := self at:firstAddedIndex ifAbsent:nil) notNil
      and:[(level := item level) > 1]]]]]
     ) ifFalse:[
-        ^ self.
+	^ self.
     ].
     xLft := self xVisibleOfVerticalLineAt:level.
 
     (xLft > margin and:[xLft < (width - margin)]) ifFalse:[
-        ^ self
+	^ self
     ].
     start := firstAddedIndex - 1.
 
     start to:1 by:-1 do:[:i| |el|
-        el := self at:i.
+	el := self at:i.
 
-        el level <= level ifTrue:[
-            i == start ifTrue:[^ self].
+	el level <= level ifTrue:[
+	    i == start ifTrue:[^ self].
 
-            yTop := (self yVisibleOfLine:i + 1) max:margin.
-            maxY := height - margin.
+	    yTop := (self yVisibleOfLine:i + 1) max:margin.
+	    maxY := height - margin.
 
-            yTop < maxY ifTrue:[
-                yBot := (self yVisibleOfLine:firstAddedIndex) - 1 min:maxY.
-                self invalidate:(Rectangle left:xLft top:yTop width:2 height:(yBot - yTop))
-            ].
-            ^ self
-        ]
+	    yTop < maxY ifTrue:[
+		yBot := (self yVisibleOfLine:firstAddedIndex) - 1 min:maxY.
+		self invalidate:(Rectangle left:xLft top:yTop width:2 height:(yBot - yTop))
+	    ].
+	    ^ self
+	]
     ].
 !
 
@@ -859,15 +859,15 @@
     searchLevel := levelOfLastItem.
 
     listSize == 0 ifTrue:[ levelOfLastItem := 1 ]
-                 ifFalse:[ levelOfLastItem := self last level ].
+		 ifFalse:[ levelOfLastItem := self last level ].
 
     (shown and:[showLines and:[listSize ~~ 0 and:[aStart > listSize]]]) ifTrue:[
-        index := self findLast:[:el| el level <= searchLevel ].
+	index := self findLast:[:el| el level <= searchLevel ].
 
-        (index ~~ 0 and:[index < listSize]) ifTrue:[
-            y0 := (self yVisibleOfLine:index) max:margin.
-            self invalidateX:0 y:y0 width:width height:(height - margin - y0).
-        ]
+	(index ~~ 0 and:[index < listSize]) ifTrue:[
+	    y0 := (self yVisibleOfLine:index) max:margin.
+	    self invalidateX:0 y:y0 width:width height:(height - margin - y0).
+	]
     ].
     ^ super listChangedRemove:aStart toIndex:aStop
 !
@@ -880,8 +880,8 @@
     newState := self list showRoot.
 
     showRoot ~~ newState ifTrue:[
-        showRoot := newState.
-        self invalidate.
+	showRoot := newState.
+	self invalidate.
     ].
     super updateFromList:what with:aPara.
 ! !
@@ -898,74 +898,74 @@
     xR := xL + w.
 
     showIndicators ifTrue:[
-        offIndcY := indicatorWidth // 2.
+	offIndcY := indicatorWidth // 2.
     ].
 
     showLines ifTrue:[
-        self drawLinesFrom:start to:stop x:xL y:yT toX:xR
+	self drawLinesFrom:start to:stop x:xL y:yT toX:xR
     ].
     prevParent := #NIL.         "/ to force a recompute
     yBot       := yT.
     showIndc   := false.
 
     start to:stop do:[:anIndex|
-        (item := self at:anIndex ifAbsent:nil) isNil ifTrue:[
-            ^ self      "/ list changed
-        ].
-        yTop   := yBot.
-        yBot   := self yVisibleOfLine:(anIndex + 1).
-        height := yBot - yTop.
-        yCtr   := yTop + (height // 2).
+	(item := self at:anIndex ifAbsent:nil) isNil ifTrue:[
+	    ^ self      "/ list changed
+	].
+	yTop   := yBot.
+	yBot   := self yVisibleOfLine:(anIndex + 1).
+	height := yBot - yTop.
+	yCtr   := yTop + (height // 2).
 
-        item parent ~~ prevParent ifTrue:[
-            prevParent  := item parent.
-            level       := item level.
-            xIcon       := self xVisibleOfIconAtLevel:level.
-            xText       := self xVisibleOfTextAtLevel:level.
-            showText    := (xText < xR).
-            showIcon    := (xIcon < xR and:[xText > xL]).
+	item parent ~~ prevParent ifTrue:[
+	    prevParent  := item parent.
+	    level       := item level.
+	    xIcon       := self xVisibleOfIconAtLevel:level.
+	    xText       := self xVisibleOfTextAtLevel:level.
+	    showText    := (xText < xR).
+	    showIcon    := (xIcon < xR and:[xText > xL]).
 
-            showIndicators ifTrue:[
-                xIndc  := self xVisibleOfIndicatorAtLevel:level.
-                showIndc := (xIcon > xL and:[xIndc < xR]).
+	    showIndicators ifTrue:[
+		xIndc  := self xVisibleOfIndicatorAtLevel:level.
+		showIndc := (xIcon > xL and:[xIndc < xR]).
 
-                showIndc ifTrue:[
-                    showIndc := prevParent notNil or:[showLeftIndicators]
-                ]
-            ]
-        ].
+		showIndc ifTrue:[
+		    showIndc := prevParent notNil or:[showLeftIndicators]
+		]
+	    ]
+	].
 
-        (showIcon and:[(icon := self validateDrawableIconFor:item) notNil]) ifTrue:[
-            icnWdt := icon width.
+	(showIcon and:[(icon := self validateDrawableIconFor:item) notNil]) ifTrue:[
+	    icnWdt := icon width.
 
-            (xIcon + icnWdt) > xL ifTrue:[
-                iconAlignment == #left ifTrue:[
-                    x := xIcon.
-                ] ifFalse:[
-                    x := xText - textStartLeft.
+	    (xIcon + icnWdt) > xL ifTrue:[
+		iconAlignment == #left ifTrue:[
+		    x := xIcon.
+		] ifFalse:[
+		    x := xText - textStartLeft.
 
-                    iconAlignment == #center ifTrue:[
-                        x := (x + xIcon - icnWdt) // 2.
-                    ] ifFalse:[
-                        x := x - icnWdt.
-                    ].
-                ].
-                yIcon := yCtr - (icon height // 2).
-                item displayIcon:icon atX:x y:yIcon on:self.
-            ]
-        ].
+		    iconAlignment == #center ifTrue:[
+			x := (x + xIcon - icnWdt) // 2.
+		    ] ifFalse:[
+			x := x - icnWdt.
+		    ].
+		].
+		yIcon := yCtr - (icon height // 2).
+		item displayIcon:icon atX:x y:yIcon on:self.
+	    ]
+	].
 
-        showText ifTrue:[
-            self drawLabelAt:anIndex x:xText y:yTop h:height
-        ].
-        (showIndc and:[item hasIndicator]) ifTrue:[
-            item isExpanded ifTrue:[icon := openIndicator ]
-                           ifFalse:[icon := closeIndicator].
+	showText ifTrue:[
+	    self drawLabelAt:anIndex x:xText y:yTop h:height
+	].
+	(showIndc and:[item hasIndicator]) ifTrue:[
+	    item isExpanded ifTrue:[icon := openIndicator ]
+			   ifFalse:[icon := closeIndicator].
 
-            icon notNil ifTrue:[
-                icon displayOn:self x:xIndc y:(yCtr - offIndcY).
-            ].
-        ].
+	    icon notNil ifTrue:[
+		icon displayOn:self x:xIndc y:(yCtr - offIndcY).
+	    ].
+	].
     ].
 
     "Modified: / 23-06-2006 / 12:49:26 / fm"
@@ -1004,119 +1004,119 @@
     minVertLevel  := 2.
 
     showLeftIndicators ifTrue:[
-        showLeftIdc := showIndicators.
-        showRoot ifFalse:[ minVertLevel := 3 ]
+	showLeftIdc := showIndicators.
+	showRoot ifFalse:[ minVertLevel := 3 ]
     ] ifFalse:[
-        showLeftIdc := false.
+	showLeftIdc := false.
     ].
 
     showRoot ifFalse:[ minHorzLevel := 2 ]
-              ifTrue:[ minHorzLevel := 1 ].
+	      ifTrue:[ minHorzLevel := 1 ].
 
     showLeftIdc ifFalse:[
-        minHorzLevel := minHorzLevel + 1.
+	minHorzLevel := minHorzLevel + 1.
     ].
 
     yBot  := begHLnY := runHLnY := yT.
     level := 1.
 
     start to:stop do:[:anIndex|
-        (item := self at:anIndex ifAbsent:nil) isNil ifTrue:[
-            ^ self mask:nil     "/ list changed
-        ].
-        yTop := yBot.
-        yBot := self yVisibleOfLine:(anIndex + 1).
-        yCtr := yTop + (yBot - yTop // 2).
+	(item := self at:anIndex ifAbsent:nil) isNil ifTrue:[
+	    ^ self mask:nil     "/ list changed
+	].
+	yTop := yBot.
+	yBot := self yVisibleOfLine:(anIndex + 1).
+	yCtr := yTop + (yBot - yTop // 2).
 
-        item parent ~~ parent ifTrue:[
-            anIndex == 1 ifTrue:[ begHLnY := runHLnY := yCtr ].
-            parent := item parent.
+	item parent ~~ parent ifTrue:[
+	    anIndex == 1 ifTrue:[ begHLnY := runHLnY := yCtr ].
+	    parent := item parent.
 
-            prevItem == parent ifTrue:[
-                level   := level + 1.
-                lftVrtX := rgtVrtX.
-            ] ifFalse:[
-                level   := item level.
-                lftVrtX := self xVisibleOfVerticalLineAt:level.
-            ].
-            showVLines := (level >= minVertLevel and:[lftVrtX >= xL]).
-            rgtVrtX    := self xVisibleOfVerticalLineAt:level + 1.
+	    prevItem == parent ifTrue:[
+		level   := level + 1.
+		lftVrtX := rgtVrtX.
+	    ] ifFalse:[
+		level   := item level.
+		lftVrtX := self xVisibleOfVerticalLineAt:level.
+	    ].
+	    showVLines := (level >= minVertLevel and:[lftVrtX >= xL]).
+	    rgtVrtX    := self xVisibleOfVerticalLineAt:level + 1.
 
-            level >= minHorzLevel ifTrue:[
-                xText := (self xVisibleOfTextAtLevel:level) - textStartLeft.
-                showHLine := (xL < xText and:[xR > lftVrtX]). 
-            ] ifFalse:[
-                showHLine := false
-            ].
-        ].
+	    level >= minHorzLevel ifTrue:[
+		xText := (self xVisibleOfTextAtLevel:level) - textStartLeft.
+		showHLine := (xL < xText and:[xR > lftVrtX]).
+	    ] ifFalse:[
+		showHLine := false
+	    ].
+	].
 
-        showHLine ifTrue:[
-            ( level ~~ 2
-             or:[showRoot or:[(showLeftIdc and:[item hasIndicator])]]
-            ) ifTrue:[
-                item drawHorizontalLineUpToText ifTrue:[ x := xText ]
-                                               ifFalse:[ x := rgtVrtX ].
+	showHLine ifTrue:[
+	    ( level ~~ 2
+	     or:[showRoot or:[(showLeftIdc and:[item hasIndicator])]]
+	    ) ifTrue:[
+		item drawHorizontalLineUpToText ifTrue:[ x := xText ]
+					       ifFalse:[ x := rgtVrtX ].
 
-                self displayLineFromX:lftVrtX y:yCtr toX:x y:yCtr.
-            ].
-        ].
+		self displayLineFromX:lftVrtX y:yCtr toX:x y:yCtr.
+	    ].
+	].
 
-        anIndex == start ifTrue:[
-            (item isExpanded and:[item hasChildren]) ifTrue:[
-                self displayLineFromX:rgtVrtX y:yCtr toX:rgtVrtX y:yBot.
-            ]
-        ].
+	anIndex == start ifTrue:[
+	    (item isExpanded and:[item hasChildren]) ifTrue:[
+		self displayLineFromX:rgtVrtX y:yCtr toX:rgtVrtX y:yBot.
+	    ]
+	].
 
-        showVLines ifTrue:[
-            parent last == item ifTrue:[ y := yCtr ]
-                               ifFalse:[ y := yBot ].
-            x  := lftVrtX.
-            p2 := parent.
-            lv := level - 1.
+	showVLines ifTrue:[
+	    parent last == item ifTrue:[ y := yCtr ]
+			       ifFalse:[ y := yBot ].
+	    x  := lftVrtX.
+	    p2 := parent.
+	    lv := level - 1.
 
-            level >= smallestLevel ifTrue:[
-                self displayLineFromX:x y:runHLnY toX:x y:y.
-            ].
+	    level >= smallestLevel ifTrue:[
+		self displayLineFromX:x y:runHLnY toX:x y:y.
+	    ].
 
-            [ (p2 notNil and:[lv >= minVertLevel]) ] whileTrue:[
-                p1 := p2 parent.
+	    [ (p2 notNil and:[lv >= minVertLevel]) ] whileTrue:[
+		p1 := p2 parent.
 
-                p1 notNil ifTrue:[
-                    x := self xVisibleOfVerticalLineAt:lv.
+		p1 notNil ifTrue:[
+		    x := self xVisibleOfVerticalLineAt:lv.
 
-                    x < xL ifTrue:[
-                        p1 := nil.
-                    ] ifFalse:[
-                        p1 last ~~ p2 ifTrue:[
-                            lv >= smallestLevel ifTrue:[
-                                self displayLineFromX:x y:(yTop - 1) toX:x y:yBot
-                            ] ifFalse:[
-                                buildInArray isNil ifTrue:[buildInArray := Array new:smallestLevel].
-                                buildInArray at:lv put:yBot
-                            ]    
-                        ].
-                    ].
-                ].
-                p2 := p1.
-                lv := lv - 1.
-            ].
-        ].
-        prevItem := item.
-        runHLnY  := yCtr.
+		    x < xL ifTrue:[
+			p1 := nil.
+		    ] ifFalse:[
+			p1 last ~~ p2 ifTrue:[
+			    lv >= smallestLevel ifTrue:[
+				self displayLineFromX:x y:(yTop - 1) toX:x y:yBot
+			    ] ifFalse:[
+				buildInArray isNil ifTrue:[buildInArray := Array new:smallestLevel].
+				buildInArray at:lv put:yBot
+			    ]
+			].
+		    ].
+		].
+		p2 := p1.
+		lv := lv - 1.
+	    ].
+	].
+	prevItem := item.
+	runHLnY  := yCtr.
     ].
 
     buildInArray notNil ifTrue:[
-        y := begHLnY.
+	y := begHLnY.
 
-        2 to:smallestLevel do:[:i| |u yB|
-            (yB := buildInArray at:i) notNil ifTrue:[
-                x := self xVisibleOfVerticalLineAt:i.
+	2 to:smallestLevel do:[:i| |u yB|
+	    (yB := buildInArray at:i) notNil ifTrue:[
+		x := self xVisibleOfVerticalLineAt:i.
 
-                x >= xL ifTrue:[
-                    self displayLineFromX:x y:y toX:x y:yB
-                ]
-            ].
-        ]
+		x >= xL ifTrue:[
+		    self displayLineFromX:x y:y toX:x y:yB
+		]
+	    ].
+	]
     ].
     self mask:nil.
 !
@@ -1133,21 +1133,21 @@
     width := icon width.
 
     (constantHeight notNil and:[icon height > constantHeight]) ifTrue:[
-        constantHeight := icon height + lineSpacing.
-        self recomputeHeightOfContents.
+	constantHeight := icon height + lineSpacing.
+	self recomputeHeightOfContents.
 
-        width <= imageWidth ifTrue:[
-            self contentsChanged.
-            StopRedrawSignal raiseRequest
-        ].
+	width <= imageWidth ifTrue:[
+	    self contentsChanged.
+	    StopRedrawSignal raiseRequest
+	].
     ] ifFalse:[
-        width <= imageWidth ifTrue:[ ^ icon ].
+	width <= imageWidth ifTrue:[ ^ icon ].
     ].
 
     maxLevel := 1.
 
     self list criticalDo:[
-        self list do:[:el| maxLevel := maxLevel max:(el level) ].
+	self list do:[:el| maxLevel := maxLevel max:(el level) ].
     ].
 
     needMore        := (width - imageWidth) max:2.
@@ -1157,18 +1157,18 @@
     alignTextRightX := alignTextRightX max:newX.
 
     widthOfContents notNil ifTrue:[
-        alignTextRight ifTrue:[
-            widthOfContents := alignTextRightX + maxWidthOfText
-        ] ifFalse:[
-            widthOfContents := widthOfContents + (newX - oldX)
-        ].
-        width           := renderer widthFor:anItem.
-        startOfText     := self xVisibleOfTextAtLevel:(anItem level).
-        widthOfContents := widthOfContents max:(startOfText + width).
+	alignTextRight ifTrue:[
+	    widthOfContents := alignTextRightX + maxWidthOfText
+	] ifFalse:[
+	    widthOfContents := widthOfContents + (newX - oldX)
+	].
+	width           := listRenderer widthFor:anItem.
+	startOfText     := self xVisibleOfTextAtLevel:(anItem level).
+	widthOfContents := widthOfContents max:(startOfText + width).
 
-        width > maxWidthOfText ifTrue:[
-            maxWidthOfText := width
-        ].
+	width > maxWidthOfText ifTrue:[
+	    maxWidthOfText := width
+	].
     ].
     self contentsChanged.
     StopRedrawSignal raiseRequest.
@@ -1185,47 +1185,47 @@
     modelChangedDuringButtonPress := nil.
 
     enabled ifFalse:[^ self].
-    self closeEditor.        
+    self closeEditor.
 
     line := self yVisibleToLineNr:y.
     line notNil ifTrue:[
-        item := self at:line ifAbsent:nil.
-        item notNil ifTrue:[
-            "/ translate the coordinate relative to the items origin    
-            xIcon := self xVisibleOfIconAtLevel:(item level).
-            x >= xIcon ifTrue:[
-                xLabel := self xVisibleOfTextAtLevel:(item level).
-                yItem := self yVisibleOfLine:line.
+	item := self at:line ifAbsent:nil.
+	item notNil ifTrue:[
+	    "/ translate the coordinate relative to the items origin
+	    xIcon := self xVisibleOfIconAtLevel:(item level).
+	    x >= xIcon ifTrue:[
+		xLabel := self xVisibleOfTextAtLevel:(item level).
+		yItem := self yVisibleOfLine:line.
 
-                x >= xLabel ifTrue:[
-                    (item processButtonPress:button x:(x - xLabel) y:(y - yItem) on:self) == true ifTrue:[
-                        ^ self
-                    ]
-                ].
-                (item processButtonPressOnIcon:button on:self) == true ifTrue:[
-                    ^ self
-                ]
-            ].
-        ]
+		x >= xLabel ifTrue:[
+		    (item processButtonPress:button x:(x - xLabel) y:(y - yItem) on:self) == true ifTrue:[
+			^ self
+		    ]
+		].
+		(item processButtonPressOnIcon:button on:self) == true ifTrue:[
+		    ^ self
+		]
+	    ].
+	]
     ] ifFalse:[
-        item := nil
+	item := nil
     ].
 
     showIndicators ifTrue:[
-        (button == 1 or:[button == #select]) ifTrue:[
-            (item notNil and:[item hasIndicator]) ifTrue:[
-                x0 := self xVisibleOfIndicatorAtLevel:(item level).
+	(button == 1 or:[button == #select]) ifTrue:[
+	    (item notNil and:[item hasIndicator]) ifTrue:[
+		x0 := self xVisibleOfIndicatorAtLevel:(item level).
 
-                (x between:x0 and:(x0 + indicatorWidth)) ifTrue:[
-                    (item isExpanded and:[item canCollapse not]) ifTrue:[
-                        "/ a special one (like a non-collapsable root)
-                    ] ifFalse:[
-                        self indicatorPressedAt:line.
-                        ^ self
-                    ].
-                ].
-            ].
-        ].
+		(x between:x0 and:(x0 + indicatorWidth)) ifTrue:[
+		    (item isExpanded and:[item canCollapse not]) ifTrue:[
+			"/ a special one (like a non-collapsable root)
+		    ] ifFalse:[
+			self indicatorPressedAt:line.
+			^ self
+		    ].
+		].
+	    ].
+	].
     ].
 
     super buttonPress:button x:x y:y.
@@ -1241,12 +1241,12 @@
     newIdx := self selectedIndex.
 
     (newIdx ~~ oldIdx and:[newIdx ~~ 0]) ifTrue:[
-        expandOnSelect ifTrue:[
-            newItem := self at:newIdx ifAbsent:nil.
-            newItem isNil ifTrue:[^ self].
-            newItem expand
-        ].
-        "/ done in buttonRelease
+	expandOnSelect ifTrue:[
+	    newItem := self at:newIdx ifAbsent:nil.
+	    newItem isNil ifTrue:[^ self].
+	    newItem expand
+	].
+	"/ done in buttonRelease
 "/        self makeLineVisible:newIdx.
     ].
 !
@@ -1264,49 +1264,49 @@
      or:[aKey == #CursorRight
      or:[aKey == #CursorLeft]]
     ) ifFalse:[
-        super keyPress:aKey x:x y:y.
-        ^ self
+	super keyPress:aKey x:x y:y.
+	^ self
     ].
 
     lineNr := self cursorLine.
 
     lineNr ~~ 0 ifTrue:[
-        item := cursorItem
+	item := cursorItem
     ] ifFalse:[
-        lineNr := self selectedIndex.
-        lineNr == 0 ifTrue:[^ self].
+	lineNr := self selectedIndex.
+	lineNr == 0 ifTrue:[^ self].
 
-        item := self at:lineNr ifAbsent:nil.
-        item isNil ifTrue:[^ self].
+	item := self at:lineNr ifAbsent:nil.
+	item isNil ifTrue:[^ self].
     ].
 
     aKey == Character space ifTrue:[
-        item toggleExpand.
-        ^ self
+	item toggleExpand.
+	^ self
     ].
     isCursorLeft := (aKey == #CursorLeft).
 
     item isExpanded == isCursorLeft ifTrue:[
-        (self sensor ctrlDown or:[self sensor shiftDown]) ifTrue:[
-            item recursiveToggleExpand.
-        ] ifFalse:[
-            item toggleExpand.
-        ].
-        ^ self
+	(self sensor ctrlDown or:[self sensor shiftDown]) ifTrue:[
+	    item recursiveToggleExpand.
+	] ifFalse:[
+	    item toggleExpand.
+	].
+	^ self
     ].
     isCursorLeft ifTrue:[
-        (item := item parent) isNil ifTrue:[^ self].
-        lineNr := self identityIndexOf:item.
+	(item := item parent) isNil ifTrue:[^ self].
+	lineNr := self identityIndexOf:item.
     ] ifFalse:[
-        item hasChildren ifFalse:[^ self].
-        lineNr := lineNr + 1.
+	item hasChildren ifFalse:[^ self].
+	lineNr := lineNr + 1.
     ].
 
     item := self at:lineNr ifAbsent:nil.
     item isNil ifTrue:[^ self].
 
     (self canSelectIndex:lineNr forAdd:false) ifTrue:[
-        self selection:lineNr
+	self selection:lineNr
     ].
 
     "Modified: / 18-09-2007 / 23:02:09 / cg"
@@ -1328,13 +1328,13 @@
     defaultWidth   := imageWidth.
 
     icons keysAndValuesDo:[:aKey :anImage|
-        anImage isNil ifTrue:[
-            ('HierachicalListView [warning]: missing image: ' , aKey) errorPrintCR.
-        ] ifFalse:[
-            image := self imageOnMyDevice:anImage.
-            icons at:aKey put:image.
-            imageWidth := image width max:imageWidth.
-        ]
+	anImage isNil ifTrue:[
+	    ('HierachicalListView [warning]: missing image: ' , aKey) errorPrintCR.
+	] ifFalse:[
+	    image := self imageOnMyDevice:anImage.
+	    icons at:aKey put:image.
+	    imageWidth := image width max:imageWidth.
+	]
     ].
     imageWidth      := (imageWidth + 1 // 2 * 2) max:defaultWidth.
     alignTextRightX := imageWidth + 20 max:alignTextRightX.
@@ -1346,9 +1346,9 @@
     "setup viewStyle specifics
     "
     <resource: #style (#'selection.highlightEnterItem'
-                       #'selection.expandOnSelect' 
-                       #'selection.autoScrollHorizontal' 
-                       )>
+		       #'selection.expandOnSelect'
+		       #'selection.autoScrollHorizontal'
+		       )>
 
     |cls|
 
@@ -1401,33 +1401,33 @@
     iconOrKey := anItem icon.
 
     iconOrKey notNil ifTrue:[
-        iconOrKey isImageOrForm ifTrue:[
-            "/ got an image; have to register the image on my device
+	iconOrKey isImageOrForm ifTrue:[
+	    "/ got an image; have to register the image on my device
 
-            iconOrKey device == device ifTrue:[
-                ^ iconOrKey
-            ].
-            ^ icons at:iconOrKey ifAbsentPut:[ self imageOnMyDevice:iconOrKey ].
-        ].
+	    iconOrKey device == device ifTrue:[
+		^ iconOrKey
+	    ].
+	    ^ icons at:iconOrKey ifAbsentPut:[ self imageOnMyDevice:iconOrKey ].
+	].
 
-        image := icons at:iconOrKey ifAbsent:nil.
-        image notNil ifTrue:[ ^ image ].
+	image := icons at:iconOrKey ifAbsent:nil.
+	image notNil ifTrue:[ ^ image ].
     ].
 
     "/ test whether a default image should be returned
     useDefaultIcons ifFalse:[
-        ^ nil
+	^ nil
     ].
 
     anItem hasChildren ifFalse:[
-        anItem isDirectoryItem ifFalse:[
-            ^ icons at:#empty ifAbsentPut:[ self imageOnMyDevice:(self class emptyIcon) ]
-        ].
-        ^ icons at:#collapsed ifAbsentPut:[ self imageOnMyDevice:(self class collapsedIcon) ].
+	anItem isDirectoryItem ifFalse:[
+	    ^ icons at:#empty ifAbsentPut:[ self imageOnMyDevice:(self class emptyIcon) ]
+	].
+	^ icons at:#collapsed ifAbsentPut:[ self imageOnMyDevice:(self class collapsedIcon) ].
     ].
 
     anItem isExpanded ifTrue:[
-        ^ icons at:#expanded ifAbsentPut:[ self imageOnMyDevice:(self class expandedIcon) ].
+	^ icons at:#expanded ifAbsentPut:[ self imageOnMyDevice:(self class expandedIcon) ].
     ].
     ^ icons at:#collapsed ifAbsentPut:[ self imageOnMyDevice:(self class collapsedIcon) ].
 
@@ -1439,19 +1439,19 @@
     "
     |image height|
 
-    height := renderer heightFor:anItem.
+    height := listRenderer heightFor:anItem.
     image := self iconFor:anItem.
 
     image notNil ifTrue:[
-        height := image height max:height.
+	height := image height max:height.
     ].
 
     hasConstantHeight ifTrue:[
-        icons size ~~ 0 ifTrue:[
-            icons do:[:anIcon| height := anIcon height max:height ]
-        ] ifFalse:[
-            image isNil ifTrue:[ height := height max:16 ]
-        ]
+	icons size ~~ 0 ifTrue:[
+	    icons do:[:anIcon| height := anIcon height max:height ]
+	] ifFalse:[
+	    image isNil ifTrue:[ height := height max:16 ]
+	]
     ].
     height := height + lineSpacing.
     ^ height max:indicatorHeight
@@ -1470,27 +1470,27 @@
     prevItem := self at:start ifAbsent:nil.
 
     (prevItem isNil or:[(currParent := prevItem parent) isNil]) ifTrue:[
-        ^ 1
+	^ 1
     ].
 
     (min := prevItem level) == 2 ifTrue:[
-        ^ min
+	^ min
     ].
     beg := start + 1.
 
     beg to:stop do:[:i|
-        item := self at:i ifAbsent:nil.
-        item isNil ifTrue:[^ min].
+	item := self at:i ifAbsent:nil.
+	item isNil ifTrue:[^ min].
 
-        (nextParent := item parent) == currParent ifFalse:[
-            (currParent := nextParent) == prevItem ifFalse:[
-                (lvl := item level) == 2 ifTrue:[
-                    ^ 2
-                ].
-                min := min min:lvl
-            ]
-        ].
-        prevItem := item
+	(nextParent := item parent) == currParent ifFalse:[
+	    (currParent := nextParent) == prevItem ifFalse:[
+		(lvl := item level) == 2 ifTrue:[
+		    ^ 2
+		].
+		min := min min:lvl
+	    ]
+	].
+	prevItem := item
     ].
     ^ min
 !
@@ -1500,51 +1500,51 @@
     "
     |parent item textX level width widthOfLabel|
 
-    width := renderer widthOfWidestLineBetween:firstLine and:lastLine.
+    width := listRenderer widthOfWidestLineBetween:firstLine and:lastLine.
     width notNil ifTrue:[^ width].
 
     width := 20.
 
     alignTextRight ifTrue:[
-        parent := nil.
-        level  := 1.
+	parent := nil.
+	level  := 1.
 
-        firstLine to:lastLine do:[:idx|
-            item := self at:idx ifAbsent:nil.
+	firstLine to:lastLine do:[:idx|
+	    item := self at:idx ifAbsent:nil.
 
-            item notNil ifTrue:[
-                width := (renderer widthFor:item) max:width.
+	    item notNil ifTrue:[
+		width := (listRenderer widthFor:item) max:width.
 
-                item parent ~~ parent ifTrue:[
-                    level  := item level max:level.
-                    parent := item parent.
-                ].
-            ].
-        ].
-        maxWidthOfText := maxWidthOfText max:width.
-        textX := self xVisibleOfIconAtLevel:(level + 1).
+		item parent ~~ parent ifTrue:[
+		    level  := item level max:level.
+		    parent := item parent.
+		].
+	    ].
+	].
+	maxWidthOfText := maxWidthOfText max:width.
+	textX := self xVisibleOfIconAtLevel:(level + 1).
 
-        alignTextRightX < textX ifTrue:[
-            alignTextRightX := textX.
-            self invalidate.
-        ].
-        ^ alignTextRightX + width
+	alignTextRightX < textX ifTrue:[
+	    alignTextRightX := textX.
+	    self invalidate.
+	].
+	^ alignTextRightX + width
     ].
 
     parent := 4711.  "/ force a computation
 
     firstLine to:lastLine do:[:idx|
-        item := self at:idx ifAbsent:nil.
+	item := self at:idx ifAbsent:nil.
 
-        item notNil ifTrue:[
-            item parent ~~ parent ifTrue:[
-                textX  := self xVisibleOfTextAtLevel:(item level).
-                parent := item parent.
-            ].
-            widthOfLabel   := renderer widthFor:item.
-            maxWidthOfText := maxWidthOfText max:widthOfLabel.
-            width          := widthOfLabel + textX max:width
-        ].
+	item notNil ifTrue:[
+	    item parent ~~ parent ifTrue:[
+		textX  := self xVisibleOfTextAtLevel:(item level).
+		parent := item parent.
+	    ].
+	    widthOfLabel   := listRenderer widthFor:item.
+	    maxWidthOfText := maxWidthOfText max:widthOfLabel.
+	    width          := widthOfLabel + textX max:width
+	].
     ].
     ^ width + viewOrigin x.
 !
@@ -1557,9 +1557,9 @@
     x := self xVisibleOfVerticalLineAt:aLevel.
 
     (showRoot and:[aLevel == 1]) ifTrue:[
-        showLeftIndicators ifFalse:[
-            ^ x - (imageWidth // 2)
-        ].
+	showLeftIndicators ifFalse:[
+	    ^ x - (imageWidth // 2)
+	].
     ].
     ^ x + (indicatorWidth // 2) + imageInset
 !
@@ -1584,7 +1584,7 @@
     "returns the visible origin x of the text label at a level.
     "
     alignTextRight ifTrue:[
-        ^ alignTextRightX - (viewOrigin x)
+	^ alignTextRightX - (viewOrigin x)
     ].
     ^ (self xVisibleOfIconAtLevel:aLevel) + imageWidth + textStartLeft
 !
@@ -1599,20 +1599,20 @@
     xOffset  := igWidth2 + opWidth2 + imageInset.
 
     showRoot ifTrue:[ firstLevel := 1 ]
-            ifFalse:[ firstLevel := 2 ].
+	    ifFalse:[ firstLevel := 2 ].
 
     showLeftIndicators ifTrue:[
-        aLevel < firstLevel ifTrue:[
-            xOffset := opWidth2 - (firstLevel * xOffset)
-        ] ifFalse:[
-            xOffset := opWidth2 + ((aLevel - firstLevel) * xOffset)
-        ]
+	aLevel < firstLevel ifTrue:[
+	    xOffset := opWidth2 - (firstLevel * xOffset)
+	] ifFalse:[
+	    xOffset := opWidth2 + ((aLevel - firstLevel) * xOffset)
+	]
     ] ifFalse:[
-        aLevel < 2 ifTrue:[
-            xOffset := igWidth2 - ((aLevel - firstLevel) * xOffset)
-        ] ifFalse:[
-            xOffset := igWidth2 + ((aLevel - firstLevel - 1) * xOffset)
-        ].
+	aLevel < 2 ifTrue:[
+	    xOffset := igWidth2 - ((aLevel - firstLevel) * xOffset)
+	] ifFalse:[
+	    xOffset := igWidth2 + ((aLevel - firstLevel - 1) * xOffset)
+	].
     ].
     "/ 2 := a left margin
     ^ xOffset + 2 - (viewOrigin x)
@@ -1639,13 +1639,13 @@
     level == 1 ifTrue:[ ^ 0 ].                                  "/ is root item
 
     level == 2 ifTrue:[                                         "/ parent is root
-        (showRoot and:[showLeftIndicators]) ifFalse:[ ^ 0 ].
+	(showRoot and:[showLeftIndicators]) ifFalse:[ ^ 0 ].
     ].
 
     xLft := self xVisibleOfIconAtLevel:(level - 1).
     xLft > 0 ifFalse:[ ^ vwOrgX + xLft max:0 ].
 
-    xRgt := (self xVisibleOfTextAtLevel:level) + (renderer widthFor:item).
+    xRgt := (self xVisibleOfTextAtLevel:level) + (listRenderer widthFor:item).
     useX := xRgt - width.
 
     useX > 0 ifFalse:[ ^ vwOrgX ].
@@ -1671,11 +1671,11 @@
     availY := (self yVisibleOfLine:lineNr) - (self yVisibleOfLine:1).
 
     availY > margin ifTrue:[
-        usedY := (self yVisibleOfLine:(numLines + 1)) - (height - margin - margin).
+	usedY := (self yVisibleOfLine:(numLines + 1)) - (height - margin - margin).
 
-        usedY > 1 ifTrue:[
-            vwOrgY := vwOrgY + (usedY min:availY).
-        ].
+	usedY > 1 ifTrue:[
+	    vwOrgY := vwOrgY + (usedY min:availY).
+	].
     ].
     vwOrgX := self computeViewOriginXat:lineNr.
 
@@ -1692,40 +1692,40 @@
     (shown and:[aLineNumber notNil]) ifFalse:[^ self].
 
     aLineNumber < 1 ifTrue:[
-        ^ self
+	^ self
     ].
 
     newX := oldX := viewOrigin x.
 
     aLineNumber == 1 ifTrue:[
-        newX := self computeViewOriginXat:1.
-        newY := 0.
+	newX := self computeViewOriginXat:1.
+	newY := 0.
     ] ifFalse:[
-        item := self at:aLineNumber ifAbsent:nil.
-        item isNil ifTrue:[^ self].
+	item := self at:aLineNumber ifAbsent:nil.
+	item isNil ifTrue:[^ self].
 
-        y0 := self yVisibleOfLine:aLineNumber.
+	y0 := self yVisibleOfLine:aLineNumber.
 
-        (     y0 < margin
-         or:[(y0 + (renderer heightFor:item)) > (height - margin)]
-        ) ifTrue:[
-            newY := ((self yAbsoluteOfLine:aLineNumber) - (height // 2)) max:0.
-        ] ifFalse:[
-            newY := viewOrigin y.
-        ].
+	(     y0 < margin
+	 or:[(y0 + (listRenderer heightFor:item)) > (height - margin)]
+	) ifTrue:[
+	    newY := ((self yAbsoluteOfLine:aLineNumber) - (height // 2)) max:0.
+	] ifFalse:[
+	    newY := viewOrigin y.
+	].
 
-        self autoScrollHorizontal ifTrue:[
-            wLine := self widthOfWidestLineBetween:aLineNumber and:aLineNumber.
-            (wLine < self innerWidth) ifTrue:[
-                (oldX == 0) ifTrue:[
-                    newX := self computeViewOriginXat:aLineNumber.
-                ] ifFalse:[
-                    newX := 0
-                ].
-            ] ifFalse:[
-                newX := self computeViewOriginXat:aLineNumber.
-            ].
-        ].
+	self autoScrollHorizontal ifTrue:[
+	    wLine := self widthOfWidestLineBetween:aLineNumber and:aLineNumber.
+	    (wLine < self innerWidth) ifTrue:[
+		(oldX == 0) ifTrue:[
+		    newX := self computeViewOriginXat:aLineNumber.
+		] ifFalse:[
+		    newX := 0
+		].
+	    ] ifFalse:[
+		newX := self computeViewOriginXat:aLineNumber.
+	    ].
+	].
     ].
     self scrollTo:(newX @ newY).
 ! !
@@ -1733,5 +1733,5 @@
 !HierarchicalListView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/HierarchicalListView.st,v 1.113 2008-12-19 08:14:52 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/HierarchicalListView.st,v 1.114 2009-08-07 10:50:41 sr Exp $'
 ! !
--- a/ListModelView.st	Tue Aug 04 14:15:20 2009 +0200
+++ b/ListModelView.st	Fri Aug 07 12:50:41 2009 +0200
@@ -15,7 +15,7 @@
 	instanceVariableNames:'list listHolder textStartLeft textStartTop viewOrigin enabled
 		fgColor bgColor lineSpacing widthOfContents computeWidthInRange
 		startOfLinesY autoScroll autoScrollBlock scrollWhenUpdating
-		hasConstantHeight constantHeight previousExtent renderer
+		hasConstantHeight constantHeight previousExtent listRenderer
 		cachedPreferredExtent'
 	classVariableNames:'DefaultForegroundColor DefaultBackgroundColor DefaultShadowColor
 		DefaultLightColor StopRedrawSignal'
@@ -75,46 +75,46 @@
     the list ( List or HierarchicalList ).
 
     ATTENTION (warning by cg):
-        in contrast to its inappropriate name, this class COMPLETELY ignores the model
-        instance variable - all is through the list/listHolder.
+	in contrast to its inappropriate name, this class COMPLETELY ignores the model
+	instance variable - all is through the list/listHolder.
 
     Each list item is obligated to provide 3 services:
-        - heightOn:aGC
-        - widthOn:aGC
-        - displayOn:aGC x:x y:y
+	- heightOn:aGC
+	- widthOn:aGC
+	- displayOn:aGC x:x y:y
 
     [Instance variables:]
-        list                   <List-Model>     List or HierarchicalList ...
-        listHolder             <Model>          Model, which keeps a List
-        textStartLeft          <Number>         left inset of text
-        viewOrigin             <Point>          the current origin
-        enabled                <Boolean>        widget is enabled/disabeled
-        fgColor                <Color>          color to draw characters
-        bgColor                <Color>          the background
-        lineSpacing            <Number>         pixels between lines
-        widthOfContents        <Number>         cached width of widest line
-        computeWidthInRange    <Point>          used for recompute width of contents
-        startOfLinesY          <Collection>     keeps all the absolute Y-start positions
-                                                for each line in the list. The first
-                                                entry into the list is the top Y inset.
-        supportsDisplayInRange <Boolean>        set to true if the list elements
-                                                supports the service:
-                                                    #displayOn:x:y:h:
-
-        hasConstantHeight      <Boolean>        true, than each line has the same height
-
-        constantHeight         <SmallInteger>   hasConstantHeight is turned on, this
-                                                is the used line height
+	list                   <List-Model>     List or HierarchicalList ...
+	listHolder             <Model>          Model, which keeps a List
+	textStartLeft          <Number>         left inset of text
+	viewOrigin             <Point>          the current origin
+	enabled                <Boolean>        widget is enabled/disabeled
+	fgColor                <Color>          color to draw characters
+	bgColor                <Color>          the background
+	lineSpacing            <Number>         pixels between lines
+	widthOfContents        <Number>         cached width of widest line
+	computeWidthInRange    <Point>          used for recompute width of contents
+	startOfLinesY          <Collection>     keeps all the absolute Y-start positions
+						for each line in the list. The first
+						entry into the list is the top Y inset.
+	supportsDisplayInRange <Boolean>        set to true if the list elements
+						supports the service:
+						    #displayOn:x:y:h:
+
+	hasConstantHeight      <Boolean>        true, than each line has the same height
+
+	constantHeight         <SmallInteger>   hasConstantHeight is turned on, this
+						is the used line height
 
     [author:]
-        Claus Atzkern
+	Claus Atzkern
 
     [see also:]
 
-        SelectionInListModelView
-        HierarchicalListView
-        List
-        HierarchicalList
+	SelectionInListModelView
+	HierarchicalListView
+	List
+	HierarchicalList
 "
 !
 
@@ -209,64 +209,75 @@
     "
     |negatedOrg|
 
-    renderer listWillChange.
+    listRenderer listWillChange.
 
     list ~~ aList ifTrue:[
-        list removeDependent:self.
-        list := aList.
-        list isNil ifTrue:[list := self newDefaultList ].
-        list addDependent:self
+	list removeDependent:self.
+	list := aList.
+	list isNil ifTrue:[list := self newDefaultList ].
+	list addDependent:self
     ].
 "/    preferredExtent := nil.
     cachedPreferredExtent := nil.
     widthOfContents := nil.
 
     realized ifTrue:[
-        self recomputeHeightOfContents.
-        scrollWhenUpdating == #beginOfText ifTrue:[
-            viewOrigin = (0@0) ifFalse:[
-                self originWillChange.
-                negatedOrg := viewOrigin negated.
-                viewOrigin := (0@0).
-                self originChanged:negatedOrg.
-            ].
-        ] ifFalse:[
-            scrollWhenUpdating == #endOfText ifTrue:[
-                self scrollTo:(0 @ self heightOfContents - self innerHeight) redraw:false
-            ]
-        ].
-        self invalidate.
+	self recomputeHeightOfContents.
+	scrollWhenUpdating == #beginOfText ifTrue:[
+	    viewOrigin = (0@0) ifFalse:[
+		self originWillChange.
+		negatedOrg := viewOrigin negated.
+		viewOrigin := (0@0).
+		self originChanged:negatedOrg.
+	    ].
+	] ifFalse:[
+	    scrollWhenUpdating == #endOfText ifTrue:[
+		self scrollTo:(0 @ self heightOfContents - self innerHeight) redraw:false
+	    ]
+	].
+	self invalidate.
     ].
     self contentsChanged
 !
 
+listRenderer
+    "returns the used listrenderer
+    "
+    ^ listRenderer
+!
+
 renderer
-    "returns the used renderer
-    "
-    ^ renderer
+    self obsoleteMethodWarning:'naming conflict renderer vs. listRenderer'.
+    ^ self listRenderer
 !
 
-renderer:aRenderer
-    "change the used renderer
+listRenderer:aRendererOrRendererClass
+    "change the used listRenderer
     "
-    aRenderer isNil ifTrue:[^ self].
-
-    renderer == aRenderer ifTrue:[^ self].
-    renderer notNil ifTrue:[renderer release].
-
-    renderer := aRenderer.
-    renderer isBehavior ifTrue:[
-        renderer := renderer basicNew initialize.
+    aRendererOrRendererClass isNil ifTrue:[^ self].
+
+    listRenderer == aRendererOrRendererClass ifTrue:[^ self].
+    listRenderer notNil ifTrue:[listRenderer release].
+
+    aRendererOrRendererClass isBehavior ifTrue:[
+	listRenderer := aRendererOrRendererClass basicNew initialize.
+    ] ifFalse:[
+	listRenderer := aRendererOrRendererClass.
     ].
-    renderer forView:self.
+    listRenderer forView:self.
+!
+
+renderer:aTableRenderer
+    self obsoleteMethodWarning:'naming conflict renderer vs. listRenderer'.
+    self listRenderer:aTableRenderer
 !
 
 setupTableRenderer
-    "under test - creates a renderer with columns based on a DataSetColumnSpec
+    "creates a renderer with columns based on a DataSetColumnSpec
      answer the new renderer"
 
-    self renderer:TableRenderer.
-    ^ renderer
+    self listRenderer:TableRenderer.
+    ^ listRenderer
 ! !
 
 !ListModelView methodsFor:'accessing-behavior'!
@@ -313,7 +324,7 @@
     "
 
     aBool == hasConstantHeight ifTrue:[
-        ^ self
+	^ self
     ].
     constantHeight    := nil.
     hasConstantHeight := aBool.
@@ -322,7 +333,7 @@
 !
 
 scrollWhenUpdating:aSymbolOrNil
-    "define how to scroll, when I get a new text 
+    "define how to scroll, when I get a new text
      (via the model or the #contents/#list)
      Allowed arguments are:
 	#keep / nil     -> no change
@@ -347,8 +358,8 @@
 !
 
 at:anIndex ifAbsent:exceptionBlock
-    "return the list element at an index if valid. 
-     If the index is invalid, return the result of evaluating 
+    "return the list element at an index if valid.
+     If the index is invalid, return the result of evaluating
      the exceptionblock.
     "
     ^ list at:anIndex ifAbsent:exceptionBlock
@@ -389,23 +400,23 @@
     |oldWidth oldHeight|
 
     (aFont isNil or:[aFont = font]) ifFalse:[
-        oldWidth  := font width.
-        oldHeight := font height.
-
-        super font:aFont.
-
-        (font widthOn:device) ~~ oldWidth ifTrue:[       "/ force a recomputation
+	oldWidth  := font width.
+	oldHeight := font height.
+
+	super font:aFont.
+
+	(font widthOn:device) ~~ oldWidth ifTrue:[       "/ force a recomputation
 "/            preferredExtent := nil.
-            cachedPreferredExtent := nil.
-            widthOfContents := nil.
-        ].
-        realized ifTrue:[
-            oldHeight ~~ (font heightOn:device) ifTrue:[
-                self recomputeHeightOfContents.
-                self contentsChanged.
-            ].
-            self invalidate
-        ].
+	    cachedPreferredExtent := nil.
+	    widthOfContents := nil.
+	].
+	realized ifTrue:[
+	    oldHeight ~~ (font heightOn:device) ifTrue:[
+		self recomputeHeightOfContents.
+		self contentsChanged.
+	    ].
+	    self invalidate
+	].
     ].
 !
 
@@ -441,13 +452,13 @@
      by which lines are vertically separated.
     "
     lineSpacing ~= aNumber ifTrue:[
-        lineSpacing := aNumber.
-
-        realized ifTrue:[
-            self recomputeHeightOfContents.
-            self invalidate
-        ].
-        self contentsChanged.
+	lineSpacing := aNumber.
+
+	realized ifTrue:[
+	    self recomputeHeightOfContents.
+	    self invalidate
+	].
+	self contentsChanged.
     ]
 !
 
@@ -455,13 +466,13 @@
     "set the background color
     "
     (aColor notNil and:[bgColor ~~ aColor]) ifTrue:[
-        bgColor := aColor.
-        super viewBackground:bgColor.
-
-        self realized ifTrue:[
-            bgColor := bgColor onDevice:device.
-            self invalidate
-        ].
+	bgColor := aColor.
+	super viewBackground:bgColor.
+
+	self realized ifTrue:[
+	    bgColor := bgColor onDevice:device.
+	    self invalidate
+	].
     ].
 ! !
 
@@ -494,25 +505,25 @@
      deltaHeight "{ Class:SmallInteger }" |
 
     (arg == #icon or:[arg == #hierarchy]) ifTrue:[
-        ^ self
+	^ self
     ].
     hasConstantHeight ifTrue:[
-        self invalidateLineAt:aLnNr.
-        ^ self
+	self invalidateLineAt:aLnNr.
+	^ self
     ].
 
     oldHeight := (self yVisibleOfLine:(aLnNr + 1)) - (self yVisibleOfLine:aLnNr).
     deltaHeight := (self heightOfLineAt:aLnNr) - oldHeight.
 
     deltaHeight == 0 ifTrue:[
-        self invalidateLineAt:aLnNr.
-        ^ self
+	self invalidateLineAt:aLnNr.
+	^ self
     ].
     cache := self startOfLinesY.
 
     aLnNr + 1 to:cache size do:[:i|
-        cache at:i put:((cache at:i) + deltaHeight)
-    ].              
+	cache at:i put:((cache at:i) + deltaHeight)
+    ].
     self contentsChanged.
     self invalidate.
 !
@@ -540,11 +551,11 @@
     newSz := startOfLinesY size + nLines.
 
     (newSz - 1) ~~ self size ifTrue:[
-        "/
-        "/ no longer synchronized
-        "/
-        self lostSynchronisation.
-        ^ self
+	"/
+	"/ no longer synchronized
+	"/
+	self lostSynchronisation.
+	^ self
     ].
     newLines := startOfLinesY. "/ copy.
     newLines addAll:(Array new:nLines) beforeIndex:start + 1.
@@ -553,14 +564,14 @@
     run   := start.
 
     nLines timesRepeat:[
-        absY1 := absY1 + (self heightOfLineAt:run).
-        run   := run + 1.
-        newLines at:run put:absY1.
+	absY1 := absY1 + (self heightOfLineAt:run).
+	run   := run + 1.
+	newLines at:run put:absY1.
     ].
     dltY := absY1 - absY0.
 
     run + 1 to:newSz do:[:i||v|
-        newLines at:i put:((newLines at:i) + dltY)
+	newLines at:i put:((newLines at:i) + dltY)
     ].
     startOfLinesY := newLines.
 
@@ -571,44 +582,44 @@
     maxHg := height - margin.
 
     absY0 < orgY ifTrue:[
-        self originWillChange.
-        viewOrigin y:(dltY + orgY).
-        self originChanged:(0 @ dltY).
+	self originWillChange.
+	viewOrigin y:(dltY + orgY).
+	self originChanged:(0 @ dltY).
     ].
 
     (visY0 >= maxHg or:[visY1 <= margin]) ifTrue:[
-        self contentsChanged.
-        ^ self
+	self contentsChanged.
+	^ self
     ].
     visY0 := visY0 max:margin.
     visY1 := visY1 min:maxHg.
 
     self hasDamage ifTrue:[
-        self invalidate:(Rectangle left:0
-                                    top:visY0 
-                                  width:width 
-                                 height:height - visY0).
-
-        self contentsChanged.
-        ^ self
+	self invalidate:(Rectangle left:0
+				    top:visY0
+				  width:width
+				 height:height - visY0).
+
+	self contentsChanged.
+	^ self
     ].
 
     (start == self size or:[(cpyHg := maxHg - visY1) < 20]) ifTrue:[
-        visY1 := maxHg
+	visY1 := maxHg
     ] ifFalse:[
-        self catchExpose.
-
-        self copyFrom:self x:0 y:visY0
-                         toX:0 y:visY1
-                       width:width height:cpyHg async:true.
-
-        self waitForExpose
+	self catchExpose.
+
+	self copyFrom:self x:0 y:visY0
+			 toX:0 y:visY1
+		       width:width height:cpyHg async:true.
+
+	self waitForExpose
     ].
 
     self invalidateX:margin
-                   y:visY0
-               width:width - margin - margin
-              height:(visY1 - visY0).
+		   y:visY0
+	       width:width - margin - margin
+	      height:(visY1 - visY0).
 
     self contentsChanged.
 !
@@ -635,7 +646,7 @@
     start := aStart.
 
     (size := stop - start + 1) == 0 ifTrue:[
-        ^ self
+	^ self
     ].
 
     self listSizeChanged:start nLines:(size negated).
@@ -644,10 +655,10 @@
     newSz := startOfLinesY size - size.
 
     (newSz - 1) ~~ self size ifTrue:[
-        "/
-        "/ no longer synchrounous
-        "/
-        ^ self lostSynchronisation
+	"/
+	"/ no longer synchrounous
+	"/
+	^ self lostSynchronisation
     ].
 
     absY0 := self yAbsoluteOfLine:start.
@@ -658,8 +669,8 @@
     newLines removeFromIndex:(start + 1) toIndex:(stop + 1).
 
     (start + 1) to:newSz do:[:i|
-        absY0 := newLines at:i.
-        newLines at:i put:(absY0 - dltY).
+	absY0 := newLines at:i.
+	newLines at:i put:(absY0 - dltY).
     ].
     startOfLinesY := newLines.
 
@@ -673,51 +684,51 @@
     maxHg := height - margin.
 
     (self size == 0 or:[(orgY ~~ 0 and:[self maxViewOriginY == 0])]) ifTrue:[
-        (orgX ~~ 0 or:[orgY ~~ 0]) ifTrue:[
-            self originWillChange.
-            viewOrigin := 0@0.
-            self originChanged:((orgX @ orgY) negated).
-        ].
-        self invalidate.
-        ^ self contentsChanged    
+	(orgX ~~ 0 or:[orgY ~~ 0]) ifTrue:[
+	    self originWillChange.
+	    viewOrigin := 0@0.
+	    self originChanged:((orgX @ orgY) negated).
+	].
+	self invalidate.
+	^ self contentsChanged
     ].
 
     visY0 < margin ifTrue:[
-        noRedraw := visY1 <= margin.
-        noRedraw ifTrue:[dltY := dltY negated] ifFalse:[dltY := visY0].
-
-        self originWillChange.
-        viewOrigin y:(dltY + orgY).
-        self originChanged:(0 @ dltY).        
+	noRedraw := visY1 <= margin.
+	noRedraw ifTrue:[dltY := dltY negated] ifFalse:[dltY := visY0].
+
+	self originWillChange.
+	viewOrigin y:(dltY + orgY).
+	self originChanged:(0 @ dltY).
     ] ifFalse:[
-        noRedraw := visY0 >= maxHg
+	noRedraw := visY0 >= maxHg
     ].
     visY0 := visY0 max:margin.
 
     self hasDamage ifTrue:[
-        self invalidate:(Rectangle left:0
-                                    top:visY0 
-                                  width:width 
-                                 height:height - visY0).
-
-        noRedraw := true
+	self invalidate:(Rectangle left:0
+				    top:visY0
+				  width:width
+				 height:height - visY0).
+
+	noRedraw := true
     ].
 
     noRedraw ifFalse:[
-        cpyHg := maxHg - visY1.
-
-        cpyHg > 20 ifTrue:[
-            self catchExpose.
-            self copyFrom:self x:0 y:visY1 toX:0 y:visY0
-                    width:width height:cpyHg async:true.
-            self waitForExpose.
-            visY0 := visY0 + cpyHg.
-        ].
-
-        self invalidateX:margin
-                       y:visY0
-                   width:width - margin - margin
-                  height:(maxHg - visY0).
+	cpyHg := maxHg - visY1.
+
+	cpyHg > 20 ifTrue:[
+	    self catchExpose.
+	    self copyFrom:self x:0 y:visY1 toX:0 y:visY0
+		    width:width height:cpyHg async:true.
+	    self waitForExpose.
+	    visY0 := visY0 + cpyHg.
+	].
+
+	self invalidateX:margin
+		       y:visY0
+		   width:width - margin - margin
+		  height:(maxHg - visY0).
     ].
     self contentsChanged.
 !
@@ -727,15 +738,15 @@
      or list holder"
 
     chgObj == self listHolder ifTrue:[
-        self list:chgObj value.
-        ^ self.
+	self list:chgObj value.
+	^ self.
     ].
 
     chgObj == self list ifTrue:[
-        renderer withinUpdateFromListDo:[
-            self updateFromList:what with:aPara.
-        ].
-        ^ self.
+	listRenderer withinUpdateFromListDo:[
+	    self updateFromList:what with:aPara.
+	].
+	^ self.
     ].
 
     super update:what with:aPara from:chgObj
@@ -747,20 +758,20 @@
     |arg1 arg2|
 
     aParameter isCollection ifFalse:[
-        what == #at:     ifTrue:[self lineChangedAt:aParameter        with:nil.   ^ self].
-        what == #insert: ifTrue:[self listChangedInsert:aParameter  nItems:1.     ^ self].
-        what == #remove: ifTrue:[self listChangedRemove:aParameter toIndex:aParameter. ^ self].
-
-        self list:(self list).  "/ reload list
-        ^ self.
+	what == #at:     ifTrue:[self lineChangedAt:aParameter        with:nil.   ^ self].
+	what == #insert: ifTrue:[self listChangedInsert:aParameter  nItems:1.     ^ self].
+	what == #remove: ifTrue:[self listChangedRemove:aParameter toIndex:aParameter. ^ self].
+
+	self list:(self list).  "/ reload list
+	^ self.
     ].
 
     arg1 := aParameter at:1.
     arg2 := aParameter at:2.
 
     (arg1 == 1 and:[arg2 == self size]) ifTrue:[
-        self list:(self list).  "/ reload list
-        ^ self
+	self list:(self list).  "/ reload list
+	^ self
     ].
 
     what == #at:               ifTrue:[self lineChangedAt:arg1        with:arg2. ^ self].
@@ -768,8 +779,8 @@
     what == #removeFrom:       ifTrue:[self listChangedRemove:arg1 toIndex:arg2. ^ self].
 
     what == #replace: ifTrue:[
-        arg1 to:arg2 do:[:i|self lineChangedAt:i with:nil].
-        ^ self
+	arg1 to:arg2 do:[:i|self lineChangedAt:i with:nil].
+	^ self
     ].
     self halt:'oops - general change'.
     self list:(self list).  "/ reload list
@@ -792,15 +803,15 @@
     y1 := y.
 
     start to:stop do:[:i|
-        item := self at:i ifAbsent:self.        "/ list changed during draw
-        item == self ifTrue:[^ self].
-
-        y0 := y1.
-        y1 := self yVisibleOfLine:(i + 1).
-
-        item notNil ifTrue:[
-            renderer display:item atX:x0 y:y0 lineHeight:(y1 - y0).
-        ]
+	item := self at:i ifAbsent:self.        "/ list changed during draw
+	item == self ifTrue:[^ self].
+
+	y0 := y1.
+	y1 := self yVisibleOfLine:(i + 1).
+
+	item notNil ifTrue:[
+	    listRenderer display:item atX:x0 y:y0 lineHeight:(y1 - y0).
+	]
     ]
 !
 
@@ -810,21 +821,21 @@
     "
     |maxX w|
 
-    maxX := renderer maxItemWidthOrNil.
+    maxX := listRenderer maxItemWidthOrNil.
     w := aWidth.
 
     maxX notNil ifTrue:[ |clip|
-        maxX := maxX - viewOrigin x.
-        maxX > xLft ifFalse:[^ self.].
-
-        w := maxX - xLft min:aWidth.
-
-        (clip := self clipRect copy) notNil ifTrue:[
-            clip width:w
-        ] ifFalse:[
-            clip := Rectangle left:xLft top:yTop width:w height:(height - yTop - margin).
-        ].
-        self clippingRectangle:clip.
+	maxX := maxX - viewOrigin x.
+	maxX > xLft ifFalse:[^ self.].
+
+	w := maxX - xLft min:aWidth.
+
+	(clip := self clipRect copy) notNil ifTrue:[
+	    clip width:w
+	] ifFalse:[
+	    clip := Rectangle left:xLft top:yTop width:w height:(height - yTop - margin).
+	].
+	self clippingRectangle:clip.
     ].
     self drawElementsFrom:start to:stop x:xLft y:yTop w:w.
 !
@@ -848,7 +859,7 @@
     |
 
     (shown and:[aLineNr notNil and:[aLineNr > 0]]) ifFalse:[
-        ^ self
+	^ self
     ].
 
     xR := width - margin.
@@ -859,11 +870,11 @@
     y0 := (self yVisibleOfLine:aLineNr) max:margin.
 
     y0 < yB ifTrue:[
-        y1 := (self yVisibleOfLine:(aLineNr + 1)) min:yB.
-
-        y1 > y0 ifTrue:[
-            self invalidateX:x0 y:y0 width:(xR - x0) height:(y1 - y0) repairNow:false.
-        ]
+	y1 := (self yVisibleOfLine:(aLineNr + 1)) min:yB.
+
+	y1 > y0 ifTrue:[
+	    self invalidateX:x0 y:y0 width:(xR - x0) height:(y1 - y0) repairNow:false.
+	]
     ].
 !
 
@@ -876,24 +887,24 @@
 !
 
 redrawX:x y:y width:w height:h
-    "redraw part of myself immediately, given logical coordinates 
+    "redraw part of myself immediately, given logical coordinates
     "
     |start stop yAbs yStart|
 
     shown ifFalse:[^ self].
 
     (self startOfLinesY size) == (self size + 1) ifFalse:[
-        "oops, recompute the height of the contents (the first time after creation).
-        "
-        self recomputeHeightOfContents.
-
-        self startOfLinesY size > 1 ifTrue:[
-            "oops, the contents height changed
-            "
-            self invalidate.
-            self contentsChanged.
-            ^ self
-        ].
+	"oops, recompute the height of the contents (the first time after creation).
+	"
+	self recomputeHeightOfContents.
+
+	self startOfLinesY size > 1 ifTrue:[
+	    "oops, the contents height changed
+	    "
+	    self invalidate.
+	    self contentsChanged.
+	    ^ self
+	].
     ].
 "/    widthOfContents isNil ifTrue:[
 "/        self preferredExtent
@@ -902,43 +913,43 @@
     start  := self yVisibleToLineNr:y.
 
     start notNil ifTrue:[
-        yAbs := y + h.
-        stop := self yVisibleToLineNr:yAbs.
-
-        stop isNil ifTrue:[
-            stop := self size.
-        ] ifFalse:[ |y0|
-            y0 := self startOfLinesY at:stop ifAbsent:nil.
-            y0 isNil ifTrue:[^ self].   "/ oops, lines differ (will be changed)
-
-            yAbs == y0 ifTrue:[
-                stop := (stop - 1) max:start
-            ].
-        ].
-
-        start > stop ifTrue:[
-            start := stop := nil.
-        ] ifFalse:[
-            (renderer validateDrawableItemsFrom:start to:stop) ifFalse:[
-                self invalidate.
-                ^ self.
-            ].
-            yStart := self yVisibleOfLine:start.
-        ].
+	yAbs := y + h.
+	stop := self yVisibleToLineNr:yAbs.
+
+	stop isNil ifTrue:[
+	    stop := self size.
+	] ifFalse:[ |y0|
+	    y0 := self startOfLinesY at:stop ifAbsent:nil.
+	    y0 isNil ifTrue:[^ self].   "/ oops, lines differ (will be changed)
+
+	    yAbs == y0 ifTrue:[
+		stop := (stop - 1) max:start
+	    ].
+	].
+
+	start > stop ifTrue:[
+	    start := stop := nil.
+	] ifFalse:[
+	    (listRenderer validateDrawableItemsFrom:start to:stop) ifFalse:[
+		self invalidate.
+		^ self.
+	    ].
+	    yStart := self yVisibleOfLine:start.
+	].
     ].
     self paint:bgColor.
     self fillRectangleX:x y:y width:w height:h.
 
     StopRedrawSignal handle:[:ex|
-        "/ an item changed its dimension during drawing, draw is aborted
-        self invalidate
+	"/ an item changed its dimension during drawing, draw is aborted
+	self invalidate
     ] do:[
 
 
-        start notNil ifTrue:[
-            self drawFrom:start to:stop x:x y:yStart w:w.
-        ].
-        renderer postRedrawX:x y:yStart w:w from:start to:stop.
+	start notNil ifTrue:[
+	    self drawFrom:start to:stop x:x y:yStart w:w.
+	].
+	listRenderer postRedrawX:x y:yStart w:w from:start to:stop.
     ].
 ! !
 
@@ -955,9 +966,9 @@
     lineNr isNil ifTrue:[ ^ self ].
 
     [   item := list at:lineNr ifAbsent:[ ^ self ].
-        aTwoArgBlock value:lineNr value:item.
-        lineNr := lineNr + 1.
-        (self yVisibleOfLine:lineNr) < height
+	aTwoArgBlock value:lineNr value:item.
+	lineNr := lineNr + 1.
+	(self yVisibleOfLine:lineNr) < height
     ] whileTrue.
 ! !
 
@@ -967,27 +978,27 @@
     "a key was pressed - handle page-keys here"
 
     <resource: #keyboard( #PreviousPage #NextPage  #HalfPageUp #HalfPageDown
-                          #BeginOfText  #EndOfText #ScrollUp   #ScrollDown
-                        )>
+			  #BeginOfText  #EndOfText #ScrollUp   #ScrollDown
+			)>
 
     |n|
 
     self size ~~ 0 ifTrue:[
-        (aKey == #PreviousPage) ifTrue:[^ self pageUp].
-        (aKey == #NextPage)     ifTrue:[^ self pageDown].
-        (aKey == #HalfPageUp)   ifTrue:[^ self halfPageUp].
-        (aKey == #HalfPageDown) ifTrue:[^ self halfPageDown].
-        (aKey == #BeginOfText)  ifTrue:[^ self scrollToTop].
-        (aKey == #EndOfText)    ifTrue:[^ self scrollToBottom].
-
-        (aKey == #ScrollUp or:[aKey == #ScrollDown]) ifTrue:[
-            n := 1 + (self sensor compressKeyPressEventsWithKey:aKey).
-            n := n * self verticalScrollStep.
-
-            aKey == #ScrollUp ifTrue:[self scrollUp:n]
-                             ifFalse:[self scrollDown:n].
-            ^ self
-        ].
+	(aKey == #PreviousPage) ifTrue:[^ self pageUp].
+	(aKey == #NextPage)     ifTrue:[^ self pageDown].
+	(aKey == #HalfPageUp)   ifTrue:[^ self halfPageUp].
+	(aKey == #HalfPageDown) ifTrue:[^ self halfPageDown].
+	(aKey == #BeginOfText)  ifTrue:[^ self scrollToTop].
+	(aKey == #EndOfText)    ifTrue:[^ self scrollToBottom].
+
+	(aKey == #ScrollUp or:[aKey == #ScrollDown]) ifTrue:[
+	    n := 1 + (self sensor compressKeyPressEventsWithKey:aKey).
+	    n := n * self verticalScrollStep.
+
+	    aKey == #ScrollUp ifTrue:[self scrollUp:n]
+			     ifFalse:[self scrollDown:n].
+	    ^ self
+	].
     ].
     super keyPress:aKey x:x y:y
 !
@@ -1028,7 +1039,7 @@
 
     deviceImage := anImage onDevice:device.
     deviceImage isImage ifTrue:[
-        deviceImage clearMaskedPixels.
+	deviceImage clearMaskedPixels.
     ].
     ^ deviceImage
 "/    |image|
@@ -1077,7 +1088,7 @@
     super initStyle.
 
     DefaultBackgroundColor notNil ifTrue:[
-        viewBackground := DefaultBackgroundColor
+	viewBackground := DefaultBackgroundColor
     ].
     lineSpacing   := 0.
     textStartLeft := 2.
@@ -1089,11 +1100,11 @@
     startOfLinesY add:(textStartTop + margin). "/ top inset of first line
 
     DefaultShadowColor notNil ifTrue:[
-        shadowColor := DefaultShadowColor
+	shadowColor := DefaultShadowColor
     ].
 
     DefaultLightColor notNil ifTrue:[
-        lightColor := DefaultLightColor
+	lightColor := DefaultLightColor
     ].
 !
 
@@ -1109,8 +1120,8 @@
     scrollWhenUpdating := #beginOfText.
     hasConstantHeight  := false.
 
-    renderer isNil ifTrue:[
-        renderer := self class defaultRenderer forView:self.
+    listRenderer isNil ifTrue:[
+	listRenderer := self class defaultRenderer forView:self.
     ].
     self list:(self newDefaultList).
 !
@@ -1122,7 +1133,7 @@
 "/        self recomputeHeightOfContents.
 "/        self contentsChanged.     "/ is computeEditorLayout what you want ?
     "/ ].
-    renderer mapped.
+    listRenderer mapped.
     super mapped
 
 !
@@ -1146,7 +1157,7 @@
 release
     "remove dependencies
     "
-    renderer release.
+    listRenderer release.
 
     self listHolder removeDependent:self.
     self list       removeDependent:self.
@@ -1163,7 +1174,7 @@
 !
 
 startOfLinesY
-    "returns a collection of absolute Y-positions per line. 
+    "returns a collection of absolute Y-positions per line.
      The first entry is the top Y inset.
      The size of the list is one more than the lists size,
      providing the Y-position of the line below the contents as its last entry."
@@ -1191,7 +1202,7 @@
     cash := self startOfLinesY.
 
     (y := cash at:aLineNr ifAbsent:nil) notNil ifTrue:[
-        ^ y
+	^ y
     ].
 
     "/ recompute a y position
@@ -1224,10 +1235,10 @@
     cache := self startOfLinesY.
 
     (size := cache size) < 2 ifTrue:[
-        "/ empty list
-        (yAbs between:textStartTop and:textStartTop+16) ifTrue:[^ 1].
-        ^ nil
-    ].   
+	"/ empty list
+	(yAbs between:textStartTop and:textStartTop+16) ifTrue:[^ 1].
+	^ nil
+    ].
 
     yCache := cache at:size ifAbsent:nil.
     yCache isNil ifTrue:[ ^ nil ].    "/ out of list
@@ -1235,34 +1246,34 @@
     yRun := yCache.
 
     yAbs >= yRun ifTrue:[
-        yAbs == yRun ifTrue:[ ^ size - 1].
-        ^ nil   "/ out of list
+	yAbs == yRun ifTrue:[ ^ size - 1].
+	^ nil   "/ out of list
     ].
 
     constantHeight notNil ifTrue:[
-        yAbs := yAbs - (cache at:1).
-        yAbs < constantHeight ifTrue:[ ^ 1 ].
-        ^ yAbs // constantHeight + 1
+	yAbs := yAbs - (cache at:1).
+	yAbs < constantHeight ifTrue:[ ^ 1 ].
+	^ yAbs // constantHeight + 1
     ].
 
     ictr := yAbs // (cache at:2).
     ictr < 1 ifTrue:[ ictr := 1 ]
-            ifFalse:[ ictr := ictr min:size ].
+	    ifFalse:[ ictr := ictr min:size ].
 
     yRun := cache at:ictr.
 
     yRun > yAbs ifTrue:[
-        [(ictr := ictr - 1) > 0 ] whileTrue:[
-            yRun := cache at:ictr.
-            yRun <= yAbs ifTrue:[ ^ ictr ].
-        ].
-        ^ 1
+	[(ictr := ictr - 1) > 0 ] whileTrue:[
+	    yRun := cache at:ictr.
+	    yRun <= yAbs ifTrue:[ ^ ictr ].
+	].
+	^ 1
     ].
 
     [ yRun ~~ yAbs ] whileTrue:[
-        ictr := ictr + 1.
-        yRun := cache at:ictr.
-        yRun > yAbs ifTrue:[ ^ ictr - 1 ].
+	ictr := ictr + 1.
+	yRun := cache at:ictr.
+	yRun > yAbs ifTrue:[ ^ ictr - 1 ].
     ].
     ^ ictr
 !
@@ -1294,7 +1305,7 @@
 lineHeightFor:anItem
     "returns the computed line height for an item
     "
-    ^ lineSpacing + (renderer heightFor:anItem)
+    ^ lineSpacing + (listRenderer heightFor:anItem)
 !
 
 listSizeChanged:anIndex nLines:noLines
@@ -1311,21 +1322,21 @@
 
     cachedPreferredExtent := nil.
     widthOfContents isNil ifTrue:[      "/ recompute whole list
-        ^ self
+	^ self
     ].
 
     (noLines < 0 or:[(size := self size) <= noLines]) ifTrue:[
-        widthOfContents := nil.         "/ force recompute whole list
-        ^ self
+	widthOfContents := nil.         "/ force recompute whole list
+	^ self
     ].
 
     stop  := anIndex + noLines - 1.     "/ recompute a range
     start := anIndex.
 
     computeWidthInRange notNil ifTrue:[
-        start := computeWidthInRange y.
-        stop  <  start ifTrue:[stop := start min:size].
-        start := (computeWidthInRange x) min:anIndex.
+	start := computeWidthInRange y.
+	stop  <  start ifTrue:[stop := start min:size].
+	start := (computeWidthInRange x) min:anIndex.
     ].
     computeWidthInRange := start@stop
 !
@@ -1334,9 +1345,9 @@
     "called when the changes derived from the model are faster than the handling
     "
     shown ifTrue:[
-        self recomputeHeightOfContents.
-        self invalidate.
-        self contentsChanged
+	self recomputeHeightOfContents.
+	self invalidate.
+	self contentsChanged
     ].
 !
 
@@ -1351,17 +1362,17 @@
     "
     |item width|
 
-    width := renderer widthOfWidestLineBetween:firstLine and:lastLine.
+    width := listRenderer widthOfWidestLineBetween:firstLine and:lastLine.
     width notNil ifTrue:[^ width].
 
     width := textStartLeft.
 
     firstLine to:lastLine do:[:anIndex|
-        item := self at:anIndex ifAbsent:nil.
-
-        item isNil ifTrue:[^ width + textStartLeft].
-
-        width := (renderer widthFor:item) max:width
+	item := self at:anIndex ifAbsent:nil.
+
+	item isNil ifTrue:[^ width + textStartLeft].
+
+	width := (listRenderer widthFor:item) max:width
     ].
     ^ width + textStartLeft
 ! !
@@ -1393,8 +1404,8 @@
     y := self yVisibleOfLine:aLineNr.
 
     (y between:0 and:height) ifTrue:[
-        y := self yVisibleOfLine:(aLineNr + 1).
-        y <= height ifTrue:[^ true ].
+	y := self yVisibleOfLine:(aLineNr + 1).
+	y <= height ifTrue:[^ true ].
     ].
     ^ false
 !
@@ -1414,17 +1425,17 @@
 
     "/ If I have an explicit preferredExtent..
     explicitExtent notNil ifTrue:[
-        ^ explicitExtent
+	^ explicitExtent
     ].
 
     "/ If I have a cached preferredExtent value..
     preferredExtent notNil ifTrue:[
-        ^ preferredExtent
+	^ preferredExtent
     ].
     cachedPreferredExtent isNil ifTrue:[
-        y := self heightOfContents.
-        x := self widthOfContents.
-        cachedPreferredExtent := x@y
+	y := self heightOfContents.
+	x := self widthOfContents.
+	cachedPreferredExtent := x@y
     ].
     ^ cachedPreferredExtent
 !
@@ -1433,7 +1444,7 @@
     "recompute all the y positions
     "
     |newList
-     yAbs "{ Class: SmallInteger }" 
+     yAbs "{ Class: SmallInteger }"
      size "{ Class: SmallInteger }"|
 
     yAbs    := (textStartTop + margin).   "/ top inset of first line
@@ -1442,16 +1453,16 @@
     newList add:yAbs.
 
     size ~~ 0 ifTrue:[
-        hasConstantHeight ifTrue:[
-            constantHeight isNil ifTrue:[ constantHeight := self heightOfAnyNonNilItem ].
-        ].
-        
-        1 to:size do:[:anIndex|
-            yAbs := yAbs + (constantHeight notNil 
-                                ifTrue:[constantHeight] 
-                                ifFalse:[self realHeightOfLineAt:anIndex]).
-            newList add:yAbs
-        ].
+	hasConstantHeight ifTrue:[
+	    constantHeight isNil ifTrue:[ constantHeight := self heightOfAnyNonNilItem ].
+	].
+
+	1 to:size do:[:anIndex|
+	    yAbs := yAbs + (constantHeight notNil
+				ifTrue:[constantHeight]
+				ifFalse:[self realHeightOfLineAt:anIndex]).
+	    newList add:yAbs
+	].
     ].
     startOfLinesY := newList.
     cachedPreferredExtent := nil.
@@ -1483,10 +1494,10 @@
     "returns the height of a line at an index (including lineSpacing...)"
 
     hasConstantHeight ifTrue:[
-        constantHeight isNil ifTrue:[ 
-            constantHeight := self heightOfAnyNonNilItem.
-        ].
-        ^ constantHeight
+	constantHeight isNil ifTrue:[
+	    constantHeight := self heightOfAnyNonNilItem.
+	].
+	^ constantHeight
     ].
     ^ self realHeightOfLineAt:aLineNr
 !
@@ -1520,7 +1531,7 @@
 
     item := self at:aLineNr ifAbsent:nil.
     item notNil ifTrue:[
-        ^ self lineHeightFor:item
+	^ self lineHeightFor:item
     ].
     ^ font height "arbitrary"
 !
@@ -1536,7 +1547,7 @@
 !
 
 viewOrigin
-    "return the viewOrigin; thats the coordinate of the contents 
+    "return the viewOrigin; thats the coordinate of the contents
      which is shown topLeft in the view.
     "
     ^ viewOrigin
@@ -1552,7 +1563,7 @@
      stop  "{ Class:SmallInteger }"
     |
     (widthOfContents notNil and:[computeWidthInRange isNil]) ifTrue:[
-        ^ widthOfContents + textStartLeft
+	^ widthOfContents + textStartLeft
     ].
     range               := computeWidthInRange.
     computeWidthInRange := nil.
@@ -1564,22 +1575,22 @@
     size := self size.
 
     size == 0 ifTrue:[
-        widthOfContents := 20.
+	widthOfContents := 20.
     ] ifFalse:[
-        widthOfContents isNil ifTrue:[
-            widthOfContents := self widthOfWidestLineBetween:1 and:size
-        ] ifFalse:[
-            start := range x.
-            stop  := range y min:size.
-
-            start > stop ifFalse:[
-                size := self widthOfWidestLineBetween:start and:stop.
-
-                widthOfContents < size ifTrue:[
-                    widthOfContents := size
-                ]
-            ]
-        ]
+	widthOfContents isNil ifTrue:[
+	    widthOfContents := self widthOfWidestLineBetween:1 and:size
+	] ifFalse:[
+	    start := range x.
+	    stop  := range y min:size.
+
+	    start > stop ifFalse:[
+		size := self widthOfWidestLineBetween:start and:stop.
+
+		widthOfContents < size ifTrue:[
+		    widthOfContents := size
+		]
+	    ]
+	]
     ].
     ^ widthOfContents + textStartLeft
 !
@@ -1587,7 +1598,7 @@
 xOriginOfContents
     "return the horizontal origin of the contents in pixels
     "
-    ^ viewOrigin x 
+    ^ viewOrigin x
 
 !
 
@@ -1618,7 +1629,7 @@
     "make the line visible
     "
     aLnNr notNil ifTrue:[
-        self scrollToLine:aLnNr
+	self scrollToLine:aLnNr
     ].
 !
 
@@ -1641,7 +1652,7 @@
     |
 
     realized ifFalse:[
-        ^ self
+	^ self
     ].
 
     innerWT := self innerWidth.
@@ -1650,15 +1661,15 @@
     h := viewOrigin y.
 
     (y := anOrigin y) > h ifTrue:[              "/ end of contents
-        y > (dY := self maxViewOriginY) ifTrue:[
-            y := dY max:h
-        ]
+	y > (dY := self maxViewOriginY) ifTrue:[
+	    y := dY max:h
+	]
     ] ifFalse:[
-        y := y max:0.
+	y := y max:0.
     ].
 
     (x := anOrigin x) > 0 ifTrue:[
-        x := x min:(self widthOfContents - innerWT).
+	x := x min:(self widthOfContents - innerWT).
     ].
     x      := x max:0.
     newOrg := (x @ y).
@@ -1667,7 +1678,7 @@
     dY     := dltOrg y.
 
     (dX == 0 and:[dY == 0]) ifTrue:[
-        ^ self
+	^ self
     ].
     dY := dY abs.
     dX := dX abs.
@@ -1675,52 +1686,52 @@
     (   (dX ~~ 0 and:[dY ~~ 0])                         "/ scroll vertical & horizontal
      or:[(innerHG - dY < 20 or:[innerWT - dX < 20])]    "/ faster to invalidate screen
     ) ifTrue:[
-        viewOrigin := newOrg.
-        self originChanged:dltOrg.
-        self invalidate.
-        ^ self
+	viewOrigin := newOrg.
+	self originChanged:dltOrg.
+	self invalidate.
+	^ self
     ].
 
     (winGrp := self windowGroup) notNil ifTrue:[
-        winGrp processRealExposeEventsFor:self.
+	winGrp processRealExposeEventsFor:self.
     ].
 
     self originWillChange.
 
     doRedraw ifFalse:[
-        viewOrigin := newOrg.
-        self originChanged:dltOrg.
-        ^ self 
+	viewOrigin := newOrg.
+	self originChanged:dltOrg.
+	^ self
     ].
 
     self catchExpose.
     viewOrigin := newOrg.
 
     dY ~~ 0 ifTrue:[                            "/ SCROLL VERTICAL
-        y0 := y1 := margin + dY.
-        h  := innerHG - dY.
-
-        dltOrg y < 0 ifTrue:[y0 := margin. y := y0]
-                    ifFalse:[y1 := margin. y := y1 + h].
-
-        self copyFrom:self x:margin y:y0 toX:margin y:y1 width:innerWT height:h async:true.
-        self invalidateX:margin y:y width:innerWT height:(innerHG - h).
+	y0 := y1 := margin + dY.
+	h  := innerHG - dY.
+
+	dltOrg y < 0 ifTrue:[y0 := margin. y := y0]
+		    ifFalse:[y1 := margin. y := y1 + h].
+
+	self copyFrom:self x:margin y:y0 toX:margin y:y1 width:innerWT height:h async:true.
+	self invalidateX:margin y:y width:innerWT height:(innerHG - h).
 
     ] ifFalse:[                                 "/ SCROLL HORIZONTAL
-        x0 := x1 := dX + margin.
-        w  := innerWT - dX.
-
-        dltOrg x < 0 ifTrue:[x0 := x := margin ]
-                    ifFalse:[x1 := margin. x := w].
-
-        self copyFrom:self x:x0 y:margin toX:x1 y:margin width:w height:innerHG async:true.
-        self invalidateX:x y:margin width:(width - w) height:innerHG.
+	x0 := x1 := dX + margin.
+	w  := innerWT - dX.
+
+	dltOrg x < 0 ifTrue:[x0 := x := margin ]
+		    ifFalse:[x1 := margin. x := w].
+
+	self copyFrom:self x:x0 y:margin toX:x1 y:margin width:w height:innerHG async:true.
+	self invalidateX:x y:margin width:(width - w) height:innerHG.
     ].
     self originChanged:dltOrg.
     self waitForExpose.
 
     winGrp notNil ifTrue:[
-        winGrp processRealExposeEventsFor:self.
+	winGrp processRealExposeEventsFor:self.
     ].
 !
 
@@ -1733,7 +1744,7 @@
      yBot "{ Class:SmallInteger }"
     |
     (shown and:[aLineNumber notNil and:[aLineNumber between:1 and:(self size)]]) ifFalse:[
-        ^ self
+	^ self
     ].
 
     yTop := self yAbsoluteOfLine:aLineNumber.
@@ -1741,11 +1752,11 @@
     orgY := viewOrigin y.
 
     yTop > orgY ifTrue:[
-        yBot := self yAbsoluteOfLine:(aLineNumber + 1).
-
-        yBot <= (orgY + inHg) ifTrue:[
-            ^ self
-        ].
+	yBot := self yAbsoluteOfLine:(aLineNumber + 1).
+
+	yBot <= (orgY + inHg) ifTrue:[
+	    ^ self
+	].
     ].
     yTop := (yTop - (inHg // 2)) max:0.
     self scrollTo:(viewOrigin x @ yTop).
@@ -1760,29 +1771,29 @@
     |timeDelta scrollBlock|
 
     autoScroll ifFalse:[
-        self stopAutoScroll.
-        ^ self
+	self stopAutoScroll.
+	^ self
     ].
 
     autoScrollBlock notNil ifTrue:[
-        Processor removeTimedBlock:autoScrollBlock.
+	Processor removeTimedBlock:autoScrollBlock.
     ] ifFalse:[
-        self compressMotionEvents:false.
+	self compressMotionEvents:false.
     ].
 
     timeDelta := 0.5 / (aDistance abs).
 
-    scrollBlock := 
-        [
-            aSelectorOrBlock isSymbol ifTrue:[
-                self perform:aSelectorOrBlock.
-            ] ifFalse:[
-                aSelectorOrBlock value
-            ].
-            autoScrollBlock notNil ifTrue:[
-                Processor addTimedBlock:autoScrollBlock afterSeconds:timeDelta.
-            ]
-        ].
+    scrollBlock :=
+	[
+	    aSelectorOrBlock isSymbol ifTrue:[
+		self perform:aSelectorOrBlock.
+	    ] ifFalse:[
+		aSelectorOrBlock value
+	    ].
+	    autoScrollBlock notNil ifTrue:[
+		Processor addTimedBlock:autoScrollBlock afterSeconds:timeDelta.
+	    ]
+	].
 
     autoScrollBlock := [self sensor pushUserEvent:#value for:scrollBlock].
     Processor addTimedBlock:autoScrollBlock afterSeconds:timeDelta.
@@ -1814,7 +1825,7 @@
     .... SelectionItemRenderer ...
 
     goal:
-        allow the user to redefine the display operation and the dimesion queries
+	allow the user to redefine the display operation and the dimesion queries
 "
 ! !
 
@@ -1853,20 +1864,20 @@
     y0 := yTop.
 
     anItem isHierarchicalItem ifTrue:[
-        anItem displayOn:view x:x0 y:y0 h:h
+	anItem displayOn:view x:x0 y:y0 h:h
     ] ifFalse:[
-        anItem isNil ifTrue:[^ self].
-
-        y0    := y0 - ((self heightFor:anItem) + 1 - h // 2).
-        label := anItem.
-
-        label isImageOrForm ifFalse:[
-            label isNumber ifTrue:[
-                label := label printString
-            ].
-            y0 := y0 + view font ascent
-        ].
-        label displayOn:view x:x0 y:y0
+	anItem isNil ifTrue:[^ self].
+
+	y0    := y0 - ((self heightFor:anItem) + 1 - h // 2).
+	label := anItem.
+
+	label isImageOrForm ifFalse:[
+	    label isNumber ifTrue:[
+		label := label printString
+	    ].
+	    y0 := y0 + view font ascent
+	].
+	label displayOn:view x:x0 y:y0
     ].
 !
 
@@ -1967,17 +1978,17 @@
     minimumRequiredColumnHeight := 0.
 
     aSeqOfColumnSpecs size == 0 ifTrue:[
-        columnDescriptors := #().
+	columnDescriptors := #().
     ] ifFalse:[
-        columnDescriptors := aSeqOfColumnSpecs collect:[:aColumnSpec|
-            ColumnDescriptor dataSetColumnSpec:aColumnSpec
-        ].
-        columnDescriptors keysAndValuesDo:[:colNr :spec|
-            spec columnNumber:colNr.
-
-            minimumRequiredColumnHeight :=
-                    minimumRequiredColumnHeight max:(spec minimumRequiredColumnHeight).
-        ].
+	columnDescriptors := aSeqOfColumnSpecs collect:[:aColumnSpec|
+	    ColumnDescriptor dataSetColumnSpec:aColumnSpec
+	].
+	columnDescriptors keysAndValuesDo:[:colNr :spec|
+	    spec columnNumber:colNr.
+
+	    minimumRequiredColumnHeight :=
+		    minimumRequiredColumnHeight max:(spec minimumRequiredColumnHeight).
+	].
     ].
     hasFixedItemWidth := attributes at:#hasFixedItemWidth ifAbsent:[false].
 
@@ -1989,8 +2000,8 @@
     xSplitbars at:1 put:xOffset.
 
     1 to:numCols do:[:aColNr|
-        xOffset := xOffset + xInset + (self defaultColumnWidthAt:aColNr).
-        xSplitbars at:(aColNr + 1) put:xOffset.
+	xOffset := xOffset + xInset + (self defaultColumnWidthAt:aColNr).
+	xSplitbars at:(aColNr + 1) put:xOffset.
     ].
     self splitbarsChanged
 !
@@ -2027,11 +2038,11 @@
     "answer the color used for drawing separators"
 
     separatorOneDColor isNil ifTrue:[
-        separatorOneDColor := self class separatorOneDColor.
-
-        (view notNil and:[view realized]) ifTrue:[
-            separatorOneDColor := separatorOneDColor onDevice:(view device).
-        ].
+	separatorOneDColor := self class separatorOneDColor.
+
+	(view notNil and:[view realized]) ifTrue:[
+	    separatorOneDColor := separatorOneDColor onDevice:(view device).
+	].
     ].
     ^ separatorOneDColor
 !
@@ -2106,17 +2117,17 @@
     |xOld xNew xPrv deltaX xAbsoluteOfFirstSplitbar|
 
     aSepIndex == 1 ifTrue:[
-        hasFixedItemWidth := true.
-        xPrv := view margin.
+	hasFixedItemWidth := true.
+	xPrv := view margin.
     ] ifFalse:[
-        xPrv := xSplitbars at:(aSepIndex - 1).
+	xPrv := xSplitbars at:(aSepIndex - 1).
     ].
 
     aSepIndex == 1 ifTrue:[
-        hasFixedItemWidth := true.
-        xPrv := view margin.
+	hasFixedItemWidth := true.
+	xPrv := view margin.
     ] ifFalse:[
-        xPrv := xSplitbars at:(aSepIndex - 1).
+	xPrv := xSplitbars at:(aSepIndex - 1).
     ].
     xOld := xSplitbars at:aSepIndex.
     xNew := x max:xPrv.
@@ -2127,48 +2138,48 @@
     xAbsoluteOfFirstSplitbar := xSplitbars at:1.
 
     xSplitbars from:aSepIndex keysAndValuesDo:[:sepIdx :sepX|
-        xSplitbars at:sepIdx put:(sepX + deltaX).
+	xSplitbars at:sepIdx put:(sepX + deltaX).
     ].
     view setWidthOfContents:(xSplitbars last).
 
     view shown ifTrue:[
-        |damage width height orgX|
-
-        view windowGroup processRealExposeEventsFor:self.
-
-        width  := view width.
-        height := view height.
-        orgX   := view viewOrigin x.
-
-        xNew := ((xNew - orgX) max:0) min:width.
-        xOld := ((xOld - orgX) max:0) min:width.
-        xPrv := ((xPrv - orgX) max:0) min:width.
-
-        xOld > xNew ifTrue:[                                    "/ <- copy to left
-            deltaX := xOld - xNew.
-
-            view copyFrom:view x:xOld y:0 toX:xNew y:0
-                    width:(width - xOld) height:height.
-
-            damage := Rectangle left:(width - deltaX) top:0 width:deltaX height:height.
-            view invalidateDeviceRectangle:damage repairNow:false.
-        ] ifFalse:[
-            xOld < xNew ifTrue:[                                "/ -> copy to right
-                view copyFrom:view x:xOld y:0 toX:xNew y:0
-                        width:(width - xNew) height:height.
-            ].
-        ].
-        xNew > xPrv ifTrue:[
-            "/ should not invalidate the items display range..."
-
-            xAbsoluteOfFirstSplitbar := xAbsoluteOfFirstSplitbar - self splitbarInset.
-            xPrv := (xPrv max:xAbsoluteOfFirstSplitbar).
-
-            xNew > xPrv ifTrue:[
-                damage := Rectangle left:xPrv top:0 width:(xNew -xPrv) height:height.
-                view invalidateDeviceRectangle:damage repairNow:false.
-            ].
-        ].
+	|damage width height orgX|
+
+	view windowGroup processRealExposeEventsFor:self.
+
+	width  := view width.
+	height := view height.
+	orgX   := view viewOrigin x.
+
+	xNew := ((xNew - orgX) max:0) min:width.
+	xOld := ((xOld - orgX) max:0) min:width.
+	xPrv := ((xPrv - orgX) max:0) min:width.
+
+	xOld > xNew ifTrue:[                                    "/ <- copy to left
+	    deltaX := xOld - xNew.
+
+	    view copyFrom:view x:xOld y:0 toX:xNew y:0
+		    width:(width - xOld) height:height.
+
+	    damage := Rectangle left:(width - deltaX) top:0 width:deltaX height:height.
+	    view invalidateDeviceRectangle:damage repairNow:false.
+	] ifFalse:[
+	    xOld < xNew ifTrue:[                                "/ -> copy to right
+		view copyFrom:view x:xOld y:0 toX:xNew y:0
+			width:(width - xNew) height:height.
+	    ].
+	].
+	xNew > xPrv ifTrue:[
+	    "/ should not invalidate the items display range..."
+
+	    xAbsoluteOfFirstSplitbar := xAbsoluteOfFirstSplitbar - self splitbarInset.
+	    xPrv := (xPrv max:xAbsoluteOfFirstSplitbar).
+
+	    xNew > xPrv ifTrue:[
+		damage := Rectangle left:xPrv top:0 width:(xNew -xPrv) height:height.
+		view invalidateDeviceRectangle:damage repairNow:false.
+	    ].
+	].
     ].
     view contentsChanged.
 ! !
@@ -2179,19 +2190,19 @@
     "called if the splitbars has changed; recompute the width of contents"
 
     view notNil ifTrue:[
-        |newWidth oldWidth|
-
-        oldWidth := view getWidthOfContents.
-
-        oldWidth notNil ifTrue:[
-            newWidth := xSplitbars last.
-
-            newWidth ~= oldWidth ifTrue:[
-                view setWidthOfContents:newWidth.
-                view contentsChanged.
-            ].
-            view invalidate.
-        ].
+	|newWidth oldWidth|
+
+	oldWidth := view getWidthOfContents.
+
+	oldWidth notNil ifTrue:[
+	    newWidth := xSplitbars last.
+
+	    newWidth ~= oldWidth ifTrue:[
+		view setWidthOfContents:newWidth.
+		view contentsChanged.
+	    ].
+	    view invalidate.
+	].
     ].
 !
 
@@ -2204,7 +2215,7 @@
     super withinUpdateFromListDo:aBlock.
 
     xAbs ~~ xSplitbars last ifTrue:[
-        self splitbarsChanged
+	self splitbarsChanged
     ].
 ! !
 
@@ -2228,68 +2239,68 @@
     xNxt >= xMax ifTrue:[^ self].
 
     view hasSelection ifTrue:[
-        hgFgColor := view hilightForegroundColor.    
-        hgBgColor := view hilightBackgroundColor.
+	hgFgColor := view hilightForegroundColor.
+	hgBgColor := view hilightBackgroundColor.
     ].
-    fgColor := view foregroundColor.    
+    fgColor := view foregroundColor.
     bgColor := view backgroundColor.
     clip    := view clipRect.
 
     clip isNil ifTrue:[
-        clip := Rectangle left:xDmg top:yStart width:wDmg height:(view height - yStart).
+	clip := Rectangle left:xDmg top:yStart width:wDmg height:(view height - yStart).
     ].
     colInset := self splitbarInset.
 
     2 to:numSplitbars do:[:anIndex|
-        |clipLft clipRgt colWdth colDesc|
-
-        xNxt < xMax ifFalse:[^ self].
-
-        x0   := xNxt.
-        xNxt := (xSplitbars at:anIndex) - xTrs.
-        x1   := xNxt.
-
-        "/ workaround due to drawing the selection frame
-        anIndex == numSplitbars ifTrue:[ x1 := x1 + self textStartLeft ].
-
-        colDesc := columnDescriptors at:(anIndex - 1) ifAbsent:[ ^ self ].    "/ can give up...
-        clipLft := x0 max:xDmg.
-        clipRgt := x1 min:xMax.
-        colWdth := x1 - x0.
-
-        (colWdth > 2 and:[clipLft < clipRgt]) ifTrue:[
-            clip := clip copy.
-            clip setLeft:clipLft.
-            clip right:clipRgt.
-            view clippingRectangle:clip.
-            y1 := yStart.
-
-            start to:stop do:[:aRowNr| |recv|
-                y0   := y1.
-                y1   := view yVisibleOfLine:(aRowNr + 1).
-
-                recv := receiver.
-                recv isNil ifTrue:[ recv := view at:aRowNr ifAbsent:nil ].
-
-                recv notNil ifTrue:[
-                    (hgFgColor notNil and:[view isInSelection:aRowNr]) ifTrue:[
-                        shownSelected := true.
-                        view paint:hgFgColor on:hgBgColor
-                    ] ifFalse:[
-                        shownSelected := false.
-                        view paint:fgColor on:bgColor.
-                    ].
-                    colDesc
-                        drawRowAt:aRowNr
-                        shownSelected:shownSelected
-                        receiver:recv
-                        x:x0 + colInset
-                        y:y0
-                        w:colWdth - colInset - colInset
-                        h:(y1 - y0) on:view.
-                ].
-            ].
-        ].
+	|clipLft clipRgt colWdth colDesc|
+
+	xNxt < xMax ifFalse:[^ self].
+
+	x0   := xNxt.
+	xNxt := (xSplitbars at:anIndex) - xTrs.
+	x1   := xNxt.
+
+	"/ workaround due to drawing the selection frame
+	anIndex == numSplitbars ifTrue:[ x1 := x1 + self textStartLeft ].
+
+	colDesc := columnDescriptors at:(anIndex - 1) ifAbsent:[ ^ self ].    "/ can give up...
+	clipLft := x0 max:xDmg.
+	clipRgt := x1 min:xMax.
+	colWdth := x1 - x0.
+
+	(colWdth > 2 and:[clipLft < clipRgt]) ifTrue:[
+	    clip := clip copy.
+	    clip setLeft:clipLft.
+	    clip right:clipRgt.
+	    view clippingRectangle:clip.
+	    y1 := yStart.
+
+	    start to:stop do:[:aRowNr| |recv|
+		y0   := y1.
+		y1   := view yVisibleOfLine:(aRowNr + 1).
+
+		recv := receiver.
+		recv isNil ifTrue:[ recv := view at:aRowNr ifAbsent:nil ].
+
+		recv notNil ifTrue:[
+		    (hgFgColor notNil and:[view isInSelection:aRowNr]) ifTrue:[
+			shownSelected := true.
+			view paint:hgFgColor on:hgBgColor
+		    ] ifFalse:[
+			shownSelected := false.
+			view paint:fgColor on:bgColor.
+		    ].
+		    colDesc
+			drawRowAt:aRowNr
+			shownSelected:shownSelected
+			receiver:recv
+			x:x0 + colInset
+			y:y0
+			w:colWdth - colInset - colInset
+			h:(y1 - y0) on:view.
+		].
+	    ].
+	].
     ].
 !
 
@@ -2310,8 +2321,8 @@
     x0 := x.
 
     self showHorizontalSeparatorsForItem ifFalse:[
-        x0 := x0 max:(self xVisibleOfSplitbarAt:1).
-        x1 <= x0 ifTrue:[^ self].
+	x0 := x0 max:(self xVisibleOfSplitbarAt:1).
+	x1 <= x0 ifTrue:[^ self].
     ].
     clipRec := Rectangle left:x0 top:0 right:x1 bottom:(view height).
 
@@ -2319,8 +2330,8 @@
     view paint:(self separatorOneDColor).
 
     start to:stop do:[:aRowNr|
-        ySep := (view yVisibleOfLine:(aRowNr + 1)) - 1.
-        view displayLineFromX:x0 y:ySep toX:x1 y:ySep.
+	ySep := (view yVisibleOfLine:(aRowNr + 1)) - 1.
+	view displayLineFromX:x0 y:ySep toX:x1 y:ySep.
     ].
 !
 
@@ -2337,34 +2348,34 @@
     y1 := view height.
 
     self showVerticalSplitbarsBelowContents ifFalse:[
-        stop isNil ifTrue:[^ self].
-
-        y1 := y1 min:(view yVisibleOfLine:(stop + 1)).
-        y1 <= y0 ifTrue:[ ^ self ].
+	stop isNil ifTrue:[^ self].
+
+	y1 := y1 min:(view yVisibleOfLine:(stop + 1)).
+	y1 <= y0 ifTrue:[ ^ self ].
     ].
     x1 := x0 + w.
     vX := view viewOrigin x.
 
     xSplitbars keysAndValuesDo:[:anIndex :physY|
-        (self showVerticalSplitbarAt:anIndex) ifTrue:[
-            x := physY - vX.
-            x > x1 ifTrue:[^ self]. "/ can giveup - behind max x1
-
-            anIndex == nrOfSep ifTrue:[
-                "/ workaround due to drawing the selection frame
-                x := x + self textStartLeft
-            ].
-            x >= x0  ifTrue:[
-                clipRec isNil ifTrue:[
-                    "/ first time to setup clipping and colors
-
-                    clipRec := Rectangle left:x0 top:y0 right:x1 bottom:y1.
-                    view clippingRectangle:clipRec.
-                    view paint:(self separatorOneDColor).
-                ].
-                view displayLineFromX:x y:y0 toX:x y:y1.
-            ].
-        ].
+	(self showVerticalSplitbarAt:anIndex) ifTrue:[
+	    x := physY - vX.
+	    x > x1 ifTrue:[^ self]. "/ can giveup - behind max x1
+
+	    anIndex == nrOfSep ifTrue:[
+		"/ workaround due to drawing the selection frame
+		x := x + self textStartLeft
+	    ].
+	    x >= x0  ifTrue:[
+		clipRec isNil ifTrue:[
+		    "/ first time to setup clipping and colors
+
+		    clipRec := Rectangle left:x0 top:y0 right:x1 bottom:y1.
+		    view clippingRectangle:clipRec.
+		    view paint:(self separatorOneDColor).
+		].
+		view displayLineFromX:x y:y0 toX:x y:y1.
+	    ].
+	].
     ].
 !
 
@@ -2374,10 +2385,10 @@
     self drawColumnsFrom:start to:stop x:x y:y w:w.
 
     self showHorizontalSeparators ifTrue:[
-        self drawHorizontalSeparatorsX:x y:y w:w from:start to:stop.
+	self drawHorizontalSeparatorsX:x y:y w:w from:start to:stop.
     ].
     self showVerticalSplitbars ifTrue:[
-        self drawVerticalSplitbarsX:x y:y w:w from:start to:stop.
+	self drawVerticalSplitbarsX:x y:y w:w from:start to:stop.
     ].
 !
 
@@ -2404,14 +2415,14 @@
 
 columnDescriptorsDo:aOneArgBlock
     columnDescriptors size > 0 ifTrue:[
-        columnDescriptors do:aOneArgBlock.
+	columnDescriptors do:aOneArgBlock.
     ].
 !
 
 columnDescriptorsKeysAndValuesDo:aTwoArgBlock
 
     columnDescriptors size > 0 ifTrue:[
-        columnDescriptors keysAndValuesDo:aTwoArgBlock.
+	columnDescriptors keysAndValuesDo:aTwoArgBlock.
     ].
 !
 
@@ -2435,12 +2446,12 @@
     |winGrp|
 
     view notNil ifTrue:[
-        winGrp := view windowGroup.
-
-        winGrp notNil ifTrue:[
-            view enableMotionEvents.
-            winGrp addPreEventHook:self.
-        ].        
+	winGrp := view windowGroup.
+
+	winGrp notNil ifTrue:[
+	    view enableMotionEvents.
+	    winGrp addPreEventHook:self.
+	].
     ].
 !
 
@@ -2450,68 +2461,68 @@
     ev isInputEvent ifFalse:[^ false].
 
     dragOperation notNil ifTrue:[
-        dragOperation value:ev.
-        ^ true
+	dragOperation value:ev.
+	^ true
     ].
 
     (view shown
     and:[ev view == view
     and:[(ev isButtonPressEvent or:[ev isButtonMotionEvent])
     and:[((ev button == 2) or:[ev button == #menu]) not]]]) ifTrue:[
-        |colIndex phyX colX|
-
-        colIndex := self xVisibleToSplitbar:(ev x).
-
-        (colIndex > 0 and:[self showVerticalSplitbarsBelowContents not]) ifTrue:[
-            "/ test whether y is below contents....
-            ev y > (view heightOfContents - view viewOrigin y) ifTrue:[
-                colIndex := 0
-            ].
-        ].
-
-        ev isButtonPressEvent ifTrue:[
-            colIndex < 1 ifTrue:[^ false].
-
-            colX := self xAbsoluteOfSplitbarAt:colIndex.
-            phyX := ev x.
-
-            dragOperation := [:event|
-                event isKeyEvent ifTrue:[
-                    event rawKey == #Escape ifTrue:[
-                        dragOperation := nil.
-                        self moveSplitbarAt:colIndex toAbsoluteX:colX.
-                    ].
-                ] ifFalse:[
-                    event isButtonPressEvent ifTrue:[
-                        dragOperation := nil.
-                        self moveSplitbarAt:colIndex toAbsoluteX:colX.
-                    ].
-                    event isButtonReleaseEvent ifTrue:[
-                        dragOperation := nil.
-                    ].
-                    event isButtonMotionEvent ifTrue:[
-                        (view sensor hasExposeEventFor:nil) ifFalse:[
-                            self
-                                moveSplitbarAt:colIndex
-                                toAbsoluteX:(colX + (event x) - phyX).
-                        ].
-                    ].
-                ].
-            ].
-            ^ true
-        ].
-
-        colIndex == 0 ifTrue:[
-            savedCursor notNil ifTrue:[
-                view cursor:savedCursor.
-                savedCursor := nil.
-            ].
-        ] ifFalse:[
-            savedCursor isNil ifTrue:[
-                savedCursor := view cursor.
-                view cursor:dragCursor.
-            ].
-        ].
+	|colIndex phyX colX|
+
+	colIndex := self xVisibleToSplitbar:(ev x).
+
+	(colIndex > 0 and:[self showVerticalSplitbarsBelowContents not]) ifTrue:[
+	    "/ test whether y is below contents....
+	    ev y > (view heightOfContents - view viewOrigin y) ifTrue:[
+		colIndex := 0
+	    ].
+	].
+
+	ev isButtonPressEvent ifTrue:[
+	    colIndex < 1 ifTrue:[^ false].
+
+	    colX := self xAbsoluteOfSplitbarAt:colIndex.
+	    phyX := ev x.
+
+	    dragOperation := [:event|
+		event isKeyEvent ifTrue:[
+		    event rawKey == #Escape ifTrue:[
+			dragOperation := nil.
+			self moveSplitbarAt:colIndex toAbsoluteX:colX.
+		    ].
+		] ifFalse:[
+		    event isButtonPressEvent ifTrue:[
+			dragOperation := nil.
+			self moveSplitbarAt:colIndex toAbsoluteX:colX.
+		    ].
+		    event isButtonReleaseEvent ifTrue:[
+			dragOperation := nil.
+		    ].
+		    event isButtonMotionEvent ifTrue:[
+			(view sensor hasExposeEventFor:nil) ifFalse:[
+			    self
+				moveSplitbarAt:colIndex
+				toAbsoluteX:(colX + (event x) - phyX).
+			].
+		    ].
+		].
+	    ].
+	    ^ true
+	].
+
+	colIndex == 0 ifTrue:[
+	    savedCursor notNil ifTrue:[
+		view cursor:savedCursor.
+		savedCursor := nil.
+	    ].
+	] ifFalse:[
+	    savedCursor isNil ifTrue:[
+		savedCursor := view cursor.
+		view cursor:dragCursor.
+	    ].
+	].
     ].
     ^ false
 !
@@ -2522,8 +2533,8 @@
     |winGrp|
 
     view notNil ifTrue:[
-        winGrp := view windowGroup.
-        winGrp notNil ifTrue:[ winGrp removePreEventHook:self ].        
+	winGrp := view windowGroup.
+	winGrp notNil ifTrue:[ winGrp removePreEventHook:self ].
     ].
 ! !
 
@@ -2534,7 +2545,7 @@
      setup my default columnDescription"
 
     attributes isNil ifTrue:[
-        attributes := IdentityDictionary new.
+	attributes := IdentityDictionary new.
     ].
     self columnDescriptors:nil.
     super forView:aView.
@@ -2544,13 +2555,13 @@
     "install event hook and enable motion events
     "
     view notNil ifTrue:[
-        dragCursor isNil ifTrue:[
-            dragCursor := self class dragCursor onDevice:(view device).
-        ].
-        separatorOneDColor notNil ifTrue:[
-            separatorOneDColor := separatorOneDColor onDevice:(view device).
-        ].
-        self isDragEnabled ifTrue:[ self addEventHook ].
+	dragCursor isNil ifTrue:[
+	    dragCursor := self class dragCursor onDevice:(view device).
+	].
+	separatorOneDColor notNil ifTrue:[
+	    separatorOneDColor := separatorOneDColor onDevice:(view device).
+	].
+	self isDragEnabled ifTrue:[ self addEventHook ].
     ].
 !
 
@@ -2572,8 +2583,8 @@
 !
 
 showVerticalSplitbarAt:aColIndex
-    aColIndex > 1 ifTrue:[ 
-        ^ (columnDescriptors at:(aColIndex - 1)) showVerticalSplitbar
+    aColIndex > 1 ifTrue:[
+	^ (columnDescriptors at:(aColIndex - 1)) showVerticalSplitbar
     ].
     ^ true
 ! !
@@ -2592,7 +2603,7 @@
     attributes at:#isDragEnabled put:aBoolean.
 
     aBoolean ifTrue:[ self addEventHook ]
-            ifFalse:[ self removeEventHook ].
+	    ifFalse:[ self removeEventHook ].
 ! !
 
 !ListModelView::TableRenderer methodsFor:'queries-dimensions'!
@@ -2627,14 +2638,14 @@
     xStart := view xAbsoluteOfItem:anItem.
 
     hasFixedItemWidth ifFalse:[
-        inset := self splitbarInset.
-        xStop := (anItem widthOn:view) + xStart + inset + inset.
-        xDiff := xStop - xSplitbars first.
-
-        xDiff > 0 ifTrue:[
-            xDiff := xDiff + 10.        "/ add more to have less computation
-            xSplitbars := xSplitbars collect:[:xSep| xSep + xDiff ].
-        ].
+	inset := self splitbarInset.
+	xStop := (anItem widthOn:view) + xStart + inset + inset.
+	xDiff := xStop - xSplitbars first.
+
+	xDiff > 0 ifTrue:[
+	    xDiff := xDiff + 10.        "/ add more to have less computation
+	    xSplitbars := xSplitbars collect:[:xSep| xSep + xDiff ].
+	].
     ].
     ^ xSplitbars last - xStart
 !
@@ -2647,11 +2658,11 @@
     index := columnDescriptors identityIndexOf:aColumn.
 
     index > 0 ifTrue:[
-        (     (x0 := xSplitbars at:index       ifAbsent:nil) notNil
-         and:[(x1 := xSplitbars at:(index + 1) ifAbsent:nil) notNil])
-        ifTrue:[
-            ^ (x1 - x0 - (2 * (self splitbarInset))) max:0
-        ].
+	(     (x0 := xSplitbars at:index       ifAbsent:nil) notNil
+	 and:[(x1 := xSplitbars at:(index + 1) ifAbsent:nil) notNil])
+	ifTrue:[
+	    ^ (x1 - x0 - (2 * (self splitbarInset))) max:0
+	].
     ].
     ^ nil
 !
@@ -2669,10 +2680,10 @@
     |item|
 
     hasFixedItemWidth ifFalse:[
-        firstLine to:lastLine do:[:i|
-            item := view at:i ifAbsent:nil.
-            item notNil ifTrue:[self widthFor:item].
-        ].
+	firstLine to:lastLine do:[:i|
+	    item := view at:i ifAbsent:nil.
+	    item notNil ifTrue:[self widthFor:item].
+	].
     ].
     ^ xSplitbars last
 !
@@ -2694,7 +2705,7 @@
 
     "/ must walk reverse because a column could have a zero width
     xSplitbars keysAndValuesReverseDo:[:index :x|
-        (x between:minX and:maxX) ifTrue:[^ index].
+	(x between:minX and:maxX) ifTrue:[^ index].
     ].
     ^ 0
 !
@@ -2729,7 +2740,7 @@
 
 new
     ClipColumnQuerySignal isNil ifTrue:[
-        ClipColumnQuerySignal := QuerySignal new.
+	ClipColumnQuerySignal := QuerySignal new.
     ].
     ^ self basicNew initialize
 ! !
@@ -2752,9 +2763,9 @@
 dataSetColumnSpec:aDataSetColumnSpec
 
     aDataSetColumnSpec isSequenceable ifTrue:[
-        dataSetColumnSpec := DataSetColumnSpec decodeFromLiteralArray:aDataSetColumnSpec.
+	dataSetColumnSpec := DataSetColumnSpec decodeFromLiteralArray:aDataSetColumnSpec.
     ] ifFalse:[
-        dataSetColumnSpec := aDataSetColumnSpec.
+	dataSetColumnSpec := aDataSetColumnSpec.
     ].
 !
 
@@ -2785,15 +2796,15 @@
     |deviceClipRectangle paint savedPaint label|
 
     isShownSelected ifFalse:[
-        "/ draw the background color if required by spec..
-        paint := self extractBackgroundColorFrom:aReceiver rowNr:aRowNr on:aGC.
-
-        paint notNil ifTrue:[
-            savedPaint := aGC paint.
-            aGC paint:paint.
-            "/ splitbarInset - draw from 0 to width of aGC (is clipped)
-            aGC fillRectangleX:0 y:y width:(aGC width) height:h.
-        ].
+	"/ draw the background color if required by spec..
+	paint := self extractBackgroundColorFrom:aReceiver rowNr:aRowNr on:aGC.
+
+	paint notNil ifTrue:[
+	    savedPaint := aGC paint.
+	    aGC paint:paint.
+	    "/ splitbarInset - draw from 0 to width of aGC (is clipped)
+	    aGC fillRectangleX:0 y:y width:(aGC width) height:h.
+	].
     ].
     w < 5 ifTrue:[ ^ self ].    "/ makes no sense to draw the label
 
@@ -2801,25 +2812,25 @@
     label isEmptyOrNil ifTrue:[^ self].
 
     ClipColumnQuerySignal handle:[:ex|
-        deviceClipRectangle isNil ifTrue:[
-            deviceClipRectangle := aGC clippingRectangleOrNil.
-            aGC clippingRectangle:(Rectangle left:x top:y width:w height:h).
-        ].
-        ex proceedWith:true.
+	deviceClipRectangle isNil ifTrue:[
+	    deviceClipRectangle := aGC clippingRectangleOrNil.
+	    aGC clippingRectangle:(Rectangle left:x top:y width:w height:h).
+	].
+	ex proceedWith:true.
     ] do:[
-        isShownSelected ifFalse:[
-            paint := self extractForegroundColorFrom:aReceiver rowNr:aRowNr on:aGC.
-
-            paint notNil ifTrue:[
-                aGC paint:paint.
-            ] ifFalse:[
-                savedPaint notNil ifTrue:[ aGC paint:savedPaint ].
-            ].        
-        ].
-        self drawObject:label x:x y:y w:w h:h on:aGC.
+	isShownSelected ifFalse:[
+	    paint := self extractForegroundColorFrom:aReceiver rowNr:aRowNr on:aGC.
+
+	    paint notNil ifTrue:[
+		aGC paint:paint.
+	    ] ifFalse:[
+		savedPaint notNil ifTrue:[ aGC paint:savedPaint ].
+	    ].
+	].
+	self drawObject:label x:x y:y w:w h:h on:aGC.
     ].
     deviceClipRectangle notNil ifTrue:[
-        aGC deviceClippingRectangle:deviceClipRectangle.
+	aGC deviceClippingRectangle:deviceClipRectangle.
     ].
 ! !
 
@@ -2829,12 +2840,12 @@
     |color selector|
 
     aReceiver notNil ifTrue:[
-        selector := dataSetColumnSpec backgroundSelector.
-
-        selector notNil ifTrue:[
-            color := aReceiver perform:selector withOptionalArgument:columnNumber and:aRowNr and:aView.
-            color notNil ifTrue:[ ^ color ].
-        ].
+	selector := dataSetColumnSpec backgroundSelector.
+
+	selector notNil ifTrue:[
+	    color := aReceiver perform:selector withOptionalArgument:columnNumber and:aRowNr and:aView.
+	    color notNil ifTrue:[ ^ color ].
+	].
     ].
     ^ dataSetColumnSpec backgroundColor.
 !
@@ -2843,11 +2854,11 @@
     |selector|
 
     aReceiver notNil ifTrue:[
-        selector := dataSetColumnSpec readSelector.
-
-        selector notNil ifTrue:[
-            ^ aReceiver perform:selector withOptionalArgument:columnNumber and:aRowNr and:aView 
-        ].
+	selector := dataSetColumnSpec readSelector.
+
+	selector notNil ifTrue:[
+	    ^ aReceiver perform:selector withOptionalArgument:columnNumber and:aRowNr and:aView
+	].
     ].
     ^ nil
 !
@@ -2856,12 +2867,12 @@
     |color selector|
 
     aReceiver notNil ifTrue:[
-        selector := dataSetColumnSpec foregroundSelector.
-
-        selector notNil ifTrue:[
-            color := aReceiver perform:selector withOptionalArgument:columnNumber and:aRowNr and:aView.
-            color notNil ifTrue:[ ^ color ].
-        ].
+	selector := dataSetColumnSpec foregroundSelector.
+
+	selector notNil ifTrue:[
+	    color := aReceiver perform:selector withOptionalArgument:columnNumber and:aRowNr and:aView.
+	    color notNil ifTrue:[ ^ color ].
+	].
     ].
     ^ dataSetColumnSpec foregroundColor.
 ! !
@@ -2883,15 +2894,15 @@
     align := self alignment.
 
     align ~~ #left ifTrue:[
-        width := anObject widthOn:aGC.
-
-        width < w ifTrue:[
-            align == #right ifTrue:[
-                x0 := x0 + w - width
-            ] ifFalse:[
-                x0 := x0 + ((w - width) // 2)
-            ].
-        ].
+	width := anObject widthOn:aGC.
+
+	width < w ifTrue:[
+	    align == #right ifTrue:[
+		x0 := x0 + w - width
+	    ] ifFalse:[
+		x0 := x0 + ((w - width) // 2)
+	    ].
+	].
     ].
     anObject displayOn:aGC x:x0 y:y.
 !
@@ -2904,9 +2915,9 @@
     height := anImage heightOn:aGC.
 
     height > h ifTrue:[
-        (self queryForClipColumnWithAvailableHeight:h) ifFalse:[
-            ^ height
-        ].
+	(self queryForClipColumnWithAvailableHeight:h) ifFalse:[
+	    ^ height
+	].
     ].
     self alignAndDisplay:anImage x:x y:y w:w on:aGC.
     ^ height
@@ -2920,9 +2931,9 @@
     height := aLabelAndIcon heightOn:aGC.
 
     height > h ifTrue:[
-        (self queryForClipColumnWithAvailableHeight:h) ifFalse:[
-            ^ height
-        ].
+	(self queryForClipColumnWithAvailableHeight:h) ifFalse:[
+	    ^ height
+	].
     ].
 
     self alignAndDisplay:aLabelAndIcon x:x y:(y + aGC font ascent) w:w on:aGC.
@@ -2940,41 +2951,41 @@
     aString isEmptyOrNil ifTrue:[ ^ fontHeight ].
 
     (self queryForClipColumnWithAvailableHeight:h) ifFalse:[
-        ^ fontHeight
+	^ fontHeight
     ].
     dataSetColumnSpec longStringCompression ifTrue:[
-        shortWidth := font widthOf:aString.
-
-        shortWidth <= w ifTrue:[
-            shortedLabel := aString.
-        ] ifFalse:[
-            |dottedString dottedWidth index|
-
-            dottedString := '...'.
-            dottedWidth  := font widthOf:dottedString.
-
-            w < dottedWidth ifTrue:[ ^ fontHeight ].   "/ give up
-
-            index := aString size // 2.
-
-            [   index := index - 1.
-
-                index > 0 ifTrue:[
-                    shortedLabel := (aString copyFirst:index), '...', (aString copyLast:index).
-                    shortWidth   := font widthOf:shortedLabel.
-                ] ifFalse:[
-                    shortedLabel := dottedString.
-                    shortWidth   := dottedWidth.
-                ].
-                shortWidth > w
-            ] whileTrue.
-        ].
+	shortWidth := font widthOf:aString.
+
+	shortWidth <= w ifTrue:[
+	    shortedLabel := aString.
+	] ifFalse:[
+	    |dottedString dottedWidth index|
+
+	    dottedString := '...'.
+	    dottedWidth  := font widthOf:dottedString.
+
+	    w < dottedWidth ifTrue:[ ^ fontHeight ].   "/ give up
+
+	    index := aString size // 2.
+
+	    [   index := index - 1.
+
+		index > 0 ifTrue:[
+		    shortedLabel := (aString copyFirst:index), '...', (aString copyLast:index).
+		    shortWidth   := font widthOf:shortedLabel.
+		] ifFalse:[
+		    shortedLabel := dottedString.
+		    shortWidth   := dottedWidth.
+		].
+		shortWidth > w
+	    ] whileTrue.
+	].
     ] ifFalse:[
-        shortedLabel := aString
+	shortedLabel := aString
     ].
 
     shortedLabel notNil ifTrue:[
-        self alignAndDisplay:shortedLabel x:x y:(y + aGC font ascent) w:w on:aGC.
+	self alignAndDisplay:shortedLabel x:x y:(y + aGC font ascent) w:w on:aGC.
     ].
     ^ fontHeight.
 !
@@ -2989,34 +3000,34 @@
     anObject isEmptyOrNil ifTrue:[ ^ 2 ]. "/ nothing to draw; add 2 pixels
 
     anObject isImage ifTrue:[
-        ^ self displayImage:anObject x:x y:y w:w h:h on:aGC.
+	^ self displayImage:anObject x:x y:y w:w h:h on:aGC.
     ].
     anObject isString ifTrue:[
-        ^ self displayString:anObject x:x y:y w:w h:h on:aGC.
-    ].        
+	^ self displayString:anObject x:x y:y w:w h:h on:aGC.
+    ].
     anObject isSequenceable ifFalse:[
-        "/ not yet handled....
-        anObject class == LabelAndIcon ifTrue:[
-            ^ self displayLabelAndIcon:anObject x:x y:y w:w h:h on:aGC
-        ].
-
-        ^ self displayString:(anObject printString) x:x y:y w:w h:h on:aGC
+	"/ not yet handled....
+	anObject class == LabelAndIcon ifTrue:[
+	    ^ self displayLabelAndIcon:anObject x:x y:y w:w h:h on:aGC
+	].
+
+	^ self displayString:(anObject printString) x:x y:y w:w h:h on:aGC
     ].
 
     totalHeight := 0.
 
     anObject do:[:aSubObj|
-        totalHeight < h ifTrue:[
-            usedHeight := self
-                    drawObject:aSubObj
-                    x:x
-                    y:(y + totalHeight)
-                    w:w
-                    h:(h - totalHeight)
-                    on:aGC.
-
-            totalHeight := totalHeight + usedHeight.
-        ].
+	totalHeight < h ifTrue:[
+	    usedHeight := self
+		    drawObject:aSubObj
+		    x:x
+		    y:(y + totalHeight)
+		    w:w
+		    h:(h - totalHeight)
+		    on:aGC.
+
+	    totalHeight := totalHeight + usedHeight.
+	].
     ].
     ^ (h - totalHeight)
 !
@@ -3024,7 +3035,7 @@
 queryForClipColumnWithAvailableHeight:anAvailableHeight
 
     anAvailableHeight > 8 ifTrue:[
-        ^ (ClipColumnQuerySignal query) == true
+	^ (ClipColumnQuerySignal query) == true
     ].
     ^ false.
 ! !
@@ -3032,7 +3043,7 @@
 !ListModelView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/ListModelView.st,v 1.117 2009-07-20 13:25:27 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/ListModelView.st,v 1.118 2009-08-07 10:50:41 sr Exp $'
 ! !
 
 ListModelView initialize!
--- a/Make.proto	Tue Aug 04 14:15:20 2009 +0200
+++ b/Make.proto	Fri Aug 07 12:50:41 2009 +0200
@@ -1,6 +1,6 @@
-# $Header: /cvs/stx/stx/libwidg2/Make.proto,v 1.139 2009-05-07 12:07:33 stefan Exp $
+# $Header: /cvs/stx/stx/libwidg2/Make.proto,v 1.140 2009-08-07 10:50:41 sr Exp $
 #
-# DO NOT EDIT 
+# DO NOT EDIT
 # automagically generated from the projectDefinition: stx_libwidg2.
 #
 # Warning: once you modify this file, do not rerun
@@ -30,15 +30,15 @@
 
 REQUIRED_SUPPORT_DIRS=
 
-# if your embedded C code requires any system includes, 
-# add the path(es) here:, 
+# if your embedded C code requires any system includes,
+# add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
 LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/libview -I$(INCLUDE_TOP)/stx/libwidg -I$(INCLUDE_TOP)/stx/libview2 -I$(INCLUDE_TOP)/stx/libbasic2 -I$(INCLUDE_TOP)/stx/libbasic
 
 
-# if you need any additional defines for embedded C code, 
-# add them here:, 
+# if you need any additional defines for embedded C code,
+# add them here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALDEFINES=-Dfoo -Dbar -DDEBUG
 LOCALDEFINES=
@@ -63,7 +63,7 @@
 
 all:: preMake classLibRule postMake
 
-pre_objs:: 
+pre_objs::
 
 
 
@@ -128,6 +128,7 @@
 $(OUTDIR)LinkButtonController.$(O) LinkButtonController.$(H): LinkButtonController.st $(INCLUDE_TOP)/stx/libwidg/ButtonController.$(H) $(INCLUDE_TOP)/stx/libview/Controller.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ListEntry.$(O) ListEntry.$(H): ListEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ListModelView.$(O) ListModelView.$(H): ListModelView.st $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/DeviceGraphicsContext.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsContext.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)LicenceBox.$(O) LicenceBox.$(H): LicenceBox.st $(INCLUDE_TOP)/stx/libwidg/DialogBox.$(H) $(INCLUDE_TOP)/stx/libview/ModalBox.$(H) $(INCLUDE_TOP)/stx/libview/StandardSystemView.$(H) $(INCLUDE_TOP)/stx/libview/TopView.$(H) $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/DeviceGraphicsContext.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsContext.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MenuPanel.$(O) MenuPanel.$(H): MenuPanel.st $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/DeviceGraphicsContext.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsContext.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MultipleItemSelectionWidget.$(O) MultipleItemSelectionWidget.$(H): MultipleItemSelectionWidget.st $(INCLUDE_TOP)/stx/libview2/ApplicationModel.$(H) $(INCLUDE_TOP)/stx/libview2/Model.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)NoteBookView.$(O) NoteBookView.$(H): NoteBookView.st $(INCLUDE_TOP)/stx/libview/View.$(H) $(INCLUDE_TOP)/stx/libview/SimpleView.$(H) $(INCLUDE_TOP)/stx/libview/DisplaySurface.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsMedium.$(H) $(INCLUDE_TOP)/stx/libview/DeviceGraphicsContext.$(H) $(INCLUDE_TOP)/stx/libview/GraphicsContext.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -173,4 +174,3 @@
 $(OUTDIR)HierarchicalItemWithLabelAndIconAndValue.$(O) HierarchicalItemWithLabelAndIconAndValue.$(H): HierarchicalItemWithLabelAndIconAndValue.st $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItemWithLabelAndIcon.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItemWithLabel.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
-
--- a/SelectionInListModelView.st	Tue Aug 04 14:15:20 2009 +0200
+++ b/SelectionInListModelView.st	Fri Aug 07 12:50:41 2009 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1999 by eXept Software AG
-              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
@@ -42,13 +42,13 @@
 
     top  := StandardSystemView new; extent:300@300.
     view := ScrollableView for:SelectionInListModelView miniScroller:true
-                        origin:0.0@0.0 corner:1.0@1.0 in:top.
+			origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     view minimumEditorHeight:100.
     view openEditorAction:[:ln :aGC| |f|
-        f := SimpleView in:aGC.
-        f viewBackground:(Color red).
-        f
+	f := SimpleView in:aGC.
+	f viewBackground:(Color red).
+	f
     ].
     view list:list.
     top  open.
@@ -57,7 +57,7 @@
 copyright
 "
  COPYRIGHT (c) 1999 by eXept Software AG
-              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
@@ -77,58 +77,58 @@
 
     [Instance variables:]
 
-        selection               <misc>       the current selection. nil, a number or collection of numbers
-        multipleSelectOk        <Boolean>    allow/disallow multiple selections( default:false )
-        selectOnButtonMenu      <Boolean>    enable/disable selection will change on menu pressed
-
-        buttonReleaseAction     <Action>     called if the mouse button is released
-        buttonMotionAction      <Action>     called during mouse motion with one argument the point
-                                             under the mouse.
-
-        actionBlock             <Block>      action evaluated on single click (0/1/2 arguments)
-        doubleClickActionBlock  <Block>      action evaluated on double click (0/1/2 arguments)
-        selectConditionBlock    <Block>      action evaluated before selection changed (0/1/2 arguments)
-
-        keyActionStyle          <Symbol>     controls how to respond to keyboard selects
-        returnKeyActionStyle    <Symbol>     controls how to respond to return key
-
-        useIndex                <Boolean>    representation of the model selection
-
-        ignoreReselect          <Boolean>    if set, a click on an already selected entry is ignored
-        toggleSelect            <Boolean>    a click on an entry unselects it and vice versa
-
-        highlightMode           <Symbol>     how to draw the selection
-        hilightFgColor          <Color>      foregroundColor of highlighted items       
-        hilightBgColor          <Color>      backgroundColor of highlighted items
-        hilightLevel            <Integer>    level to draw selections (i.e. for 3D effect)
-        hilightFrameColor       <Color>      rectangle around highlighted items
-        hilightStyle            <Boolean>    actions on widget are enabled/disabled
-        strikeOut               <Boolean>    turn on/off strikeOut mode
-
-        dropTarget              <DropTarget> keeps information about the drop operation
-        dropSource              <DropSource> keeps information about the drag operation
-
-        editorView              <View>       editor on current selected item
-        openEditorAction        <Action>     action to get an editor on the current selection from user
-        closeEditorAction       <Action>     action invoked before the editor is closed.
-
-        enterItem               <Item/nil>   item over which the mouse pointer is located
-                                             or nil
-        highlightEnterItem      <Boolean>    enable or disable highlight of enterItem
+	selection               <misc>       the current selection. nil, a number or collection of numbers
+	multipleSelectOk        <Boolean>    allow/disallow multiple selections( default:false )
+	selectOnButtonMenu      <Boolean>    enable/disable selection will change on menu pressed
+
+	buttonReleaseAction     <Action>     called if the mouse button is released
+	buttonMotionAction      <Action>     called during mouse motion with one argument the point
+					     under the mouse.
+
+	actionBlock             <Block>      action evaluated on single click (0/1/2 arguments)
+	doubleClickActionBlock  <Block>      action evaluated on double click (0/1/2 arguments)
+	selectConditionBlock    <Block>      action evaluated before selection changed (0/1/2 arguments)
+
+	keyActionStyle          <Symbol>     controls how to respond to keyboard selects
+	returnKeyActionStyle    <Symbol>     controls how to respond to return key
+
+	useIndex                <Boolean>    representation of the model selection
+
+	ignoreReselect          <Boolean>    if set, a click on an already selected entry is ignored
+	toggleSelect            <Boolean>    a click on an entry unselects it and vice versa
+
+	highlightMode           <Symbol>     how to draw the selection
+	hilightFgColor          <Color>      foregroundColor of highlighted items
+	hilightBgColor          <Color>      backgroundColor of highlighted items
+	hilightLevel            <Integer>    level to draw selections (i.e. for 3D effect)
+	hilightFrameColor       <Color>      rectangle around highlighted items
+	hilightStyle            <Boolean>    actions on widget are enabled/disabled
+	strikeOut               <Boolean>    turn on/off strikeOut mode
+
+	dropTarget              <DropTarget> keeps information about the drop operation
+	dropSource              <DropSource> keeps information about the drag operation
+
+	editorView              <View>       editor on current selected item
+	openEditorAction        <Action>     action to get an editor on the current selection from user
+	closeEditorAction       <Action>     action invoked before the editor is closed.
+
+	enterItem               <Item/nil>   item over which the mouse pointer is located
+					     or nil
+	highlightEnterItem      <Boolean>    enable or disable highlight of enterItem
 
     [author:]
-        Claus Atzkern
+	Claus Atzkern
 
     [see also:]
 
-        ListModelView
-        HierarchicalListView
+	ListModelView
+	HierarchicalListView
 "
 !
 
 examples
 "
-                                                                        [exBegin]
+									[exBegin]
     |top list view|
 
     list := List new.
@@ -136,13 +136,13 @@
     1 to:100 do:[:i| list add:('element: ', i printString) ].
     top  := StandardSystemView new; extent:300@300.
     view := ScrollableView for:SelectionInListModelView miniScroller:true
-                        origin:0.0@0.0 corner:1.0@1.0 in:top.
+			origin:0.0@0.0 corner:1.0@1.0 in:top.
     view list:list.
     top  open.
-                                                                        [exEnd]
-
-
-                                                                        [exBegin]
+									[exEnd]
+
+
+									[exBegin]
     |top list view|
 
     list := List new.
@@ -150,22 +150,22 @@
     1 to:100 do:[:i| list add:('element: ', i printString) ].
     top  := StandardSystemView new; extent:300@300.
     view := ScrollableView for:SelectionInListModelView miniScroller:true
-                        origin:0.0@0.0 corner:1.0@1.0 in:top.
+			origin:0.0@0.0 corner:1.0@1.0 in:top.
     view list:list.
 
     view openEditorAction:[:ln :aGC| |field|
-        field := EditField new.
-        field level:0.
-        field acceptOnLostFocus:true.
-        field acceptAction:[:x| list at:ln put:(field contents) ].
-        field font:(aGC font).
-        field contents:(list at:ln).
-        field
+	field := EditField new.
+	field level:0.
+	field acceptOnLostFocus:true.
+	field acceptAction:[:x| list at:ln put:(field contents) ].
+	field font:(aGC font).
+	field contents:(list at:ln).
+	field
     ].
     top open.
-                                                                        [exEnd]
-
-                                                                        [exBegin]
+									[exEnd]
+
+									[exBegin]
     |top list view item|
 
     list := HierarchicalList new.
@@ -176,12 +176,12 @@
 
     top  := StandardSystemView new; extent:300@300.
     view := ScrollableView for:SelectionInListModelView miniScroller:true
-                        origin:0.0@0.0 corner:1.0@1.0 in:top.
+			origin:0.0@0.0 corner:1.0@1.0 in:top.
 
     view list:list.
     view doubleClickAction:[:i| (list at:i) toggleExpand ].
     top  open.
-                                                                        [exEnd]
+									[exEnd]
 
 "
 ! !
@@ -192,13 +192,13 @@
     "extract values from the styleSheet and cache them in class variables"
 
     <resource: #style   (
-                        #'selection.hilightForegroundColor' #'selection.hilightBackgroundColor'
-                        #'selection.hilightFrameColor'      #'selection.hilightLevel'
-                        #'selection.foregroundColor'        #'selection.backgroundColor'
-                        #'selection.shadowColor'            #'selection.lightColor'
-                        #'selection.font'                   #'selection.hilightStyle'
-                        #'text.foregroundColor'
-                        )>
+			#'selection.hilightForegroundColor' #'selection.hilightBackgroundColor'
+			#'selection.hilightFrameColor'      #'selection.hilightLevel'
+			#'selection.foregroundColor'        #'selection.backgroundColor'
+			#'selection.shadowColor'            #'selection.lightColor'
+			#'selection.font'                   #'selection.hilightStyle'
+			#'text.foregroundColor'
+			)>
 
     DefaultHilightForegroundColor  := StyleSheet colorAt:'selection.hilightForegroundColor'.
     DefaultHilightBackgroundColor  := StyleSheet colorAt:'selection.hilightBackgroundColor'.
@@ -211,7 +211,7 @@
     DefaultLightColor              := StyleSheet colorAt:'selection.lightColor'.
 
     DefaultForegroundColor isNil ifTrue:[
-        DefaultForegroundColor := StyleSheet colorAt:'text.foregroundColor' default:Black
+	DefaultForegroundColor := StyleSheet colorAt:'text.foregroundColor' default:Black
     ].
     "
      self updateStyleCache
@@ -245,9 +245,9 @@
     "get the action block to be performed on select
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     index or item
-        -  2 argument     index or item, self
+	- no argument
+	-  1 argument     index or item
+	-  2 argument     index or item, self
     "
     ^ actionBlock
 !
@@ -256,9 +256,9 @@
     "set the action block to be performed on select
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     index or item
-        -  2 argument     index or item, self
+	- no argument
+	-  1 argument     index or item
+	-  2 argument     index or item, self
     "
     actionBlock := aOneArgAction
 !
@@ -267,9 +267,9 @@
     "get the action block to be performed on doubleclick.
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     selectedIndex
-        -  2 argument     selectedIndex, self
+	- no argument
+	-  1 argument     selectedIndex
+	-  2 argument     selectedIndex, self
     "
     ^ doubleClickActionBlock
 !
@@ -278,9 +278,9 @@
     "set the action block to be performed on doubleclick.
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     selectedIndex
-        -  2 argument     selectedIndex, self
+	- no argument
+	-  1 argument     selectedIndex
+	-  2 argument     selectedIndex, self
     "
     doubleClickActionBlock := aOneArgAction
 !
@@ -288,14 +288,14 @@
 keyActionStyle
     "defines how the view should respond to alpha-keys pressed.
      Possible values are:
-        #select               -> will select next entry starting with that
-                                 character and perform the click-action
-
-        #selectAndDoubleclick -> will select next & perform double-click action
-
-        #pass                 -> will pass key to superclass (i.e. no special treatment)
-
-        nil                   -> will ignore key
+	#select               -> will select next entry starting with that
+				 character and perform the click-action
+
+	#selectAndDoubleclick -> will select next & perform double-click action
+
+	#pass                 -> will pass key to superclass (i.e. no special treatment)
+
+	nil                   -> will ignore key
 
      the default (set in #initialize) is #select
     "
@@ -305,14 +305,14 @@
 keyActionStyle:aSymbol
     "defines how the view should respond to alpha-keys pressed.
      Possible values are:
-        #select               -> will select next entry starting with that
-                                 character and perform the click-action
-
-        #selectAndDoubleclick -> will select next & perform double-click action
-
-        #pass                 -> will pass key to superclass (i.e. no special treatment)
-
-        nil                   -> will ignore key
+	#select               -> will select next entry starting with that
+				 character and perform the click-action
+
+	#selectAndDoubleclick -> will select next & perform double-click action
+
+	#pass                 -> will pass key to superclass (i.e. no special treatment)
+
+	nil                   -> will ignore key
 
      the default (set in #initialize) is #select
     "
@@ -322,13 +322,13 @@
 returnKeyActionStyle
     "defines how the view should respond to a return key pressed.
      Possible values are:
-        #doubleClick          -> perform double-click action
-
-        #pass                 -> will pass key to superclass (i.e. no special treatment)
-
-        nil                   -> will ignore key
-
-     the default (set in #initialize) is #doubleClick 
+	#doubleClick          -> perform double-click action
+
+	#pass                 -> will pass key to superclass (i.e. no special treatment)
+
+	nil                   -> will ignore key
+
+     the default (set in #initialize) is #doubleClick
     "
     ^ returnKeyActionStyle
 !
@@ -336,13 +336,13 @@
 returnKeyActionStyle:aSymbol
     "defines how the view should respond to a return key pressed.
      Possible values are:
-        #doubleClick          -> perform double-click action
-
-        #pass                 -> will pass key to superclass (i.e. no special treatment)
-
-        nil                   -> will ignore key
-
-     the default (set in #initialize) is #doubleClick 
+	#doubleClick          -> perform double-click action
+
+	#pass                 -> will pass key to superclass (i.e. no special treatment)
+
+	nil                   -> will ignore key
+
+     the default (set in #initialize) is #doubleClick
     "
     returnKeyActionStyle := aSymbol
 !
@@ -353,9 +353,9 @@
      returns false
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     index
-        -  2 argument     index, isForAdd
+	- no argument
+	-  1 argument     index
+	-  2 argument     index, isForAdd
     "
     ^ selectConditionBlock
 !
@@ -366,9 +366,9 @@
      returns false.
 
      The arguments to the block are:
-        - no argument
-        -  1 argument     index
-        -  2 argument     index, isForAdd
+	- no argument
+	-  1 argument     index
+	-  2 argument     index, isForAdd
     "
     selectConditionBlock := aOneArgBlock.
 ! !
@@ -385,33 +385,33 @@
     "enable or disable to highlight the item over which the mouse pointer is located
     "
     highlightEnterItem ~~ aBool ifTrue:[
-        highlightEnterItem := aBool.
-        self pointerEntersItem:nil.
-
-        highlightEnterItem ifTrue:[
-            self enableMotionEvents
-        ].
+	highlightEnterItem := aBool.
+	self pointerEntersItem:nil.
+
+	highlightEnterItem ifTrue:[
+	    self enableMotionEvents
+	].
     ].
 !
 
 highlightMode
     "get the mode how to draw a selected line:
-        #line           draw whole line selected
-        #label          draw label selected
-        #dropMode       set during drop
+	#line           draw whole line selected
+	#label          draw label selected
+	#dropMode       set during drop
     "
     ^ highlightMode
 !
 
 highlightMode:aMode
     "set the mode how to draw a selected line:
-        #line           draw whole line selected
-        #label          draw label selected
-        #dropMode       set during drop
+	#line           draw whole line selected
+	#label          draw label selected
+	#dropMode       set during drop
     "
     highlightMode ~~ aMode ifTrue:[
-        highlightMode := aMode.
-        self invalidateSelection.
+	highlightMode := aMode.
+	self invalidateSelection.
     ].
 !
 
@@ -441,8 +441,8 @@
     "turn on/off strikeOut mode
     "
     strikeOut ~~ aBoolean ifTrue:[
-        strikeOut := aBoolean.
-        self invalidateSelection.
+	strikeOut := aBoolean.
+	self invalidateSelection.
     ].
 ! !
 
@@ -455,7 +455,7 @@
 !
 
 ignoreReselect:aBoolean
-    "set/clear the ignoreReselect flag - 
+    "set/clear the ignoreReselect flag -
      if set, a click on an already selected entry is ignored.
      Otherwise the notification is done, even if no
      change in the selection occurs.
@@ -492,20 +492,20 @@
     multipleSelectOk == state ifTrue:[ ^ self ].
 
     selection isNil ifTrue:[
-        multipleSelectOk := state.
-        ^ self.
+	multipleSelectOk := state.
+	^ self.
     ].
 
     multipleSelectOk ifFalse:[
-        selection := Array with:selection.
-        multipleSelectOk := true.
-        ^ self
+	selection := Array with:selection.
+	multipleSelectOk := true.
+	^ self
     ].
 
     selection size == 1 ifTrue:[
-        selection := selection first.
+	selection := selection first.
     ] ifFalse:[
-        self selection:nil
+	self selection:nil
     ].
     multipleSelectOk := false.
 !
@@ -549,7 +549,7 @@
 !
 
 selectOnButtonPress:aBoolean
-    "set/clear the selectOnButtonPress flag - 
+    "set/clear the selectOnButtonPress flag -
      if set (default), the selection changed on button press. This was the
      behaviour until now.
      if cleared, the selection is changed on button release. This new behaviour allows to start
@@ -565,7 +565,7 @@
      on the current selection."
 
     selectOnMenuButton isNil ifTrue:[
-        ^ UserPreferences current selectOnRightClick
+	^ UserPreferences current selectOnRightClick
     ].
     ^ selectOnMenuButton
 !
@@ -624,10 +624,10 @@
 
     (editor := editorView) notNil ifTrue:[
 "/        editorView := nil.
-        action := self closeEditorAction.
-        action notNil ifTrue:[action value:editor.].
-        editor destroy.
-        editorView := nil.
+	action := self closeEditorAction.
+	action notNil ifTrue:[action value:editor.].
+	editor destroy.
+	editorView := nil.
     ].
 !
 
@@ -686,7 +686,7 @@
     editorView isNil ifTrue:[^ nil].
 
     editorView superView isNil ifTrue:[
-        self addSubView:editorView
+	self addSubView:editorView
     ].
     self computeEditorLayout.
     editorView realize.
@@ -734,7 +734,7 @@
     super lineChangedAt:aLnNr with:arg.
 
     (editorView notNil and:[aLnNr == self selectedIndex]) ifTrue:[
-        self computeEditorLayout.
+	self computeEditorLayout.
     ]
 !
 
@@ -746,57 +746,57 @@
     selection isNil ifTrue:[^ self].
 
     self size == 0 ifTrue:[
-        selection := nil.
-        ^ self selectionChanged
+	selection := nil.
+	^ self selectionChanged
     ].
 
     multipleSelectOk ifFalse:[
-        selection < aLnNr ifTrue:[^ self].
-
-        selection := selection + aDeltaLines.
-
-        (aDeltaLines < 0 and:[selection < aLnNr]) ifTrue:[
-            selection := nil.
-            ^ self selectionChanged
-        ]
+	selection < aLnNr ifTrue:[^ self].
+
+	selection := selection + aDeltaLines.
+
+	(aDeltaLines < 0 and:[selection < aLnNr]) ifTrue:[
+	    selection := nil.
+	    ^ self selectionChanged
+	]
     ] ifTrue:[
-        changed := false.
-
-        aDeltaLines < 0  ifFalse:[
-            selection keysAndValuesDo:[:i :ln|
-                ln >= aLnNr ifTrue:[
-                    changed := true.
-                    selection at:i put:(ln + aDeltaLines)
-                ]
-            ]
-        ] ifTrue:[
-            cnts := 0.
-
-            selection keysAndValuesDo:[:i :ln||new|
-                ln >= aLnNr ifTrue:[
-                    changed := true.
-
-                    (new := ln + aDeltaLines) < aLnNr ifTrue:[
-                        cnts := cnts + 1.
-                        new  := nil
-                    ].
-                    selection at:i put:new
-                ]
-            ].
-            cnts ~~ 0 ifTrue:[
-                cnts == selection size ifTrue:[
-                    selection := nil
-                ] ifFalse:[
-                    selection := selection select:[:ln| ln notNil]
-                ].
-                ^ self selectionChanged.
-            ].
-        ].
-        changed ifFalse:[^ self].
+	changed := false.
+
+	aDeltaLines < 0  ifFalse:[
+	    selection keysAndValuesDo:[:i :ln|
+		ln >= aLnNr ifTrue:[
+		    changed := true.
+		    selection at:i put:(ln + aDeltaLines)
+		]
+	    ]
+	] ifTrue:[
+	    cnts := 0.
+
+	    selection keysAndValuesDo:[:i :ln||new|
+		ln >= aLnNr ifTrue:[
+		    changed := true.
+
+		    (new := ln + aDeltaLines) < aLnNr ifTrue:[
+			cnts := cnts + 1.
+			new  := nil
+		    ].
+		    selection at:i put:new
+		]
+	    ].
+	    cnts ~~ 0 ifTrue:[
+		cnts == selection size ifTrue:[
+		    selection := nil
+		] ifFalse:[
+		    selection := selection select:[:ln| ln notNil]
+		].
+		^ self selectionChanged.
+	    ].
+	].
+	changed ifFalse:[^ self].
     ].
 
     (useIndex and:[model notNil]) ifTrue:[
-        model setValue:(self argForChangeMessage)
+	model setValue:(self argForChangeMessage)
     ].
 !
 
@@ -817,26 +817,26 @@
     self closeEditor.
 
     (model isNil and:[actionBlock isNil]) ifTrue:[
-        ^ self
+	^ self
     ].
 
     arg := self argForChangeMessage.
 
     model notNil ifTrue:[
-        model removeDependent:self.
-        "/ change models value to force a change notification: reselect mode
-        arg = model value ifTrue:[
-            model setValue:(arg isNil ifTrue:[0] ifFalse:[nil]).
-        ].
-        self sendChangeMessage:#value: with:arg.
-        model notNil ifTrue:[  "/ argggh could be nilled
-            model addDependent:self.
-            self updateFromModel. "/ care for possibly lost change notification, due to #removeDependent
-        ]
+	model removeDependent:self.
+	"/ change models value to force a change notification: reselect mode
+	arg = model value ifTrue:[
+	    model setValue:(arg isNil ifTrue:[0] ifFalse:[nil]).
+	].
+	self sendChangeMessage:#value: with:arg.
+	model notNil ifTrue:[  "/ argggh could be nilled
+	    model addDependent:self.
+	    self updateFromModel. "/ care for possibly lost change notification, due to #removeDependent
+	]
     ].
 
     actionBlock notNil ifTrue:[
-        actionBlock valueWithOptionalArgument:arg and:self
+	actionBlock valueWithOptionalArgument:arg and:self
     ].
 !
 
@@ -846,38 +846,38 @@
     |value newSelection|
 
     model isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     buttonMotionAction notNil ifTrue:[
-        "running in button motion; discard change notification
-        "
-        ^ self
+	"running in button motion; discard change notification
+	"
+	^ self
     ].
 
     value := model value.
 
     (useIndex or:[value isNil or:[value isNumber]]) ifFalse:[
-        multipleSelectOk ifFalse:[
-            newSelection := self identityIndexOf:value
-        ] ifTrue:[
-            value size == 0 ifTrue:[
-                newSelection := nil
-            ] ifFalse:[
-                newSelection := OrderedCollection new.
-
-                value do:[:e||index|
-                    index := self identityIndexOf:e.
-                    index ~~ 0 ifTrue:[ newSelection add:index ].
-                ].
-
-                newSelection isEmpty ifTrue:[
-                    newSelection := nil
-                ].
-            ]
-        ].
+	multipleSelectOk ifFalse:[
+	    newSelection := self identityIndexOf:value
+	] ifTrue:[
+	    value size == 0 ifTrue:[
+		newSelection := nil
+	    ] ifFalse:[
+		newSelection := OrderedCollection new.
+
+		value do:[:e||index|
+		    index := self identityIndexOf:e.
+		    index ~~ 0 ifTrue:[ newSelection add:index ].
+		].
+
+		newSelection isEmpty ifTrue:[
+		    newSelection := nil
+		].
+	    ]
+	].
     ] ifTrue:[
-        newSelection := value copy
+	newSelection := value copy
     ].
     self setSelection:newSelection.
 ! !
@@ -903,29 +903,29 @@
     inset    := 15 + margin.
 
     visibleY <= inset ifTrue:[
-        self yOriginOfContents == 0 ifTrue:[ ^ false ].
+	self yOriginOfContents == 0 ifTrue:[ ^ false ].
     ] ifFalse:[
-        visibleY < (self height - inset) ifTrue:[ ^ false ].
-        self yOriginOfContents < self maxViewOriginY ifFalse:[ ^ false ].
+	visibleY < (self height - inset) ifTrue:[ ^ false ].
+	self yOriginOfContents < self maxViewOriginY ifFalse:[ ^ false ].
     ].
 
     aContext contentsWillChange.
 
     visibleY <= inset ifTrue:[ self scrollUp:inset ]
-                     ifFalse:[ self scrollDown:inset ].
+		     ifFalse:[ self scrollDown:inset ].
 
     ^ true
 !
 
 dropSource
     "returns the dropSource or nil"
-    
+
     ^ dropSource
 !
 
-dropSource:aDropSourceOrNil 
+dropSource:aDropSourceOrNil
     "set the dropSource or nil"
-    
+
     dropSource := aDropSourceOrNil.
 !
 
@@ -935,12 +935,12 @@
     buttonMotionAction := buttonReleaseAction := nil.
 
     dropSource notNil ifTrue:[
-        dropSource startDragSelector notNil ifTrue:[
-            ^ dropSource startDragIn:self at:aPoint
-        ] ifFalse:[
-            ^ DragAndDropManager new 
-                startDragFrom:self dropSource:dropSource offset:#center
-        ]
+	dropSource startDragSelector notNil ifTrue:[
+	    ^ dropSource startDragIn:self at:aPoint
+	] ifFalse:[
+	    ^ DragAndDropManager new
+		startDragFrom:self dropSource:dropSource offset:#center
+	]
     ].
     ^ nil
 ! !
@@ -958,9 +958,9 @@
     y1 := y.
 
     start to:stop do:[:i|
-        y0 := y1.
-        y1 := self yVisibleOfLine:(i + 1).
-        self drawLabelAt:i x:x0 y:y0 h:(y1 - y0)
+	y0 := y1.
+	y1 := self yVisibleOfLine:(i + 1).
+	self drawLabelAt:i x:x0 y:y0 h:(y1 - y0)
     ].
 
 
@@ -970,11 +970,11 @@
     "draw the lines between start to stop without clearing the background
     "
     highlightMode notNil ifTrue:[
-        self selectionDo:[:lnNr|
-            (lnNr between:start and:stop) ifTrue:[
-                self drawSelectionFrameAt:lnNr x:x w:w
-            ]
-        ]
+	self selectionDo:[:lnNr|
+	    (lnNr between:start and:stop) ifTrue:[
+		self drawSelectionFrameAt:lnNr x:x w:w
+	    ]
+	]
     ].
     super drawFrom:start to:stop x:x y:y w:w.
 !
@@ -986,8 +986,8 @@
 
     x := xI + 1.
     editorView notNil ifTrue:[
-        "/ there is an open editor for the line; thus no redraw for the label (hidden by editor)
-        self selectedIndex == anIndex ifTrue:[^ self].
+	"/ there is an open editor for the line; thus no redraw for the label (hidden by editor)
+	self selectedIndex == anIndex ifTrue:[^ self].
     ].
 
     item := self at:anIndex ifAbsent:nil.
@@ -996,55 +996,55 @@
     drawStrikeOut := false.
 
     (highlightMode notNil and:[self isInSelection:anIndex]) ifTrue:[
-        strikeOut ifTrue:[
-            drawStrikeOut := true.
-            self paint:fgColor on:bgColor
-        ] ifFalse:[
-            (highlightMode == #dropMode or:[self hasFocus not]) ifTrue:[
-                self paint:hilightFgColorNoFocus on:hilightBgColorNoFocus.
-            ] ifFalse:[
-                self paint:hilightFgColor on:hilightBgColor
-            ].
-        ]
+	strikeOut ifTrue:[
+	    drawStrikeOut := true.
+	    self paint:fgColor on:bgColor
+	] ifFalse:[
+	    (highlightMode == #dropMode or:[self hasFocus not]) ifTrue:[
+		self paint:hilightFgColorNoFocus on:hilightBgColorNoFocus.
+	    ] ifFalse:[
+		self paint:hilightFgColor on:hilightBgColor
+	    ].
+	]
     ] ifFalse:[
-        enterItem == item ifTrue:[
-            self paint:hilightBgColor on:bgColor.
-        ] ifFalse:[
-            self paint:fgColor on:bgColor.
-        ].
+	enterItem == item ifTrue:[
+	    self paint:hilightBgColor on:bgColor.
+	] ifFalse:[
+	    self paint:fgColor on:bgColor.
+	].
     ].
-    renderer display:item atX:x y:y lineHeight:h.
+    listRenderer display:item atX:x y:y lineHeight:h.
 
     drawStrikeOut ifTrue:[
-        xOut0 := self xVisibleOfItem:item.
-        highlightMode == #label ifTrue:[
-            xOut1 := xOut0 + (renderer widthFor:item).
-        ] ifFalse:[
-            xOut1 := width - margin.
-        ].
-        y0 := y + (h // 2).
-        self displayLineFromX:xOut0 y:y0 toX:xOut1 y:y0.
-        y0 := y0 - 1.
-        self displayLineFromX:xOut0 y:y0 toX:xOut1 y:y0.
+	xOut0 := self xVisibleOfItem:item.
+	highlightMode == #label ifTrue:[
+	    xOut1 := xOut0 + (listRenderer widthFor:item).
+	] ifFalse:[
+	    xOut1 := width - margin.
+	].
+	y0 := y + (h // 2).
+	self displayLineFromX:xOut0 y:y0 toX:xOut1 y:y0.
+	y0 := y0 - 1.
+	self displayLineFromX:xOut0 y:y0 toX:xOut1 y:y0.
     ].
 
     cursorItem == item ifTrue:[
-        "/ textStartLeft
-        self maskOrigin:((self viewOrigin + (0 @ 1)) \\ (lineMask extent)).
-        self mask:lineMask.
-        w := renderer widthFor:item.
-        self displayRectangleX:x -1 y:(y+2) width:w+2 height:(h - 4).
-        self mask:nil.
+	"/ textStartLeft
+	self maskOrigin:((self viewOrigin + (0 @ 1)) \\ (lineMask extent)).
+	self mask:lineMask.
+	w := listRenderer widthFor:item.
+	self displayRectangleX:x -1 y:(y+2) width:w+2 height:(h - 4).
+	self mask:nil.
     ] ifFalse:[
-        enterItem == item ifTrue:[
-            self highlightWithUnderline ifTrue:[
-                "/ underline the hilite...
-                y0 := y + h - 2.
-                x1 := x + (renderer widthFor:item).
-
-                self displayLineFromX:x y:y0 toX:x1 y:y0.
-            ]
-        ].
+	enterItem == item ifTrue:[
+	    self highlightWithUnderline ifTrue:[
+		"/ underline the hilite...
+		y0 := y + h - 2.
+		x1 := x + (listRenderer widthFor:item).
+
+		self displayLineFromX:x y:y0 toX:x1 y:y0.
+	    ]
+	].
     ].
 !
 
@@ -1055,23 +1055,23 @@
     |item xMax xLftDmg xRgtDmg x0 x1 y0 y1 hL wL|
 
     (strikeOut or:[highlightMode isNil]) ifTrue:[
-        ^ self
+	^ self
     ].
     editorView notNil ifTrue:[
-        "/ there is an open editor; do not redraw selected
-        ^ self
+	"/ there is an open editor; do not redraw selected
+	^ self
     ].
 
     (    highlightMode == #line
      or:[highlightMode == #label
      or:[highlightMode == #dropMode]]
     ) ifFalse:[
-        "/ highlightMode not supported
-        ^ self
+	"/ highlightMode not supported
+	^ self
     ].
     (item := self at:lnNr ifAbsent:nil) isNil ifTrue:[
-        "/ list might change during drawing; item no longer visible
-        ^ self
+	"/ list might change during drawing; item no longer visible
+	^ self
     ].
     xMax := x + w.
 
@@ -1082,23 +1082,23 @@
     hL := y1 - y0.
 
     highlightMode == #line ifTrue:[
-        x0 := x.
-        x1 := xMax.
+	x0 := x.
+	x1 := xMax.
     ] ifFalse:[ "/ is #label or #rectangle
-        x0 := (self xVisibleOfItem:item) - (textStartLeft // 2).
-        x0 >= xMax ifTrue:[ ^ self ].
-
-        x1 := x0 + (renderer widthFor:item) + textStartLeft + 1.
-        x1 < x ifTrue:[ ^ self ].
+	x0 := (self xVisibleOfItem:item) - (textStartLeft // 2).
+	x0 >= xMax ifTrue:[ ^ self ].
+
+	x1 := x0 + (listRenderer widthFor:item) + textStartLeft + 1.
+	x1 < x ifTrue:[ ^ self ].
     ].
     xLftDmg := x0 max:x.
     xRgtDmg := x1 min:xMax.
     xRgtDmg > xLftDmg ifFalse:[^ self].
 
     (highlightMode == #dropMode or:[self hasFocus not]) ifTrue:[
-        self paint:hilightBgColorNoFocus.
+	self paint:hilightBgColorNoFocus.
     ] ifFalse:[
-        self paint:hilightBgColor.
+	self paint:hilightBgColor.
     ].
     self fillRectangleX:xLftDmg y:y0 width:(xRgtDmg - xLftDmg) height:hL.
     wL := x1 - x0.
@@ -1106,37 +1106,37 @@
     "/ DRAW THE FRAME
 
     hilightFrameColor notNil ifTrue:[
-        hilightLevel == 0 ifTrue:[
-            self paint:hilightFrameColor.
-
-            highlightMode == #line ifTrue:[
-                self displayLineFromX:x0 y:y0 toX:x1 y:y0.
-                y1 := y0 + hL - 1.
-                self displayLineFromX:x0 y:y1 toX:x1 y:y1.
-            ] ifFalse:[
-                self displayRectangleX:x0 y:y0 width:wL height:hL
-            ].
-            ^ self.
-        ]
+	hilightLevel == 0 ifTrue:[
+	    self paint:hilightFrameColor.
+
+	    highlightMode == #line ifTrue:[
+		self displayLineFromX:x0 y:y0 toX:x1 y:y0.
+		y1 := y0 + hL - 1.
+		self displayLineFromX:x0 y:y1 toX:x1 y:y1.
+	    ] ifFalse:[
+		self displayRectangleX:x0 y:y0 width:wL height:hL
+	    ].
+	    ^ self.
+	]
     ] ifFalse:[
-        hilightStyle == #motif ifTrue:[
-            self paint:bgColor.
-            y1 := y0 + 1.
-            highlightMode == #line ifTrue:[
-                self displayLineFromX:x0 y:y1 toX:x1 y:y1.
-                y1 := y0 + hL - 2.
-                self displayLineFromX:x0 y:y1 toX:x1 y:y1.
-            ] ifFalse:[
-                self displayRectangleX:x0 + 1 y:y1 width:wL - 2 height:hL - 2
-            ]
-        ].
-        hilightLevel == 0 ifTrue:[ ^ self ].
+	hilightStyle == #motif ifTrue:[
+	    self paint:bgColor.
+	    y1 := y0 + 1.
+	    highlightMode == #line ifTrue:[
+		self displayLineFromX:x0 y:y1 toX:x1 y:y1.
+		y1 := y0 + hL - 2.
+		self displayLineFromX:x0 y:y1 toX:x1 y:y1.
+	    ] ifFalse:[
+		self displayRectangleX:x0 + 1 y:y1 width:wL - 2 height:hL - 2
+	    ]
+	].
+	hilightLevel == 0 ifTrue:[ ^ self ].
     ].
 
     "/ draw edge
     highlightMode == #line ifTrue:[
-        x0 := margin.
-        wL := width - x0 - x0.
+	x0 := margin.
+	wL := width - x0 - x0.
     ].
     self drawEdgesForX:x0 y:y0 width:wL height:hL level:hilightLevel.
 !
@@ -1145,9 +1145,9 @@
     "invalidate the current selection
     "
     shown ifTrue:[
-        self selectionDo:[:aLnNr|
-            self invalidateLineAt:aLnNr
-        ].
+	self selectionDo:[:aLnNr|
+	    self invalidateLineAt:aLnNr
+	].
     ].
 !
 
@@ -1158,23 +1158,23 @@
     |item x|
 
     editorView notNil ifTrue:[
-        "/ there is an open editor; do not redraw selected
-        ^ self
+	"/ there is an open editor; do not redraw selected
+	^ self
     ].
 
     (shown and:[aLineNr notNil and:[highlightMode notNil]]) ifFalse:[
-        ^ self
+	^ self
     ].
 
     highlightMode == #label ifTrue:[
-        item := self at:aLineNr ifAbsent:nil.
-
-        item isNil ifTrue:[
-            ^ self
-        ].
-        x := (self xVisibleOfItem:item) - (textStartLeft // 2)
+	item := self at:aLineNr ifAbsent:nil.
+
+	item isNil ifTrue:[
+	    ^ self
+	].
+	x := (self xVisibleOfItem:item) - (textStartLeft // 2)
     ] ifFalse:[
-        x := 0.
+	x := 0.
     ].
     self invalidateLineAt:aLineNr fromX:x
 ! !
@@ -1189,24 +1189,24 @@
     isInSelection := self isInSelection:lineNr.
 
     multipleSelectOk ifFalse:[
-        isInSelection ifTrue:[
-            self deselect
-        ]ifFalse:[
-            (self canSelectIndex:lineNr forAdd:false) ifTrue:[
-                self buttonPressOrReleaseAtLine:lineNr x:x y:y.
-            ].
-        ].
-        ^ self
+	isInSelection ifTrue:[
+	    self deselect
+	]ifFalse:[
+	    (self canSelectIndex:lineNr forAdd:false) ifTrue:[
+		self buttonPressOrReleaseAtLine:lineNr x:x y:y.
+	    ].
+	].
+	^ self
     ].
     isInSelection ifTrue:[
-        self removeFromSelection:lineNr
+	self removeFromSelection:lineNr
     ] ifFalse:[
-        self addToSelection:lineNr.
-
-        (self isInSelection:lineNr) ifFalse:[
-            "/ cannot add to selection
-            ^ self
-        ].
+	self addToSelection:lineNr.
+
+	(self isInSelection:lineNr) ifFalse:[
+	    "/ cannot add to selection
+	    ^ self
+	].
     ].
 
     prvLine := lineNr.
@@ -1214,38 +1214,38 @@
     doAdd   := isInSelection not.
 
     buttonMotionAction := [:p| |rowNr mustRestore step f|
-        rowNr := self yVisibleToLineNr:(p y).
-
-        (rowNr notNil and:[rowNr ~~ prvLine]) ifTrue:[
-            rowNr == lineNr ifTrue:[
-                mustRestore := true
-            ] ifFalse:[
-                rowNr > lineNr ifTrue:[ mustRestore := (rowNr < prvLine) ]
-                              ifFalse:[ mustRestore := (rowNr > prvLine) ].
-            ].
-            prvLine > rowNr ifTrue:[ step := -1 ]
-                          ifFalse:[ step :=  1 ].
-            mustRestore ifTrue:[
-                [ prvLine ~~ rowNr ] whileTrue:[
-                    (chgSet removeIdentical:prvLine ifAbsent:nil) notNil ifTrue:[
-                        doAdd ifFalse:[ self addToSelection:prvLine ]
-                               ifTrue:[ self removeFromSelection:prvLine ].
-                    ].
-                    prvLine := prvLine + step.
-                ].
-            ] ifFalse:[
-                [ prvLine ~~ rowNr ] whileTrue:[
-                    prvLine := prvLine + step.
-
-                    doAdd ~~ (self isInSelection:rowNr) ifTrue:[
-                        chgSet add:prvLine.
-
-                        doAdd ifTrue:[ self addToSelection:prvLine ]
-                             ifFalse:[ self removeFromSelection:prvLine ].
-                    ]
-                ].
-            ].
-        ].
+	rowNr := self yVisibleToLineNr:(p y).
+
+	(rowNr notNil and:[rowNr ~~ prvLine]) ifTrue:[
+	    rowNr == lineNr ifTrue:[
+		mustRestore := true
+	    ] ifFalse:[
+		rowNr > lineNr ifTrue:[ mustRestore := (rowNr < prvLine) ]
+			      ifFalse:[ mustRestore := (rowNr > prvLine) ].
+	    ].
+	    prvLine > rowNr ifTrue:[ step := -1 ]
+			  ifFalse:[ step :=  1 ].
+	    mustRestore ifTrue:[
+		[ prvLine ~~ rowNr ] whileTrue:[
+		    (chgSet removeIdentical:prvLine ifAbsent:nil) notNil ifTrue:[
+			doAdd ifFalse:[ self addToSelection:prvLine ]
+			       ifTrue:[ self removeFromSelection:prvLine ].
+		    ].
+		    prvLine := prvLine + step.
+		].
+	    ] ifFalse:[
+		[ prvLine ~~ rowNr ] whileTrue:[
+		    prvLine := prvLine + step.
+
+		    doAdd ~~ (self isInSelection:rowNr) ifTrue:[
+			chgSet add:prvLine.
+
+			doAdd ifTrue:[ self addToSelection:prvLine ]
+			     ifFalse:[ self removeFromSelection:prvLine ].
+		    ]
+		].
+	    ].
+	].
     ].
 !
 
@@ -1257,28 +1257,28 @@
     self stopAutoScroll.
 
     (buttonMask ~~ 0 and:[buttonMotionAction notNil]) ifTrue:[
-        buttonMotionAction value:(x@y).
-
-        (autoScroll and:[buttonMotionAction notNil]) ifTrue:[
-            "/ if moved outside of view, start autoscroll
-            (y between:0 and:height) ifFalse:[
-                y < 0 ifTrue:[ self startAutoScroll:#scrollUp distance:y ]
-                     ifFalse:[ self startAutoScroll:#scrollDown distance:(y - height) ].
-            ].
-        ].
-        ^ self
+	buttonMotionAction value:(x@y).
+
+	(autoScroll and:[buttonMotionAction notNil]) ifTrue:[
+	    "/ if moved outside of view, start autoscroll
+	    (y between:0 and:height) ifFalse:[
+		y < 0 ifTrue:[ self startAutoScroll:#scrollUp distance:y ]
+		     ifFalse:[ self startAutoScroll:#scrollDown distance:(y - height) ].
+	    ].
+	].
+	^ self
     ].
 
     (enabled and:[highlightEnterItem]) ifTrue:[
-        self sensor anyButtonPressed ifFalse:[
-            lnNr := self yVisibleToLineNr:y.
-
-            lnNr notNil ifTrue:[ item := self at:lnNr ifAbsent:nil ]
-                       ifFalse:[ item := nil ].
-
-            self pointerEntersItem:item.
-        ]
-    ].    
+	self sensor anyButtonPressed ifFalse:[
+	    lnNr := self yVisibleToLineNr:y.
+
+	    lnNr notNil ifTrue:[ item := self at:lnNr ifAbsent:nil ]
+		       ifFalse:[ item := nil ].
+
+	    self pointerEntersItem:item.
+	]
+    ].
 !
 
 buttonMultiPress:button x:x y:y
@@ -1291,14 +1291,14 @@
     enabled ifFalse:[^ self].
 
     ((button == 1) or:[button == #select]) ifTrue:[
-        doubleClickActionBlock notNil ifTrue:[
-            (     (lnNr := self yVisibleToLineNr:y)   notNil
-             and:[(item := self at:lnNr ifAbsent:nil) notNil]
-            ) ifTrue:[
-                doubleClickActionBlock valueWithOptionalArgument:lnNr and:self.
-            ].
-        ].
-        ^ self.
+	doubleClickActionBlock notNil ifTrue:[
+	    (     (lnNr := self yVisibleToLineNr:y)   notNil
+	     and:[(item := self at:lnNr ifAbsent:nil) notNil]
+	    ) ifTrue:[
+		doubleClickActionBlock valueWithOptionalArgument:lnNr and:self.
+	    ].
+	].
+	^ self.
     ].
 
     super buttonMultiPress:button x:x y:y
@@ -1313,7 +1313,7 @@
 
     self pointerEntersItem:nil.
     self cursorEntersItem:nil.
-    self closeEditor.        
+    self closeEditor.
 
     enabled ifFalse:[^ self].
 
@@ -1321,165 +1321,165 @@
     lineNr := self yVisibleToLineNr:y.
 
     ((button == 2) or:[button == #menu]) ifTrue:[
-        (self selectOnMenuButton and:[self numberOfSelections <= 1]) ifTrue:[
-            (     lineNr notNil
-             and:[self canSelectIndex:lineNr forAdd:false ]
-            ) ifTrue:[
-                (lineNr ~~ self selectedIndex) ifTrue: [
-                    (self selectWithoutScroll:lineNr redraw:true) ifTrue:[
-                        self selectionChanged
-                    ].
-                ].
-                item := self selectedElement.
-            ] ifFalse:[
-                item := nil.
-                item := self selectedElement.
+	(self selectOnMenuButton and:[self numberOfSelections <= 1]) ifTrue:[
+	    (     lineNr notNil
+	     and:[self canSelectIndex:lineNr forAdd:false ]
+	    ) ifTrue:[
+		(lineNr ~~ self selectedIndex) ifTrue: [
+		    (self selectWithoutScroll:lineNr redraw:true) ifTrue:[
+			self selectionChanged
+		    ].
+		].
+		item := self selectedElement.
+	    ] ifFalse:[
+		item := nil.
+		item := self selectedElement.
 "/                self deselect.
-            ]
-        ] ifFalse:[
-            item := self selectedElement.
-        ].
-
-        item notNil ifTrue:[
-            self makeSelectionVisible.
-
-            menu := item perform:#middleButtonMenu ifNotUnderstood:nil.
-            menu notNil ifTrue:[
-                menu isCollection ifTrue:[
-                    menu := Menu decodeFromLiteralArray:menu.
-                    appl := self application.
-
-                    appl notNil ifTrue:[
-                        menu findGuiResourcesIn:appl.
-                        "/ menu receiver:appl  -- now done in findGuiResources ...
-                    ] ifFalse:[
-                        menu receiver:item
-                    ]
-                ].
-                self startUpMenu:menu.
-                ^ self
-            ].
-        ].
-        super buttonPress:button x:x y:y.
-        ^ self
+	    ]
+	] ifFalse:[
+	    item := self selectedElement.
+	].
+
+	item notNil ifTrue:[
+	    self makeSelectionVisible.
+
+	    menu := item perform:#middleButtonMenu ifNotUnderstood:nil.
+	    menu notNil ifTrue:[
+		menu isCollection ifTrue:[
+		    menu := Menu decodeFromLiteralArray:menu.
+		    appl := self application.
+
+		    appl notNil ifTrue:[
+			menu findGuiResourcesIn:appl.
+			"/ menu receiver:appl  -- now done in findGuiResources ...
+		    ] ifFalse:[
+			menu receiver:item
+		    ]
+		].
+		self startUpMenu:menu.
+		^ self
+	    ].
+	].
+	super buttonPress:button x:x y:y.
+	^ self
     ].
     lineNr isNil ifTrue:[ ^ self ].
     modelChangedDuringButtonPress := false.
 
     sensor ctrlDown ifTrue:[
-        self buttonControlPressAtLine:lineNr x:x y:y.
-        ^ self
+	self buttonControlPressAtLine:lineNr x:x y:y.
+	^ self
     ].
 
     isSelected  := self isInSelection:lineNr.
 
     (self canDrag and:[sensor shiftDown not]) ifTrue:[
-        dragDistance := UserPreferences current motionDistanceToStartDrag.
-
-        isSelected ifTrue:[
-            buttonMotionAction := 
-                [:p|
-                    ((x@y) dist:p) > dragDistance ifTrue:[
-                        self startDragAt:p.
-                    ]
-                ].
-            buttonReleaseAction := [ self buttonPressOrReleaseAtLine:lineNr x:x y:y ].
-            ^ self.
-        ].
-
-        self selectOnButtonPress ifFalse: [
-            |oldSelection|
-
-            "/ set selection to line;
-            "/ set the model without change notification (objects to drag)
-
-            oldSelection := selection copy.
-            self selectAndUpdateModelWithoutChangeNotification: lineNr.
-            self windowGroup processExposeEvents.
-
-            buttonMotionAction := 
-                [:p|
-                    ((x@y) dist:p) > dragDistance ifTrue:[
-                        |handler|
-
-                        handler := self startDragAt:p.
-                        handler contentsWillChange.
-                        "/ restore old selection
-                        self selectAndUpdateModelWithoutChangeNotification: oldSelection.
-                        self windowGroup processExposeEvents.
-                    ].
-                ].
-
-            buttonReleaseAction := [
-                (self canSelectIndex:lineNr forAdd:false) ifTrue:[
-                    "/ notify selection change
-                    self selectionChanged.
-                ] ifFalse:[
-                    "/ restore old selection
-                    self selectAndUpdateModelWithoutChangeNotification: oldSelection.
-                ].
-            ].
-            ^ self
-        ].
+	dragDistance := UserPreferences current motionDistanceToStartDrag.
+
+	isSelected ifTrue:[
+	    buttonMotionAction :=
+		[:p|
+		    ((x@y) dist:p) > dragDistance ifTrue:[
+			self startDragAt:p.
+		    ]
+		].
+	    buttonReleaseAction := [ self buttonPressOrReleaseAtLine:lineNr x:x y:y ].
+	    ^ self.
+	].
+
+	self selectOnButtonPress ifFalse: [
+	    |oldSelection|
+
+	    "/ set selection to line;
+	    "/ set the model without change notification (objects to drag)
+
+	    oldSelection := selection copy.
+	    self selectAndUpdateModelWithoutChangeNotification: lineNr.
+	    self windowGroup processExposeEvents.
+
+	    buttonMotionAction :=
+		[:p|
+		    ((x@y) dist:p) > dragDistance ifTrue:[
+			|handler|
+
+			handler := self startDragAt:p.
+			handler contentsWillChange.
+			"/ restore old selection
+			self selectAndUpdateModelWithoutChangeNotification: oldSelection.
+			self windowGroup processExposeEvents.
+		    ].
+		].
+
+	    buttonReleaseAction := [
+		(self canSelectIndex:lineNr forAdd:false) ifTrue:[
+		    "/ notify selection change
+		    self selectionChanged.
+		] ifFalse:[
+		    "/ restore old selection
+		    self selectAndUpdateModelWithoutChangeNotification: oldSelection.
+		].
+	    ].
+	    ^ self
+	].
     ].
 
     multipleSelectOk ifFalse:[
-        (isSelected or:[self canSelectIndex:lineNr forAdd:false]) ifTrue:[
-            self buttonPressOrReleaseAtLine:lineNr x:x y:y.
-
-            (dragDistance notNil and:[self isInSelection:lineNr]) ifTrue:[
-                buttonMotionAction := 
-                    [:p|
-                        ((x@y) dist:p) > dragDistance ifTrue:[
-                            self startDragAt:p.
-                        ].
-                    ].
-            ].
-        ].
-        ^ self
+	(isSelected or:[self canSelectIndex:lineNr forAdd:false]) ifTrue:[
+	    self buttonPressOrReleaseAtLine:lineNr x:x y:y.
+
+	    (dragDistance notNil and:[self isInSelection:lineNr]) ifTrue:[
+		buttonMotionAction :=
+		    [:p|
+			((x@y) dist:p) > dragDistance ifTrue:[
+			    self startDragAt:p.
+			].
+		    ].
+	    ].
+	].
+	^ self
     ].
     startLine := lineNr.
 
     sensor shiftDown ifTrue:[ |min max|
-        (isSelected or:[self canSelectIndex:lineNr forAdd:true]) ifFalse:[
-            ^ self
-        ].
-
-        multipleSelectOk ifTrue:[
-            startLine := self firstInSelection.
-            startLine isNil ifTrue:[ startLine := lineNr ].
-
-            startLine <= lineNr ifTrue:[
-                self selectFrom:startLine to:lineNr.
-            ] ifFalse:[
-                startLine := self lastInSelection.
-                self selectFrom:lineNr to:startLine.
-            ].
-        ]
+	(isSelected or:[self canSelectIndex:lineNr forAdd:true]) ifFalse:[
+	    ^ self
+	].
+
+	multipleSelectOk ifTrue:[
+	    startLine := self firstInSelection.
+	    startLine isNil ifTrue:[ startLine := lineNr ].
+
+	    startLine <= lineNr ifTrue:[
+		self selectFrom:startLine to:lineNr.
+	    ] ifFalse:[
+		startLine := self lastInSelection.
+		self selectFrom:lineNr to:startLine.
+	    ].
+	]
     ] ifFalse:[
-        (isSelected or:[self canSelectIndex:lineNr forAdd:false]) ifFalse:[
-            ^ self
-        ].
-        self buttonPressOrReleaseAtLine:lineNr x:x y:y.
+	(isSelected or:[self canSelectIndex:lineNr forAdd:false]) ifFalse:[
+	    ^ self
+	].
+	self buttonPressOrReleaseAtLine:lineNr x:x y:y.
     ].
 
     multipleSelectOk ifTrue:[
-        buttonMotionAction := 
-            [:p| |ln|
-                (p y between:0 and:height) ifTrue:[ |ln|
-                    ln := self yVisibleToLineNr:p y.
-                    ln isNil ifTrue:[ln := self size].
-
-                    (ln ~~ self lastInSelection and:[ln ~~ self firstInSelection]) ifTrue:[
-                        self selectFrom:startLine to:ln.
-                        dragDistance := nil.   "/ selection changed - no longer dragable
-                    ]
-                ].
-
-                (dragDistance notNil and:[(x dist:p x) > dragDistance]) ifTrue:[
-                    self startDragAt:p.
-                ].
-            ].
+	buttonMotionAction :=
+	    [:p| |ln|
+		(p y between:0 and:height) ifTrue:[ |ln|
+		    ln := self yVisibleToLineNr:p y.
+		    ln isNil ifTrue:[ln := self size].
+
+		    (ln ~~ self lastInSelection and:[ln ~~ self firstInSelection]) ifTrue:[
+			self selectFrom:startLine to:ln.
+			dragDistance := nil.   "/ selection changed - no longer dragable
+		    ]
+		].
+
+		(dragDistance notNil and:[(x dist:p x) > dragDistance]) ifTrue:[
+		    self startDragAt:p.
+		].
+	    ].
     ].
 
     "Modified: / 27-03-2007 / 08:43:58 / cg"
@@ -1489,24 +1489,24 @@
     "handle a button press or release at a line
     "
     aLnNr == self selectedIndex ifTrue:[
-        editorView notNil ifTrue:[^ self].
-
-        self openEditorAction notNil ifTrue:[
-            self openEditorAtX:x y:y.
-            editorView notNil ifTrue:[^ self].
-        ].
-
-        ignoreReselect ifFalse:[
-            (toggleSelect and:[self sensor ctrlDown]) ifTrue:[
-                self selection:nil
-            ] ifFalse:[
-                self selectionChanged
-            ].
-        ].
+	editorView notNil ifTrue:[^ self].
+
+	self openEditorAction notNil ifTrue:[
+	    self openEditorAtX:x y:y.
+	    editorView notNil ifTrue:[^ self].
+	].
+
+	ignoreReselect ifFalse:[
+	    (toggleSelect and:[self sensor ctrlDown]) ifTrue:[
+		self selection:nil
+	    ] ifFalse:[
+		self selectionChanged
+	    ].
+	].
     ] ifFalse:[
-        (self selectWithoutScroll:aLnNr redraw:true) ifTrue:[
-            self selectionChanged
-        ]
+	(self selectWithoutScroll:aLnNr redraw:true) ifTrue:[
+	    self selectionChanged
+	]
     ].
 !
 
@@ -1519,15 +1519,15 @@
     buttonMotionAction   := modelChangedDuringButtonPress := nil.
 
     buttonReleaseAction notNil ifTrue:[
-        buttonReleaseAction value.
-        buttonReleaseAction := nil.
+	buttonReleaseAction value.
+	buttonReleaseAction := nil.
     ].
 
     self cursorEntersItem:nil.
     self stopAutoScroll.
 
     (makeSelectionVisible == true and:[self hasSelection]) ifTrue:[
-        self makeSelectionVisible
+	self makeSelectionVisible
     ].
 !
 
@@ -1543,26 +1543,26 @@
     lnNr isNil ifTrue:[lnNr := 0].
 
     self sensor shiftDown ifTrue:[
-        stp := -1.              "/ search backward
-        to1 :=  1.
-        fr2 := size.
+	stp := -1.              "/ search backward
+	to1 :=  1.
+	fr2 := size.
     ] ifFalse:[
-        stp := 1.               "/ search forward
-        to1 := size.
-        fr2 := 1.
+	stp := 1.               "/ search forward
+	to1 := size.
+	fr2 := 1.
     ].
 
     idx := self findLineFrom:lnNr+stp to:to1 by:stp startingWithCharacter:aKey.
 
     idx == 0 ifTrue:[
-        idx := self findLineFrom:fr2 to:lnNr-stp by:stp startingWithCharacter:aKey.
-        idx == 0 ifTrue:[^ self].
+	idx := self findLineFrom:fr2 to:lnNr-stp by:stp startingWithCharacter:aKey.
+	idx == 0 ifTrue:[^ self].
     ].
 
     self selection:idx.
 
     keyActionStyle == #selectAndDoubleClick ifTrue:[
-        self doubleClicked
+	self doubleClicked
     ].
 !
 
@@ -1576,14 +1576,14 @@
     item := self at:anIndex ifAbsent:nil.
 
     item isHierarchicalItem ifTrue:[
-        item := item string
+	item := item string
     ].
     item isNil ifTrue:[^ nil].
 
     (Error catch:[
-        s := item asString
+	s := item asString
     ]) ifTrue:[
-        s := item displayString
+	s := item displayString
     ].
     ^ s
 !
@@ -1594,12 +1594,12 @@
     "/     draw the frame at the top and bottom, but NOT at the left and right
 
     self hasSelection ifTrue:[
-        (hilightFrameColor notNil 
-        or:[hilightStyle == #motif
-        or:[hilightLevel ~~ 0]]) ifTrue:[
-           "/ invalidate the right-edge
-            self invalidate:(((width-3) @ 0) corner:((width-1) @ (height-1))).
-        ]
+	(hilightFrameColor notNil
+	or:[hilightStyle == #motif
+	or:[hilightLevel ~~ 0]]) ifTrue:[
+	   "/ invalidate the right-edge
+	    self invalidate:(((width-3) @ 0) corner:((width-1) @ (height-1))).
+	]
     ].
 
     super containerChangedSize.
@@ -1611,25 +1611,25 @@
     |lnNr x|
 
     (shown and:[self size ~~ 0]) ifFalse:[
-        cursorItem := nil.
-        ^ self.  
+	cursorItem := nil.
+	^ self.
     ].
 
     anItemOrNil == cursorItem ifTrue:[ ^ self ].
 
     2 timesRepeat:[
-        cursorItem notNil ifTrue:[
-            lnNr := self identityIndexOf:cursorItem.
-            lnNr notNil ifTrue:[
-                x := self xVisibleOfItem:cursorItem.
-                self invalidateLineAt:lnNr fromX:x
-            ].
-        ].
-        "/ set the new item
-        cursorItem := anItemOrNil.
+	cursorItem notNil ifTrue:[
+	    lnNr := self identityIndexOf:cursorItem.
+	    lnNr notNil ifTrue:[
+		x := self xVisibleOfItem:cursorItem.
+		self invalidateLineAt:lnNr fromX:x
+	    ].
+	].
+	"/ set the new item
+	cursorItem := anItemOrNil.
     ].
     cursorItem notNil ifTrue:[
-        self makeLineVisible:lnNr
+	self makeLineVisible:lnNr
     ].
 !
 
@@ -1639,11 +1639,11 @@
     |arg|
 
     doubleClickActionBlock notNil ifTrue:[
-        arg := self selectedIndex.
-
-        arg ~~ 0 ifTrue:[
-            doubleClickActionBlock valueWithOptionalArgument:arg and:self.
-        ]
+	arg := self selectedIndex.
+
+	arg ~~ 0 ifTrue:[
+	    doubleClickActionBlock valueWithOptionalArgument:arg and:self.
+	]
     ].
 !
 
@@ -1656,31 +1656,31 @@
      stop     "{ Class:SmallInteger }"
     |
     (size := self size) ~~ 0 ifTrue:[
-        aStep > 0 ifTrue:[
-            aStart > aStop ifTrue:[^ 0].
-        ] ifFalse:[
-            (aStep == 0 or:[aStop > aStart]) ifTrue:[^ 0]
-        ].
-
-        start := aStart < 0 ifTrue:[1] ifFalse:[aStart min:size].
-        stop  := aStop  < 0 ifTrue:[1] ifFalse:[aStop  min:size].
-        char  := aCharacter asUppercase.
-
-        start to:stop by:aStep do:[:anIndex|
-            lbl := self characterSearchItemStringAt:anIndex.
-            lbl notNil ifTrue:[
-                cmp := lbl string at:1 ifAbsent:nil.
-
-                cmp notNil ifTrue:[
-                    (char == cmp or:[char == cmp asUppercase]) ifTrue:[
-                        (self canSelectIndex:anIndex forAdd:false) ifTrue:[
-                            ^ anIndex
-                        ].
-                        ^ 0
-                    ]
-                ]
-            ]
-        ]
+	aStep > 0 ifTrue:[
+	    aStart > aStop ifTrue:[^ 0].
+	] ifFalse:[
+	    (aStep == 0 or:[aStop > aStart]) ifTrue:[^ 0]
+	].
+
+	start := aStart < 0 ifTrue:[1] ifFalse:[aStart min:size].
+	stop  := aStop  < 0 ifTrue:[1] ifFalse:[aStop  min:size].
+	char  := aCharacter asUppercase.
+
+	start to:stop by:aStep do:[:anIndex|
+	    lbl := self characterSearchItemStringAt:anIndex.
+	    lbl notNil ifTrue:[
+		cmp := lbl string at:1 ifAbsent:nil.
+
+		cmp notNil ifTrue:[
+		    (char == cmp or:[char == cmp asUppercase]) ifTrue:[
+			(self canSelectIndex:anIndex forAdd:false) ifTrue:[
+			    ^ anIndex
+			].
+			^ 0
+		    ]
+		]
+	    ]
+	]
     ].
     ^ 0
 
@@ -1692,8 +1692,8 @@
 
     lnNr := self identityIndexOf:enterItem.
     lnNr notNil ifTrue:[
-        x := self xVisibleOfItem:enterItem.
-        self invalidateLineAt:lnNr fromX:x
+	x := self xVisibleOfItem:enterItem.
+	self invalidateLineAt:lnNr fromX:x
     ].
 !
 
@@ -1701,8 +1701,8 @@
     "a key was pressed - handle page-keys here
     "
     <resource: #keyboard( #CursorUp #CursorDown #EndOfText #EndOfLine
-                          #BeginOfText #BeginOfLine #Return
-                          #CmdReturn #CmdCursorUp #CmdCursorDown #SelectAll)>
+			  #BeginOfText #BeginOfLine #Return
+			  #CmdReturn #CmdCursorUp #CmdCursorDown #SelectAll)>
 
     |lineNr listSize shifted newSel step start|
 
@@ -1712,154 +1712,154 @@
     listSize == 0 ifTrue:[^ self].
 
     aKey isCharacter ifTrue:[
-        keyActionStyle notNil ifTrue:[
-            keyActionStyle == #pass ifTrue:[
-                super keyPress:aKey x:x y:y
-            ] ifFalse:[
-                self characterPress:aKey x:x y:y.
-            ].
-        ].
-        ^ self
+	keyActionStyle notNil ifTrue:[
+	    keyActionStyle == #pass ifTrue:[
+		super keyPress:aKey x:x y:y
+	    ] ifFalse:[
+		self characterPress:aKey x:x y:y.
+	    ].
+	].
+	^ self
     ].
 
     aKey == #Escape ifTrue:[
-        cursorItem notNil ifTrue:[
-            self cursorEntersItem:nil.
-            self makeSelectionVisible.
-        ].
-        super keyPress:aKey x:x y:y.
-        ^ self
+	cursorItem notNil ifTrue:[
+	    self cursorEntersItem:nil.
+	    self makeSelectionVisible.
+	].
+	super keyPress:aKey x:x y:y.
+	^ self
     ].
 
     ((aKey == #BeginOfText) or:[aKey == #BeginOfLine]) ifTrue:[
-        self cursorEntersItem:nil.
-
-        1 to:listSize do:[:i|
-            (self canSelectIndex:i forAdd:false) ifTrue:[
-                self selection:i.
-                ^ self
-            ].
-        ].
-        ^ self
+	self cursorEntersItem:nil.
+
+	1 to:listSize do:[:i|
+	    (self canSelectIndex:i forAdd:false) ifTrue:[
+		self selection:i.
+		^ self
+	    ].
+	].
+	^ self
     ].
 
     ((aKey == #EndOfText) or:[aKey == #EndOfLine]) ifTrue:[
-        self cursorEntersItem:nil.
-
-        listSize to:1 by:-1 do:[:i|
-            (self canSelectIndex:i forAdd:false) ifTrue:[
-                self selection:i.
-                ^ self
-            ].
-        ].
-        ^ self
+	self cursorEntersItem:nil.
+
+	listSize to:1 by:-1 do:[:i|
+	    (self canSelectIndex:i forAdd:false) ifTrue:[
+		self selection:i.
+		^ self
+	    ].
+	].
+	^ self
     ].
     lineNr := self cursorLine.
 
     aKey == #Return ifTrue:[
-        returnKeyActionStyle == #pass ifTrue:[
-            super keyPress:aKey x:x y:y
-        ] ifFalse:[
-            lineNr ~~ 0 ifTrue:[
-                self cursorEntersItem:nil.
-
-                (self canSelectIndex:lineNr forAdd:false) ifTrue:[
-                    self selection:lineNr
-                ].
-            ].
-
-            returnKeyActionStyle == #doubleClick ifTrue:[
-                self doubleClicked
-            ].
-        ].
-        ^ self
+	returnKeyActionStyle == #pass ifTrue:[
+	    super keyPress:aKey x:x y:y
+	] ifFalse:[
+	    lineNr ~~ 0 ifTrue:[
+		self cursorEntersItem:nil.
+
+		(self canSelectIndex:lineNr forAdd:false) ifTrue:[
+		    self selection:lineNr
+		].
+	    ].
+
+	    returnKeyActionStyle == #doubleClick ifTrue:[
+		self doubleClicked
+	    ].
+	].
+	^ self
     ].
 
     aKey == #SelectAll ifTrue:[
-        self selectAll.
-        ^ self
+	self selectAll.
+	^ self
     ].
 
     (lineNr == 0 and:[selection notNil]) ifTrue:[
-        multipleSelectOk ifFalse:[lineNr := selection]
-                          ifTrue:[lineNr := selection last].
+	multipleSelectOk ifFalse:[lineNr := selection]
+			  ifTrue:[lineNr := selection last].
     ].
 
     aKey == #CmdReturn ifTrue:[
-        "/ toggle selection of the item
-        lineNr ~~ 0 ifTrue:[
-            (self isInSelection:lineNr) ifTrue:[ self removeFromSelection:lineNr ]
-                                       ifFalse:[ self addToSelection:lineNr ].
-
-            self cursorEntersItem:(self at:lineNr).
-        ].
-        ^ self
+	"/ toggle selection of the item
+	lineNr ~~ 0 ifTrue:[
+	    (self isInSelection:lineNr) ifTrue:[ self removeFromSelection:lineNr ]
+				       ifFalse:[ self addToSelection:lineNr ].
+
+	    self cursorEntersItem:(self at:lineNr).
+	].
+	^ self
     ].
 
     (aKey == #CmdCursorDown or:[aKey == #CmdCursorUp]) ifTrue:[
-        aKey == #CmdCursorDown ifTrue:[
-            lineNr := lineNr + 1.
-            lineNr > listSize ifTrue:[lineNr := 1].
-        ] ifFalse:[
-            lineNr := lineNr - 1.
-            lineNr < 1 ifTrue:[lineNr := listSize].
-        ].
-        self cursorEntersItem:(self at:lineNr).
-        ^ self
+	aKey == #CmdCursorDown ifTrue:[
+	    lineNr := lineNr + 1.
+	    lineNr > listSize ifTrue:[lineNr := 1].
+	] ifFalse:[
+	    lineNr := lineNr - 1.
+	    lineNr < 1 ifTrue:[lineNr := listSize].
+	].
+	self cursorEntersItem:(self at:lineNr).
+	^ self
     ].
 
     (aKey == #CursorUp or:[aKey == #CursorDown]) ifFalse:[
-        super keyPress:aKey x:x y:y.
-        ^ self
+	super keyPress:aKey x:x y:y.
+	^ self
     ].
     shifted := (multipleSelectOk and:[self sensor shiftDown]).
     self cursorEntersItem:nil.
 
     aKey == #CursorDown ifTrue:[ step :=  1.]
-                       ifFalse:[ step := -1.].
+		       ifFalse:[ step := -1.].
 
     shifted ifFalse:[ |compressed|
-        compressed := self sensor compressKeyPressEventsWithKey:aKey.
-
-        compressed ~~ 0 ifTrue:[
-            aKey == #CursorDown ifTrue:[
-                lineNr := lineNr + compressed.
-                lineNr > listSize ifTrue:[lineNr := 1].
-            ] ifFalse:[
-                lineNr := lineNr - compressed.
-                lineNr < 1 ifTrue:[lineNr := listSize].
-            ].
-        ].
+	compressed := self sensor compressKeyPressEventsWithKey:aKey.
+
+	compressed ~~ 0 ifTrue:[
+	    aKey == #CursorDown ifTrue:[
+		lineNr := lineNr + compressed.
+		lineNr > listSize ifTrue:[lineNr := 1].
+	    ] ifFalse:[
+		lineNr := lineNr - compressed.
+		lineNr < 1 ifTrue:[lineNr := listSize].
+	    ].
+	].
     ].
     start  := lineNr.
     lineNr := lineNr + step.
 
     [ lineNr ~~ start ] whileTrue:[
-        (lineNr between:1 and:listSize) ifFalse:[
-            lineNr < 1 ifTrue:[ lineNr := listSize ]
-                      ifFalse:[ lineNr := 1 ].
-        ] ifTrue:[
-            (self canSelectIndex:lineNr forAdd:shifted) ifTrue:[
-                shifted ifFalse:[
-                    self selection:lineNr.
-                    ^ self
-                ].
-                (self isInSelection:lineNr) ifFalse:[
-                    selection isNil ifTrue:[ newSel := Array with:lineNr ]
-                                   ifFalse:[ newSel := selection copyWith:lineNr ].
-                ] ifTrue:[
-                    (start ~~ 0 and:[selection size > 1]) ifFalse:[
-                        ^ self
-                    ].
-                    newSel := selection copyWithout:start.
-                ].
-                self selectWithoutScroll:newSel redraw:true.
-                self makeLineVisible:lineNr.
-                self selectionChanged.
-                ^ self
-            ].
-            lineNr := lineNr + step.
-        ]
+	(lineNr between:1 and:listSize) ifFalse:[
+	    lineNr < 1 ifTrue:[ lineNr := listSize ]
+		      ifFalse:[ lineNr := 1 ].
+	] ifTrue:[
+	    (self canSelectIndex:lineNr forAdd:shifted) ifTrue:[
+		shifted ifFalse:[
+		    self selection:lineNr.
+		    ^ self
+		].
+		(self isInSelection:lineNr) ifFalse:[
+		    selection isNil ifTrue:[ newSel := Array with:lineNr ]
+				   ifFalse:[ newSel := selection copyWith:lineNr ].
+		] ifTrue:[
+		    (start ~~ 0 and:[selection size > 1]) ifFalse:[
+			^ self
+		    ].
+		    newSel := selection copyWithout:start.
+		].
+		self selectWithoutScroll:newSel redraw:true.
+		self makeLineVisible:lineNr.
+		self selectionChanged.
+		^ self
+	    ].
+	    lineNr := lineNr + step.
+	]
     ].
 !
 
@@ -1869,12 +1869,12 @@
     |newItem|
 
     (shown and:[self size ~~ 0]) ifFalse:[
-        enterItem := nil.
-        ^ self.  
+	enterItem := nil.
+	^ self.
     ].
 
     highlightEnterItem ifTrue:[ newItem := anItemOrNil ]
-                      ifFalse:[ newItem := nil ].
+		      ifFalse:[ newItem := nil ].
 
     anItemOrNil == enterItem ifTrue:[ ^ self ].
 
@@ -1898,19 +1898,19 @@
     "/     draw the frame at the top and bottom, but NOT at the left and right
 
     self hasSelection ifTrue:[
-        selectionWasVisible := self isSelectionVisibleIn:(previousExtent ? self extent).
-
-        (hilightFrameColor notNil 
-        or:[hilightStyle == #motif
-        or:[hilightLevel ~~ 0]]) ifTrue:[
-           "/ invalidate the right-edge
-            self invalidate:(((width-3) @ 0) corner:((width-1) @ (height-1))).
-        ].
+	selectionWasVisible := self isSelectionVisibleIn:(previousExtent ? self extent).
+
+	(hilightFrameColor notNil
+	or:[hilightStyle == #motif
+	or:[hilightLevel ~~ 0]]) ifTrue:[
+	   "/ invalidate the right-edge
+	    self invalidate:(((width-3) @ 0) corner:((width-1) @ (height-1))).
+	].
     ].
     super sizeChanged:how.
 
     selectionWasVisible ifTrue:[
-        self makeSelectionVisible
+	self makeSelectionVisible
     ].
 ! !
 
@@ -1931,15 +1931,15 @@
      the mouse pointer enters"
 
     (editorView notNil and:[editorView realized]) ifTrue:[
-        ^ false
+	^ false
     ].
 
     (UserPreferences current focusFollowsMouse ~~ false
     and:[(styleSheet at:#'selection.requestFocusOnPointerEnter' default:true)
     ]) ifTrue:[
-        self size > 0 ifTrue:[
-            ^ true
-        ]
+	self size > 0 ifTrue:[
+	    ^ true
+	]
     ].
     ^ false
 ! !
@@ -1965,12 +1965,12 @@
 initStyle
     "setup viewStyle specifics
     "
-    <resource: #style (#'selection.selectOnMenuButton' 
-                       #'selection.font')>
+    <resource: #style (#'selection.selectOnMenuButton'
+		       #'selection.font')>
     super initStyle.
 
     lineMask isNil ifTrue:[
-        lineMask := Form width:2 height:2 fromArray:#[16rAA 16r55].
+	lineMask := Form width:2 height:2 fromArray:#[16rAA 16r55].
     ].
 
     hilightFrameColor   := nil.
@@ -1979,71 +1979,71 @@
     textStartLeft       := 4.
     selectOnMenuButton  := styleSheet at:#'selection.selectOnMenuButton' default:nil.
     selectOnMenuButton isNil ifTrue:[
-        selectOnMenuButton := UserPreferences current selectOnRightClick
+	selectOnMenuButton := UserPreferences current selectOnRightClick
     ].
 
     super font:(styleSheet fontAt:#'selection.font').
 
     device hasGrayscales ifTrue:[
-        "
-         must get rid of these hard codings
-        "
-        (hilightStyle == #next) ifTrue:[
-            hilightFgColor := fgColor.
-            hilightBgColor := White.
-            hilightFrameColor := fgColor
-        ] ifFalse:[
-            (hilightStyle == #motif) ifTrue:[
-                fgColor := White.
-                bgColor := Grey.
-                viewBackground := bgColor.
-                hilightFgColor := bgColor.
-                hilightBgColor := fgColor.
-            ] ifFalse:[
-                (hilightStyle == #openwin) ifTrue:[
-                    hilightFgColor := fgColor.
-                    hilightBgColor := Color grey.
-                ]
-            ]
-        ]
+	"
+	 must get rid of these hard codings
+	"
+	(hilightStyle == #next) ifTrue:[
+	    hilightFgColor := fgColor.
+	    hilightBgColor := White.
+	    hilightFrameColor := fgColor
+	] ifFalse:[
+	    (hilightStyle == #motif) ifTrue:[
+		fgColor := White.
+		bgColor := Grey.
+		viewBackground := bgColor.
+		hilightFgColor := bgColor.
+		hilightBgColor := fgColor.
+	    ] ifFalse:[
+		(hilightStyle == #openwin) ifTrue:[
+		    hilightFgColor := fgColor.
+		    hilightBgColor := Color grey.
+		]
+	    ]
+	]
     ].
 
     hilightFgColor isNil ifTrue:[
-        hilightFgColor := bgColor.
+	hilightFgColor := bgColor.
     ].
     hilightBgColor isNil ifTrue:[
-        hilightBgColor := fgColor.
+	hilightBgColor := fgColor.
     ].
     DefaultForegroundColor notNil ifTrue:[
-        fgColor := DefaultForegroundColor
+	fgColor := DefaultForegroundColor
     ].
     DefaultBackgroundColor notNil ifTrue:[
-        bgColor := viewBackground := DefaultBackgroundColor
+	bgColor := viewBackground := DefaultBackgroundColor
     ].
 
     DefaultHilightForegroundColor notNil ifTrue:[
-        hilightFgColor := DefaultHilightForegroundColor
+	hilightFgColor := DefaultHilightForegroundColor
     ].
     DefaultHilightBackgroundColor notNil ifTrue:[
-        hilightBgColor := DefaultHilightBackgroundColor
+	hilightBgColor := DefaultHilightBackgroundColor
     ].
     DefaultHilightFrameColor notNil ifTrue:[
-        hilightFrameColor := DefaultHilightFrameColor
+	hilightFrameColor := DefaultHilightFrameColor
     ].
 
     hilightLevel := DefaultHilightLevel ? 0.
     lineSpacing  := (hilightLevel abs > 0) ifTrue:[3] ifFalse:[2].
 
     hilightFgColor isNil ifTrue:[
-        hilightFgColor := bgColor.
-        hilightBgColor := fgColor.
+	hilightFgColor := bgColor.
+	hilightBgColor := fgColor.
     ].
 
     hilightFgColorNoFocus isNil ifTrue:[
-        hilightFgColorNoFocus := hilightFgColor.
+	hilightFgColorNoFocus := hilightFgColor.
     ].
     hilightBgColorNoFocus isNil ifTrue:[
-        hilightBgColorNoFocus := hilightBgColor lightened.
+	hilightBgColorNoFocus := hilightBgColor lightened.
     ].
 !
 
@@ -2085,14 +2085,14 @@
     |lnNr item y0 x0 y1|
 
     editorView isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     (    (lnNr := self selectedIndex) == 0
      or:[(item := self at:lnNr ifAbsent:nil) isNil]
     ) ifTrue:[
-        "/ there is no more single selection; thus close the editor
-        ^ self closeEditor
+	"/ there is no more single selection; thus close the editor
+	^ self closeEditor
     ].
 
     x0 := (self xVisibleOfItem:item) - (textStartLeft // 2).
@@ -2100,7 +2100,7 @@
     y1 := self yVisibleOfLine:(lnNr + 1).
 
     minimumEditorHeight notNil ifTrue:[
-        y1 := y0 + ((y1 - y0) max:minimumEditorHeight).
+	y1 := y0 + ((y1 - y0) max:minimumEditorHeight).
     ].
     "/ Changed by cg:
     "/ editorView layout:( Rectangle left:x top:y right:(width - 1 - margin) bottom:(h + 2 "- 1") ).
@@ -2123,8 +2123,8 @@
     item isNil ifTrue:[^ self].
 
     x < (self xVisibleOfItem:item) ifTrue:[
-        "/ not part of the selection frame; ignorre
-        ^ self
+	"/ not part of the selection frame; ignorre
+	^ self
     ].
     editor := self openEditor.
     editor isNil ifTrue:[^ self].
@@ -2137,11 +2137,11 @@
     "/ Changed by cg:
     "/ but only if there was no initial selection
     editor isInputField ifTrue:[
-        editor hasSelection ifFalse:[
-            self sensor 
-                pushEvent:(WindowEvent buttonPress:#select x:x0 y:y0 view:editor);
-                pushEvent:(WindowEvent buttonRelease:#select x:x0 y:y0 view:editor).
-        ]
+	editor hasSelection ifFalse:[
+	    self sensor
+		pushEvent:(WindowEvent buttonPress:#select x:x0 y:y0 view:editor);
+		pushEvent:(WindowEvent buttonRelease:#select x:x0 y:y0 view:editor).
+	]
     ].
 
     "/ to clear the selection
@@ -2187,8 +2187,8 @@
     y1 := cachedLinesY at:cachedMaxIdx.
 
     (minimumEditorHeight notNil and:[openEditorAction notNil]) ifTrue:[
-        y0 := cachedLinesY at:(cachedMaxIdx - 1) ifAbsent:0.
-        y1 := y0 + ((y1 - y0) max:minimumEditorHeight).
+	y0 := cachedLinesY at:(cachedMaxIdx - 1) ifAbsent:0.
+	y1 := y0 + ((y1 - y0) max:minimumEditorHeight).
     ].
     ^ y1
 ! !
@@ -2201,26 +2201,26 @@
     |oldSelect forAdd|
 
     (self isInSelection:lineNr) ifTrue:[
-        ^ self
+	^ self
     ].
 
     multipleSelectOk ifTrue:[ forAdd := selection notNil ]
-                    ifFalse:[ forAdd := false ].
+		    ifFalse:[ forAdd := false ].
 
     (self canSelectIndex:lineNr forAdd:forAdd) ifFalse:[
-        ^ self
+	^ self
     ].
 
     self closeEditor.
     self cursorEntersItem:nil.
 
     multipleSelectOk ifFalse:[
-        oldSelect := selection.
-        selection := lineNr.
-        oldSelect notNil ifTrue:[ self invalidateSelectionAt:oldSelect ].
+	oldSelect := selection.
+	selection := lineNr.
+	oldSelect notNil ifTrue:[ self invalidateSelectionAt:oldSelect ].
     ] ifTrue:[
-        selection notNil ifTrue:[ selection := selection copyWith:lineNr ]
-                        ifFalse:[ selection := OrderedCollection with:lineNr ].
+	selection notNil ifTrue:[ selection := selection copyWith:lineNr ]
+			ifFalse:[ selection := OrderedCollection with:lineNr ].
     ].
     self invalidateSelectionAt:lineNr.
     self selectionChanged.
@@ -2257,10 +2257,10 @@
     "return true, if line, aNumber is in the selection
     "
     multipleSelectOk ifFalse:[
-        ^ (aNumber == selection)
+	^ (aNumber == selection)
     ].
     selection notNil ifTrue:[
-        ^ selection includesIdentical:aNumber
+	^ selection includesIdentical:aNumber
     ].
     ^ false
 !
@@ -2275,7 +2275,7 @@
     "returns true if any selected element is visible"
 
     self selectionDo:[:aLineNr|
-        (self isLineVisible:aLineNr in:anExtentPoint) ifTrue:[^ true].
+	(self isLineVisible:aLineNr in:anExtentPoint) ifTrue:[^ true].
     ].
     ^ false
 !
@@ -2307,8 +2307,8 @@
     (firstLine isNil or:[firstLine == 0]) ifTrue:[^ self].
 
     self selectionDo:[:aLnNr|
-        (self lineIsFullyVisible:aLnNr) ifTrue:[^ self].
-    ].    
+	(self lineIsFullyVisible:aLnNr) ifTrue:[^ self].
+    ].
     self makeLineVisible:(self firstInSelection).
 !
 
@@ -2324,22 +2324,22 @@
     "remove line from selection without scrolling but raise a change notification
     "
     (self isInSelection:lineNr) ifFalse:[
-        ^ self
+	^ self
     ].
     self closeEditor.
     self cursorEntersItem:nil.
 
     (multipleSelectOk and:[self numberOfSelections > 1]) ifTrue:[
-        selection := selection copyWithout:lineNr.
+	selection := selection copyWithout:lineNr.
     ] ifFalse:[
-        selection := nil
+	selection := nil
     ].
     self invalidateSelectionAt:lineNr.
     self selectionChanged.
 !
 
 selectAll
-    "select all entries. 
+    "select all entries.
      Model and/or actionBlock notification IS done."
 
     self selectFrom:1 to:self size.
@@ -2357,7 +2357,7 @@
 
     idx := self identityIndexOf:anElement.
     idx == 0 ifTrue:[
-        ^ exceptionalValue value
+	^ exceptionalValue value
     ].
     self selection:idx
 !
@@ -2373,27 +2373,27 @@
     stop  := aStop.
 
     aStart < aStop ifTrue:[
-        start := aStart max:1.
-        stop  := aStop  min:(self size).
-        step  := 1.
-        start > stop ifTrue:[^ self].
+	start := aStart max:1.
+	stop  := aStop  min:(self size).
+	step  := 1.
+	start > stop ifTrue:[^ self].
 
     ] ifFalse:[
-        start := aStart min:(self size).
-        stop  := aStop  max:1.
-        step  := -1.
-        start < stop ifTrue:[^ self].
+	start := aStart min:(self size).
+	stop  := aStop  max:1.
+	step  := -1.
+	start < stop ifTrue:[^ self].
     ].
     nsel := OrderedCollection new.
 
     start to:stop by:step do:[:i|
-        (self canSelectIndex:i forAdd:true) ifTrue:[
-            nsel add:i.
-        ].
+	(self canSelectIndex:i forAdd:true) ifTrue:[
+	    nsel add:i.
+	].
     ].
 
     (self selectWithoutScroll:nsel redraw:true) ifTrue:[
-        self selectionChanged
+	self selectionChanged
     ].
 !
 
@@ -2403,7 +2403,7 @@
     |index|
 
     (index := self selectedIndex) ~~ 0 ifTrue:[
-        ^ self at:index ifAbsent:nil
+	^ self at:index ifAbsent:nil
     ].
     ^ nil
 !
@@ -2413,17 +2413,17 @@
      lines are selected, 0 is returned
     "
     selection notNil ifTrue:[
-        multipleSelectOk ifFalse:[ ^ selection ].
-
-        selection size == 1 ifTrue:[
-            ^ selection at:1
-        ]
+	multipleSelectOk ifFalse:[ ^ selection ].
+
+	selection size == 1 ifTrue:[
+	    ^ selection at:1
+	]
     ].
     ^ 0
 !
 
 selection
-    "return the selection index or collection of indices 
+    "return the selection index or collection of indices
      in case of multiple selection enabled
     "
     ^ selection
@@ -2436,8 +2436,8 @@
      The model and/or actionBlock IS notified.
     "
     (self selectWithoutScroll:something redraw:true) ifTrue:[
-        self makeSelectionVisible.
-        self selectionChanged
+	self makeSelectionVisible.
+	self selectionChanged
     ].
 
 !
@@ -2459,11 +2459,11 @@
      For multiple selections, it is called for each.
     "
     selection notNil ifTrue:[
-        multipleSelectOk ifTrue:[
-            selection do:aBlock
-        ] ifFalse:[
-            aBlock value:selection
-        ].
+	multipleSelectOk ifTrue:[
+	    selection do:aBlock
+	] ifFalse:[
+	    aBlock value:selection
+	].
     ].
 
 
@@ -2474,8 +2474,8 @@
      For multiple selections a collection containing the entries is returned.
     "
     multipleSelectOk ifTrue:[
-        selection isNil ifTrue:[^ #()].
-        ^ selection collect:[:nr| self at:nr ]
+	selection isNil ifTrue:[^ #()].
+	^ selection collect:[:nr| self at:nr ]
     ].
     selection isNil ifTrue:[^ nil].
     ^ self at:selection ifAbsent:nil.
@@ -2500,7 +2500,7 @@
      *** No model and/or actionBlock notification is done here.
     "
     (self selectWithoutScroll:something redraw:true) ifTrue:[
-        self makeSelectionVisible
+	self makeSelectionVisible
     ]
 
 ! !
@@ -2519,18 +2519,18 @@
     |item isOk|
 
     selectConditionBlock notNil ifTrue:[
-        isOk := selectConditionBlock valueWithOptionalArgument:anIndex and:isForAdd.
-
-        isOk ifFalse:[
-            ^ false
-        ]
+	isOk := selectConditionBlock valueWithOptionalArgument:anIndex and:isForAdd.
+
+	isOk ifFalse:[
+	    ^ false
+	]
     ].
 
     item := self at:anIndex ifAbsent:nil.
     item isNil ifTrue:[^ false].
 
     item isHierarchicalItem ifTrue:[
-        ^ item isSelectable
+	^ item isSelectable
     ].
     ^ true
 !
@@ -2540,7 +2540,7 @@
      the model and/or actionBlock is notified
     "
     (self selectWithoutScroll:nil redraw:false) ifTrue:[
-        self selectionChanged
+	self selectionChanged
     ]
 !
 
@@ -2564,45 +2564,45 @@
     oldSelect := selection.
 
     (something isNil or:[something == 0]) ifTrue:[
-        selection := nil
+	selection := nil
     ] ifFalse:[
-        something isNumber ifTrue:[
-            selection := multipleSelectOk ifTrue:[Array with:something]
-                                         ifFalse:[something]
-        ] ifFalse:[
-            something size == 0 ifTrue:[
-                selection := nil
-            ] ifFalse:[
-                selection := multipleSelectOk ifTrue:[something]
-                                             ifFalse:[something at:1]
-            ]
-        ]
+	something isNumber ifTrue:[
+	    selection := multipleSelectOk ifTrue:[Array with:something]
+					 ifFalse:[something]
+	] ifFalse:[
+	    something size == 0 ifTrue:[
+		selection := nil
+	    ] ifFalse:[
+		selection := multipleSelectOk ifTrue:[something]
+					     ifFalse:[something at:1]
+	    ]
+	]
     ].
     selection = oldSelect ifTrue:[^ false].
 
     modelChangedDuringButtonPress notNil ifTrue:[
-        modelChangedDuringButtonPress := true.
+	modelChangedDuringButtonPress := true.
     ].
 
     self closeEditor.
     self cursorEntersItem:nil.
 
-    
+
     (doRedraw and:[shown]) ifFalse:[
-        ^ true
+	^ true
     ].
 
     multipleSelectOk ifFalse:[
-        oldSelect notNil ifTrue:[self invalidateSelectionAt:oldSelect].
-        selection notNil ifTrue:[self invalidateSelectionAt:selection].
+	oldSelect notNil ifTrue:[self invalidateSelectionAt:oldSelect].
+	selection notNil ifTrue:[self invalidateSelectionAt:selection].
     ] ifTrue:[
-        (selection notNil and:[oldSelect notNil]) ifTrue:[
-            selection do:[:i|(oldSelect includesIdentical:i) ifFalse:[self invalidateSelectionAt:i]].
-            oldSelect do:[:i|(selection includesIdentical:i) ifFalse:[self invalidateSelectionAt:i]].
-        ] ifFalse:[
-            oldSelect isNil ifTrue:[oldSelect := selection].
-            oldSelect do:[:i|self invalidateSelectionAt:i]
-        ]
+	(selection notNil and:[oldSelect notNil]) ifTrue:[
+	    selection do:[:i|(oldSelect includesIdentical:i) ifFalse:[self invalidateSelectionAt:i]].
+	    oldSelect do:[:i|(selection includesIdentical:i) ifFalse:[self invalidateSelectionAt:i]].
+	] ifFalse:[
+	    oldSelect isNil ifTrue:[oldSelect := selection].
+	    oldSelect do:[:i|self invalidateSelectionAt:i]
+	]
     ].
     ^ true
 ! !
@@ -2610,5 +2610,5 @@
 !SelectionInListModelView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInListModelView.st,v 1.143 2009-05-27 06:05:59 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInListModelView.st,v 1.144 2009-08-07 10:50:41 sr Exp $'
 ! !
--- a/bc.mak	Tue Aug 04 14:15:20 2009 +0200
+++ b/bc.mak	Fri Aug 07 12:50:41 2009 +0200
@@ -1,6 +1,6 @@
-# $Header: /cvs/stx/stx/libwidg2/bc.mak,v 1.68 2009-05-07 12:07:41 stefan Exp $
+# $Header: /cvs/stx/stx/libwidg2/bc.mak,v 1.69 2009-08-07 10:50:41 sr Exp $
 #
-# DO NOT EDIT 
+# DO NOT EDIT
 # automagically generated from the projectDefinition: stx_libwidg2.
 #
 # Warning: once you modify this file, do not rerun
@@ -86,6 +86,7 @@
 $(OUTDIR)LinkButtonController.$(O) LinkButtonController.$(H): LinkButtonController.st $(INCLUDE_TOP)\stx\libwidg\ButtonController.$(H) $(INCLUDE_TOP)\stx\libview\Controller.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ListEntry.$(O) ListEntry.$(H): ListEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ListModelView.$(O) ListModelView.$(H): ListModelView.st $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\DeviceGraphicsContext.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsContext.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)LicenceBox.$(O) LicenceBox.$(H): LicenceBox.st $(INCLUDE_TOP)\stx\libwidg\DialogBox.$(H) $(INCLUDE_TOP)\stx\libview\ModalBox.$(H) $(INCLUDE_TOP)\stx\libview\StandardSystemView.$(H) $(INCLUDE_TOP)\stx\libview\TopView.$(H) $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\DeviceGraphicsContext.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsContext.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MenuPanel.$(O) MenuPanel.$(H): MenuPanel.st $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\DeviceGraphicsContext.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsContext.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MultipleItemSelectionWidget.$(O) MultipleItemSelectionWidget.$(H): MultipleItemSelectionWidget.st $(INCLUDE_TOP)\stx\libview2\ApplicationModel.$(H) $(INCLUDE_TOP)\stx\libview2\Model.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)NoteBookView.$(O) NoteBookView.$(H): NoteBookView.st $(INCLUDE_TOP)\stx\libview\View.$(H) $(INCLUDE_TOP)\stx\libview\SimpleView.$(H) $(INCLUDE_TOP)\stx\libview\DisplaySurface.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsMedium.$(H) $(INCLUDE_TOP)\stx\libview\DeviceGraphicsContext.$(H) $(INCLUDE_TOP)\stx\libview\GraphicsContext.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)