DataSetView.st
changeset 646 4cbd9dd64372
parent 637 e56ec99923ae
child 647 ee98a1976972
--- a/DataSetView.st	Sat Jan 03 18:30:43 1998 +0100
+++ b/DataSetView.st	Sat Jan 03 18:32:12 1998 +0100
@@ -369,97 +369,6 @@
 "
 ! !
 
-!DataSetView class methodsFor:'test'!
-
-ptest:as3D
-    |t1 top scr clDc rows slct list bool tmArr listModel|
-
-    top  := StandardSystemView new label:'select'; extent:600@440.
-    scr  := DataSetView origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
-
-    clDc := OrderedCollection new.
-    rows := OrderedCollection new.
-    list := #( 'Text ' 'Field ' 'C-Box ' 'C-List ' true ).
-    slct := #( #text   #field   #cbox    #clist    #toggle ).
-    bool := true.
-
-    clDc add:( DataSetColumnSpec label:'Text'   editorType:#None        selector:#text ).
-    clDc add:( DataSetColumnSpec label:'Field'  editorType:#InputField  selector:#field ).
-    clDc add:( DataSetColumnSpec label:'C-Box'  editorType:#ComboBox    selector:#cbox ).
-    clDc add:( DataSetColumnSpec label:'C-List' editorType:#ComboList   selector:#clist ).
-    clDc add:( DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).
-
-    scr columnDescriptors:clDc.
-    scr beDependentOfRows:false.
-    scr has3Dseparators:as3D.
-
-    top openAndWait.
-    tmArr := Array new:4.
-    listModel := List new.
-    scr listHolder:listModel.
-
-    (1 to:tmArr size) do:[:i|
-        listModel removeAll.
-
-        t1 := Time millisecondsToRun:[
-            1 to:200 do:[:i| |values|
-                values := list collect:[:n|
-                    n isString ifTrue:[n, i printString]
-                              ifFalse:[n == true ifTrue:[bool] ifFalse:[n]]
-                ].
-                listModel add:(Structure newWith:slct values:values).
-                bool := bool not.
-
-                i even ifTrue:[
-                    listModel removeFirst
-                ]       
-            ].
-        ].
-        tmArr at:i put:t1
-    ].
-    t1 := 0.
-
-    Transcript showCR:'----------'.
-    tmArr do:[:t|
-        t1 := t1 + t.
-        Transcript showCR:'TIME : ', t printString.
-    ].
-    Transcript showCR:'----------'.
-    Transcript showCR:'DIFF : ', (t1 // tmArr size) printString.
-    top destroy.
-
-
-
-!
-
-test:as3D
-    |top scr columns rows bool rdWtSel|
-
-    top  := StandardSystemView new label:'select'; extent:700@440.
-    scr  := DataSetView origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
-    scr has3Dseparators:as3D.
-
-    columns := OrderedCollection new.
-    rows    := OrderedCollection new.
-    bool    := true.
-    rdWtSel := #( #at: #at:put: ).
-
-    1 to:11 do:[:i||n|
-        n := i printString.
-        rows add:(Array with:('text: ', n) with:('input: ', n) with:bool).
-        bool := bool not.
-    ].
-
-    columns add:(DataSetColumnSpec label:'Text'   editorType:#None        selector:rdWtSel).
-    columns add:(DataSetColumnSpec label:'Input'  editorType:#InputField  selector:rdWtSel).
-    columns add:(DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:rdWtSel).
-
-    scr columnDescriptors:columns.
-    scr list:rows.
-    top open.
-
-! !
-
 !DataSetView methodsFor:'accessing'!
 
 add:aRow
@@ -616,6 +525,42 @@
 
 !DataSetView methodsFor:'change & update'!
 
+recomputeLabels
+    "labels changed; recompute labels
+    "
+    |hgt lbl prv lst|
+
+    labels size ~~ 0 ifTrue:[ labels do:[:b| b destroy] ].
+    labels := OrderedCollection new.
+
+    columnView numberOfColumns == 0 ifTrue:[
+        ^ self
+    ].
+
+    hgt := 0.
+    prv := nil.
+    lst := columnView lastColumn.
+
+    columnView columnsDo:[:aCol|
+        (aCol showColSeparator or:[aCol == lst]) ifTrue:[
+            lbl := DSVLabelView column:(prv ? aCol) in:self.
+            prv := nil.
+            hgt := (lbl preferredExtent y) max:hgt.
+            labels add:lbl.
+        ] ifFalse:[
+            (prv isNil and:[aCol label notNil]) ifTrue:[prv := aCol]
+        ]
+    ].
+
+    columnView superView origin:( 0.0 @ (hgt + 10) ).
+
+    realized ifTrue:[
+        self updateLabels.
+        labels do:[:l| l realize ].
+    ]
+
+!
+
 update:what with:aPara from:chgObj
     "one of my models changed
     "
@@ -673,77 +618,53 @@
         ^ self
     ].
 
-    what == #style ifTrue:[
-        ^ self updateLabels
-    ].
+    what == #style         ifTrue:[ ^ self updateLabels ].
+    what == #sizeOfColumns ifTrue:[ ^ self recomputeLabels ].
 
-    what ~~ #sizeOfColumns ifTrue:[
-        shown ifTrue:[
-            what == #sizeOfContents ifTrue:[
-                columnView sizeOfListChanged ifFalse:[
-                    self updateLabels.
-                ].
-            ] ifFalse:[
-                what == #originOfContents ifTrue:[
-                    (labels size ~~ 0 and:[(val := aPara x) ~~ 0]) ifTrue:[
-                        labels do:[:b| b origin:((b origin) - (val @ 0)) ]
-                    ]
+    shown ifTrue:[
+        what == #sizeOfContents ifTrue:[
+            columnView sizeOfListChanged ifFalse:[
+                self updateLabels.
+            ].
+        ] ifFalse:[
+            what == #originOfContents ifTrue:[
+                (labels size ~~ 0 and:[(val := aPara x) ~~ 0]) ifTrue:[
+                    labels do:[:b| b origin:((b origin) - (val @ 0)) ]
                 ]
             ]
-        ].
-        ^ self
-    ].
-
-    labels size ~~ 0 ifTrue:[
-        labels do:[:b| b destroy].
+        ]
     ].
-    spv    := columnView superView.
-    labels := OrderedCollection new.
-
-    columnView numberOfColumns == 0 ifTrue:[
-        spv origin:( 0.0 @ 0.0 ).
-    ] ifFalse:[
-        h  := 0.
-        bg := columnView backgroundColor.
-        ft := columnView font.
-
-        columnView columnsDo:[:aCol||b|
-            b := DSVLabelView column:aCol in:self.
-            h := (b preferredExtent y) max:h.
-            labels add:b.
-        ].
-        h := h + 10.
-        spv origin:( 0.0 @ h ).
-
-        realized ifTrue:[
-            self updateLabels.
-            labels do:[:l| l realize ].
-        ]
-    ]
 !
 
 updateLabels
-    "labels changed; recompute labels
+    "layout of labels changed; recompute layout
     "
-    |x0 x1 pt dX y|
+    |x0 x1 pt dX y id lst|
 
-    labels size ~~ 0 ifTrue:[
-        pt := device translatePoint:(0@0) from:(columnView id) to:(self id).
-        x0 := columnView leftInset + columnView margin + pt x. 
-        x0 := x0 - columnView xOriginOfContents.
+    labels size == 0 ifTrue:[ ^ self ].
 
-        dX := columnView separatorSize - 1.
-        y  := (columnView superView origin y) - 1.
+    pt  := device translatePoint:(0@0) from:(columnView id) to:(self id).
+    x0  := columnView leftInset + columnView margin + pt x. 
+    x0  := x0 - columnView xOriginOfContents.
+    dX  := columnView separatorSize - 1.
+    y   := (columnView superView origin y) - 1.
+    lst := columnView lastColumn.
+    id  := 1.
+    x1  := 0.
 
-        labels keysAndValuesDo:[:i :bt|
-            x1 := (columnView columnAt:i) width.
-            bt origin:(x0 @ 1) extent:(x1 - dX @ y).
+    columnView columnsDo:[:aCol|
+        x1 := x1 + aCol width.
+
+        (aCol showColSeparator or:[aCol == lst]) ifTrue:[
+            (labels at:id) origin:(x0 @ 1) extent:(x1 - dX @ y).
             x0 := x0 + x1.
-        ].
+            x1 := 0.
+            id := id + 1.
+        ]
+    ].
 
-        scrollerInsetView bottomInset:((y + 1) negated).
-        scrollerInsetView raise.
-    ].
+    scrollerInsetView bottomInset:((y + 1) negated).
+    scrollerInsetView raise.
 ! !
 
 !DataSetView methodsFor:'change & update list'!
@@ -893,5 +814,5 @@
 !DataSetView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.7 1998-01-02 15:58:24 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.8 1998-01-03 17:32:12 ca Exp $'
 ! !