level fixes;
authorpenk
Wed, 21 Aug 2002 18:25:59 +0200
changeset 2146 4ae1ec9f5307
parent 2145 aa6c81509521
child 2147 844ef88050b4
level fixes; labelView draws last partial label
DSVColumnView.st
DSVLabelView.st
DataSetView.st
--- a/DSVColumnView.st	Wed Aug 21 18:24:53 2002 +0200
+++ b/DSVColumnView.st	Wed Aug 21 18:25:59 2002 +0200
@@ -197,7 +197,8 @@
 updateStyleCache
     "extract values from the styleSheet and cache them in class variables
     "
-    <resource: #style (#textForegroundColor #'scrollableView.backgroundColor'
+    <resource: #style (#textForegroundColor 
+                       #'scrollableView.backgroundColor'
                        #'selection.hilightForegroundColor'
                        #'selection.hilightBackgroundColor'   )>
 
@@ -311,20 +312,37 @@
 labelView:aView
     labelView := aView for:self.
 
+    labelView layout:(LayoutFrame
+                        leftFraction:0 offset:0 
+                        rightFraction:1 offset:0 
+                        topFraction:0 offset:0 
+                        bottomFraction:0 offset:[self preferredLabelViewHeight]).
 !
 
 layout:aLayout
     "layout changed; change the layout of the labelView dependent on my layout
     "
-    |newLyt lblLyt bOffset tOffset|
+    |modifiedLayout newLyt lblLyt bOffset tOffset|
+
+^ super layout:aLayout.
+
+self halt.
+    (labelView notNil and:[labelView isVisible]) ifTrue:[
+        modifiedLayout := aLayout copy.
+        modifiedLayout topOffset:(1 + self preferredLabelViewHeight).
+        super layout:modifiedLayout.
+    ] ifFalse:[
+        super layout:aLayout.
+    ].
+    ^ self.
 
     (newLyt := aLayout ? layout) isNil ifTrue:[
         ^ self
     ].
-    lblLyt := newLyt copy.
+"/    lblLyt := newLyt copy.
 
     labelView isVisible ifTrue:[
-        bOffset := labelView preferredHeight.
+        bOffset := self preferredLabelViewHeight.
         tOffset := margin.
         newLyt topOffset:1 + bOffset.
     ] ifFalse:[
@@ -332,11 +350,10 @@
         tOffset := -2.
         newLyt topOffset:margin.
     ].
-    lblLyt bottomFraction:0 offset:bOffset.
-    lblLyt topFraction:0    offset:tOffset.
-    labelView layout:lblLyt.
+"/    lblLyt bottomFraction:0 offset:bOffset.
+"/    lblLyt topFraction:0    offset:tOffset.
+"/    labelView layout:lblLyt.
     super layout:newLyt.
-
 !
 
 level:aLevel
@@ -344,7 +361,7 @@
     "
     aLevel ~~ level ifTrue:[
         super level:aLevel.
-        labelView level:aLevel.
+"/        labelView level:aLevel.
     ]
 !
 
@@ -364,6 +381,45 @@
     "Created: / 30.1.2000 / 12:10:57 / cg"
 !
 
+preferredLabelViewHeight
+    ^ labelView preferredHeight + (labelView margin + self verticalSpacing * 2).
+!
+
+recomputeLayout
+    "layout/visiblity of labelView changed
+    "
+    |newLyt lblLyt bOffset tOffset|
+
+"/self halt.
+"/    "/ adjust my topOffset, if labelView is shown.
+"/    labelView isVisible ifTrue:[
+"/        tOffset := labelView height. 
+"/    ] ifFalse:[
+"/        tOffset := 0.
+"/    ].
+"/    (tOffset ~~ self layout topOffset) ifTrue:[
+"/        self layout topOffset:tOffset.
+"/        self containerChangedSize
+"/    ].
+
+^ self.
+"/    lblLyt := newLyt copy.
+
+    labelView isVisible ifTrue:[
+        bOffset := self preferredLabelViewHeight.
+        tOffset := margin.
+        newLyt topOffset:1 + bOffset.
+    ] ifFalse:[
+        bOffset := -1.
+        tOffset := -2.
+        newLyt topOffset:margin.
+    ].
+"/    lblLyt bottomFraction:0 offset:bOffset.
+"/    lblLyt topFraction:0    offset:tOffset.
+"/    labelView layout:lblLyt.
+    super layout:newLyt.
+!
+
 rowFontAscent
     "returns the inset of a printable text in a row
     "
@@ -1385,12 +1441,12 @@
     "/ no - must compute even if not visible.
     "/ (could be invisible in a notebook ...)
     realized ifTrue:[                   "used to be: shown" 
-        labelView isVisible ifTrue:[
-            lyt := labelView layout.
-            lyt  leftOffset:(layout leftOffset).
-            lyt rightOffset:(layout rightOffset).
-            labelView layout:lyt.
-        ].
+"/        labelView isVisible ifTrue:[
+"/            lyt := labelView layout.
+"/            lyt  leftOffset:(layout leftOffset).
+"/            lyt rightOffset:(layout rightOffset).
+"/            labelView layout:lyt.
+"/        ].
         self fitColumns.
     ]
 !
@@ -1652,14 +1708,6 @@
     ]
 !
 
-invalidateX:x y:y width:w height:h
-    "invalidate a rectangle 
-    "
-    shown ifTrue:[
-        self invalidate:(Rectangle left:x top:y width:w height:h)
-    ]
-!
-
 redrawVisibleRow:aRow
     "redraw row if visible
     "
@@ -2952,13 +3000,6 @@
 
 !
 
-innerWidth
-    "returns the inner width of the contents shown
-    "
-    ^ width - margin - margin
-
-!
-
 verticalScrollStep
     "return the amount to scroll when stepping up/down.
     "
@@ -3018,7 +3059,9 @@
      dY      "{ Class:SmallInteger }"
      innerHG "{ Class:SmallInteger }"
      innerWT "{ Class:SmallInteger }"
+     lMargin
     |
+
     shown ifFalse:[
         ^ self
     ].
@@ -3082,17 +3125,30 @@
             self invalidate.
         ] ifFalse:[                             "/ COPY HORIZONTAL
             x0 := x1 := dX + margin.
-            w  := width - dX - margin.
-
-            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:false.
-
-            labelView notNil ifTrue:[
-                labelView copyFromX:x0 y:margin toX:x1 y:margin width:w invalidateX:x.
+            w  := width - dX.
+            lMargin := labelView margin.
+
+            dltOrg x < 0 ifTrue:[
+                " ->"
+                x0 := x := margin. 
+                self copyFrom:self x:margin y:margin toX:margin+dX y:margin width:innerWT-dX height:innerHG async:false.
+                self invalidateX:margin y:margin width:dX height:innerHG.
+
+                labelView notNil ifTrue:[
+                    labelView copyFrom:labelView x:lMargin y:lMargin toX:lMargin+dX y:lMargin width:labelView innerWidth-dX height:labelView innerHeight async:false.
+                    labelView invalidateX:lMargin y:lMargin width:dX height:labelView innerHeight.
+                ].
+            ] ifFalse:[
+                x1 := margin. x := w.
+                self copyFrom:self x:margin+dX y:margin toX:margin y:margin width:innerWT-dX height:innerHG async:false.
+                self invalidateX:width-margin-dX y:margin width:dX height:innerHG.
+
+                labelView notNil ifTrue:[
+                    labelView copyFrom:labelView x:lMargin+dX y:lMargin toX:lMargin y:lMargin width:labelView innerWidth-dX height:labelView innerHeight async:false.
+                    labelView invalidateX:labelView width-lMargin-dX y:lMargin width:dX height:labelView innerHeight.
+                ].
             ].
-            self invalidateX:x y:margin width:(width - w) height:innerHG.
+            labelView repairDamage.
         ]
     ].
     self originChanged:dltOrg.
@@ -3628,5 +3684,5 @@
 !DSVColumnView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DSVColumnView.st,v 1.139 2002-08-02 12:00:55 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DSVColumnView.st,v 1.140 2002-08-21 16:25:57 penk Exp $'
 ! !
--- a/DSVLabelView.st	Wed Aug 21 18:24:53 2002 +0200
+++ b/DSVLabelView.st	Wed Aug 21 18:25:59 2002 +0200
@@ -17,8 +17,8 @@
 "{ Package: 'stx:libwidg2' }"
 
 SimpleView subclass:#DSVLabelView
-	instanceVariableNames:'isVisible dataSet lineDrag columns selection enabled
-		preferredHeight handleCursor tabSpacing opaqueColumnResize'
+	instanceVariableNames:'dataSet lineDrag columns selection enabled preferredHeight
+		handleCursor tabSpacing opaqueColumnResize verticalLabelSpacing'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-DataSet'
@@ -66,8 +66,6 @@
                                                 entry, this action could be enabled or
                                                 disabled.
 
-        isVisible       <Boolean>               true if the labelView is shown
-
         preferredHeight <Integer>               the preferred height of the labelView
 
 
@@ -80,9 +78,6 @@
         DataSetColumn
         DataSetView
 "
-
-
-
 ! !
 
 !DSVLabelView class methodsFor:'accessing'!
@@ -104,20 +99,17 @@
 columns:aListOfColumns
     "the list of columns changed
     "
-    |layout|
+"/    |layout|
 
     columns         := aListOfColumns.
     preferredHeight := nil.
     selection       := nil.
 
-    isVisible ifTrue:[
-        dataSet layout:layout.
-    ].
-!
-
-level:aLevel
-    "ignorre; alway 0 relative to superView
-    "
+    self changed:#columnLayout.
+"/    dataSet recomputeLayout
+"/    isVisible ifTrue:[
+"/        dataSet layout:layout.
+"/    ].
 !
 
 opaqueColumnResize
@@ -126,26 +118,12 @@
 
 opaqueColumnResize:aBoolean
     opaqueColumnResize := aBoolean
-!
-
-preferredHeight
-
-    preferredHeight isNil ifTrue:[
-        preferredHeight := 0.
-
-        columns do:[:c|preferredHeight := (c label preferredHeight) max:preferredHeight ].
-
-        
-        preferredHeight := preferredHeight 
-                         + (margin + margin + dataSet horizontalSpacing * 2)
-    ].
-    ^ preferredHeight
 ! !
 
 !DSVLabelView methodsFor:'drawing'!
 
 invalidate
-    (shown and:[isVisible]) ifTrue:[
+    (shown) ifTrue:[
         super invalidate
     ]
 !
@@ -155,9 +133,9 @@
     "
     |cL xL xR hg|
 
-    (isVisible and:[shown]) ifTrue:[
+    (shown) ifTrue:[
         cL := columns at:anIndex ifAbsent:[^ nil].
-        xL := dataSet xVisibleOfColNr:anIndex.
+        xL := self xVisibleOfColNr:anIndex.
         xR := xL + cL width.
 
         (xL < width and:[xR > 0]) ifTrue:[
@@ -168,53 +146,9 @@
             self invalidate:(Rectangle left:xL top:margin width:(xR - xL) height:hg)
         ]
     ]
-
 !
 
-redrawEdgesX:x y:yTop width:aWidth height:aHeight
-    "redraw the edges in the range
-    "
-    |tabXL desc drawWidth
-     maxX "{ Class:SmallInteger }"
-     h    "{ Class:SmallInteger }"
-     x1   "{ Class:SmallInteger }"
-     x0   "{ Class:SmallInteger }"
-    |
-    maxX := (x + aWidth) min:(width - margin).
-    h    := height - margin - margin.
-    x1   := dataSet xVisibleOfColNr:1.
-
-    columns keysAndValuesDo:[:aKey :aCol|
-        desc := aCol description.
-        x0   := x1.
-        x1   := x1 + aCol width.
-
-        aKey == selection ifTrue:[
-            (x1 > x and:[x0 < maxX]) ifTrue:[
-                dataSet drawEdgesAtX:x0 y:margin width:(x1 - x0) height:h level:-1 on:self.
-            ].
-            tabXL notNil ifTrue:[drawWidth := x0 - tabXL].
-        ] ifFalse:[
-            desc labelHasButtonLayout ifFalse:[
-                tabXL notNil ifTrue:[drawWidth := x0 - tabXL].
-            ] ifTrue:[
-                tabXL isNil ifTrue:[tabXL := x0].
-                desc labelIsPartOfGroup ifFalse:[drawWidth := x1 - tabXL].
-            ]
-        ].
-        drawWidth notNil ifTrue:[
-            ((tabXL + drawWidth) > x and:[tabXL < maxX]) ifTrue:[
-                dataSet drawEdgesAtX:tabXL y:margin width:drawWidth height:h level:1 on:self.
-            ].
-            drawWidth := tabXL := nil.
-        ]
-    ].
-    tabXL notNil ifTrue:[
-        dataSet drawEdgesAtX:tabXL y:margin width:(x1 - tabXL) height:h level:1 on:self
-    ]
-!
-
-redrawX:x y:y width:w height:h
+redrawColumnsInX:x y:y width:w height:h
     "redraw a rectangle
     "
     |savClip bg fg fgColor bgColor
@@ -225,7 +159,7 @@
      x1     "{ Class:SmallInteger }"
      x0     "{ Class:SmallInteger }"
     |
-    (isVisible and:[shown]) ifFalse:[^ self].
+    (shown) ifFalse:[^ self].
 
     bgColor := dataSet backgroundColor.
     self paint:bgColor.
@@ -239,7 +173,7 @@
     lblH    := height - margin - margin.
     savClip := clipRect.
 
-    x1 := dataSet xVisibleOfColNr:1.
+    x1 := self xVisibleOfColNr:1.
 
     columns keysAndValuesDo:[:aKey :aCol| |anItem|
         anItem := aCol label.
@@ -268,11 +202,82 @@
                 bg := bgColor
             ].
 
-            self   paint:fg on:bg.
+            self   paint:fg on:bg.            
             anItem redrawX:x0 w:wt h:height inset:inset on:self.
         ]
     ].
-    self clippingRectangle:(Rectangle left:x top:y width:w height:h).
+!
+
+redrawEdgesX:x y:yTop width:aWidth height:aHeight
+    "redraw the edges in the range
+    "
+    |tabXL desc drawWidth
+     maxX "{ Class:SmallInteger }"
+     h    "{ Class:SmallInteger }"
+     x1   "{ Class:SmallInteger }"
+     x0   "{ Class:SmallInteger }"
+     y0   "{ Class:SmallInteger }"
+     absLabelLevel
+    |
+
+    maxX := (x + aWidth) min:(width - margin).
+    absLabelLevel := 1.
+    x1   := self xVisibleOfColNr:1.
+
+    y0 := margin.
+    h  := height - margin - margin.
+"/    margin >= absLabelLevel ifTrue:[
+"/        y0 := y0 - absLabelLevel.
+"/        h := h + absLabelLevel+absLabelLevel.
+"/    ].
+    columns keysAndValuesDo:[:aKey :aCol|
+        desc := aCol description.
+        x0   := x1.
+        x1   := x1 + aCol width.
+
+        aKey == selection ifTrue:[
+            (x1 > x and:[x0 < maxX]) ifTrue:[
+                dataSet drawEdgesAtX:x0 y:y0 width:(x1 - x0) height:h level:(absLabelLevel negated) on:self.
+            ].
+            tabXL notNil ifTrue:[drawWidth := x0 - tabXL].
+        ] ifFalse:[
+            desc labelHasButtonLayout ifFalse:[
+                tabXL notNil ifTrue:[drawWidth := x0 - tabXL].
+            ] ifTrue:[
+                tabXL isNil ifTrue:[tabXL := x0].
+                desc labelIsPartOfGroup ifFalse:[drawWidth := x1 - tabXL].
+            ]
+        ].
+        drawWidth notNil ifTrue:[
+            ((tabXL + drawWidth) > x and:[tabXL < maxX]) ifTrue:[
+                dataSet drawEdgesAtX:tabXL y:y0 width:drawWidth height:h level:absLabelLevel on:self.
+            ].
+            drawWidth := tabXL := nil.
+        ]
+    ].
+    tabXL notNil ifTrue:[
+        dataSet drawEdgesAtX:tabXL y:y0 width:(x1 - tabXL) height:h level:absLabelLevel on:self
+    ].
+
+    x1 < (maxX - absLabelLevel - absLabelLevel - 3) ifTrue:[
+        dataSet drawEdgesAtX:x1 y:y0 width:(width-margin-x1-absLabelLevel) height:h level:absLabelLevel on:self
+    ].
+!
+
+redrawX:x y:y width:wArg height:h
+    |savClip w|
+
+    (shown) ifFalse:[^ self].
+
+    w := wArg.
+    self redrawColumnsInX:x y:y width:w height:h.
+
+    super redrawX:x y:y width:w height:h.
+
+"/    (x + w) >= (width-margin) ifTrue:[
+"/        w := (width-margin) - 1 - x.
+"/    ].
+    self clippingRectangle:(Rectangle left:x top:margin width:w height:height-margin-margin).
     self redrawEdgesX:x y:y width:w height:h.
     self clippingRectangle:savClip.
 ! !
@@ -308,7 +313,7 @@
     col := columns at:idx ifAbsent:nil.
 
     (col notNil and:[col isResizeable]) ifTrue:[
-        x1 := dataSet xVisibleOfColNr:(idx + 1).
+        x1 := self xVisibleOfColNr:(idx + 1).
         (x between:(x1-tabSpacing) and:(x1+tabSpacing))
         "/ x + tabSpacing > x1 
         ifTrue:[
@@ -325,7 +330,7 @@
     "
     |x1 idx col|
 
-    (isVisible and:[enabled and:[shown]]) ifFalse:[
+    (enabled and:[shown]) ifFalse:[
         ^ self
     ].
 
@@ -336,7 +341,7 @@
         col := columns at:idx ifAbsent:nil.
 
         col isResizeable ifTrue:[
-            x1 := dataSet xVisibleOfColNr:(idx + 1).
+            x1 := self xVisibleOfColNr:(idx + 1).
             (x between:(x1-tabSpacing) and:(x1+tabSpacing))
             ifTrue:[
                 col := columns at:idx ifAbsent:nil.
@@ -421,7 +426,7 @@
     "
     |x0 x1|
 
-    x1 := dataSet xVisibleOfColNr:1.
+    x1 := self xVisibleOfColNr:1.
 
     columns keysAndValuesDo:[:index :aCol|
         x0 := x1.
@@ -434,33 +439,37 @@
     ^ 0
 ! !
 
+!DSVLabelView methodsFor:'initialization'!
+
+initStyle
+    super initStyle.
+
+    handleCursor := (VariablePanel cursorForOrientation:#horizontal onDevice:device) onDevice:device.
+    font := (self class defaultFont).
+    "/ self level:0.
+    self level:(StyleSheet at:#'dataSet.labelView.level' default:-1).
+    verticalLabelSpacing := (StyleSheet at:#'dataSet.labelView.verticalSpace' default:2).
+!
+
+initialize
+    super initialize.
+    "/ super level:(self defaultLevel).
+
+    enabled    := true.
+    columns    := #().
+    tabSpacing := self class tabSpacing.
+
+    self enableMotionEvents.
+! !
+
 !DSVLabelView methodsFor:'instance creation'!
 
 for:aColumnView
     "initialization
     "
     dataSet   := aColumnView.
-    self level:(dataSet level).
-    self borderWidth:(dataSet borderWidth).
-!
-
-initStyle
-    super initStyle.
-
-    handleCursor := (VariablePanel cursorForOrientation:#horizontal onDevice:device) onDevice:device.
-    font := (self class defaultFont).
-!
-
-initialize
-    super initialize.
-    super level:0.
-
-    enabled    := true.
-    isVisible  := true.
-    columns    := #().
-    tabSpacing := self class tabSpacing.
-
-    self enableMotionEvents.
+"/    self level:(dataSet level).
+"/    self borderWidth:(dataSet borderWidth).
 !
 
 realize
@@ -468,7 +477,6 @@
     "
     self  bitGravity:#NorthWest.
     super realize.
-
 ! !
 
 !DSVLabelView methodsFor:'queries'!
@@ -485,16 +493,31 @@
     enabled := aState.
 !
 
-isVisible
-    ^ isVisible
+isVisible:aBool
+
+    aBool ~~ self isVisible ifTrue:[
+"/        dataSet layout:nil.
+        super isVisible:aBool.
+        dataSet recomputeLayout.
+    ].
 !
 
-isVisible:aBool
+preferredHeight
+    |h|
+
+    preferredHeight notNil ifTrue:[
+        ^ preferredHeight
+    ].
 
-    aBool ~~ isVisible ifTrue:[
-        isVisible := aBool.
-        dataSet layout:nil.
-    ].
+    h := 0.
+    columns do:[:c | h := (c label preferredHeight) max:h ].
+    ^ self margin + verticalLabelSpacing + h + verticalLabelSpacing + self margin
+!
+
+xVisibleOfColNr:colNr
+    "/ must adjust, because dataset includes its own margin, which might be different from ours
+
+    ^ (dataSet xVisibleOfColNr:colNr) - dataSet margin + margin
 !
 
 xVisibleToSelectionIndex:x
@@ -503,7 +526,7 @@
     "
     |index column|
 
-    (isVisible and:[enabled]) ifTrue:[
+    (shown and:[enabled]) ifTrue:[
         (     (index  := dataSet xVisibleToColNr:x)  notNil
          and:[(column := columns at:index ifAbsent:nil) notNil
          and:[column label isSelectable]]
@@ -518,7 +541,7 @@
 
 copyFromX:x0 y:y0 toX:x1 y:y1 width:w invalidateX:leftX
 
-    (shown and:[isVisible]) ifFalse:[^ self].
+    (shown) ifFalse:[^ self].
 
     (self sensor hasDamageFor:self) ifTrue:[
         self invalidate
@@ -592,5 +615,5 @@
 !DSVLabelView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DSVLabelView.st,v 1.41 2001-10-10 14:10:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DSVLabelView.st,v 1.42 2002-08-21 16:25:51 penk Exp $'
 ! !
--- a/DataSetView.st	Wed Aug 21 18:24:53 2002 +0200
+++ b/DataSetView.st	Wed Aug 21 18:25:59 2002 +0200
@@ -16,7 +16,7 @@
 "{ Package: 'stx:libwidg2' }"
 
 ScrollableView subclass:#DataSetView
-	instanceVariableNames:''
+	instanceVariableNames:'labelView rememberedTopOffsetOfScrolledView'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-DataSet'
@@ -268,17 +268,104 @@
 "
 ! !
 
+!DataSetView methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    changedObject == scrolledView ifTrue:[
+        (something == #sizeOfView) ifTrue:[
+           self recomputeLabelLayout.
+        ].
+    ].
+    changedObject == labelView ifTrue:[
+        ((something == #visibility)
+        or:[something == #columnLayout]) ifTrue:[
+            self recomputeLayouts.
+            ^ self
+        ].
+        
+    ].
+
+    super update:something with:aParameter from:changedObject
+! !
+
 !DataSetView methodsFor:'initialize / release'!
 
 initialize
     "set column area
     "
+    |columnView|
+
     "/ preset flags to avoid creation and later destruction of scrollBars ...
     self setVertical:true mini:false horizontal:true mini:true.
     super initialize.
 
     self setupVertical:true mini:false horizontal:true mini:true.
-    self scrolledView:(DSVColumnView new labelView:(DSVLabelView in:self)).
+
+    labelView := DSVLabelView in:self.
+    columnView := DSVColumnView new.
+    columnView labelView:labelView.
+
+    columnView addDependent:self.
+    labelView addDependent:self.
+
+    self scrolledView:columnView.
+! !
+
+!DataSetView methodsFor:'layout computation'!
+
+recomputeLabelLayout
+    |columnView columnViewLayout newLeft newRight|
+
+    columnView := self scrolledView.
+    columnView isNil ifTrue:[^ self].
+    (columnViewLayout := columnView layout) isNil ifTrue:[^ self].
+
+    newLeft := columnViewLayout leftOffset.
+    newRight := columnViewLayout rightOffset.
+    (newLeft ~~ labelView layout leftOffset
+    or:[ newRight ~~ labelView layout rightOffset]) ifTrue:[
+        labelView layout leftOffset:newLeft.
+        labelView layout rightOffset:newRight.
+        labelView isVisible ifTrue:[labelView containerChangedSize]
+    ].
+!
+
+recomputeLayouts
+    |columnView columnViewLayout newOffset|
+
+    columnView := self scrolledView.
+    columnView isNil ifTrue:[^ self].
+    (columnViewLayout := columnView layout) isNil ifTrue:[^ self].
+
+    labelView isVisible ifFalse:[
+        newOffset := scrolledViewLayout topOffset.
+    ] ifTrue:[
+        newOffset := scrolledViewLayout topOffset + (columnView preferredLabelViewHeight).
+    ].
+
+    newOffset ~~ columnViewLayout topOffset ifTrue:[
+        columnViewLayout topOffset:newOffset.
+        columnView shown ifTrue:[
+            columnView containerChangedSize.
+        ]
+    ].
+    labelView containerChangedSize.
+!
+
+scrolledViewLayout:aLayout
+    "invoked by superclasses setLayout method, whenever the scrolled views
+     layout changes (due to added/removed scrollbars)."
+
+    |modifiedLayout originalTopOffset|
+
+    "/ always copy - since layout it destructively modified in #recomputeLayouts
+    modifiedLayout := aLayout copy.    
+    labelView isVisible ifTrue:[
+        originalTopOffset := scrolledViewLayout topOffset.
+        modifiedLayout topOffset:(originalTopOffset + labelView height).
+        labelView layout topOffset:originalTopOffset.
+    ].
+    super scrolledViewLayout:modifiedLayout
 ! !
 
 !DataSetView methodsFor:'queries'!
@@ -292,5 +379,5 @@
 !DataSetView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.32 2002-04-10 10:48:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.33 2002-08-21 16:25:59 penk Exp $'
 ! !