DataSetView.st
author Claus Gittinger <cg@exept.de>
Sun, 14 Feb 1999 16:46:57 +0100
changeset 1200 0d5be0a2bb21
parent 1187 544b83216038
child 1314 c98924f94a97
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1997 by Claus Gittinger / eXept Software AG
              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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"




View subclass:#DataSetView
	instanceVariableNames:'labelView columnView listHolder useIndex scrolledView'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-DataSet'
!

!DataSetView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by Claus Gittinger / eXept Software AG
              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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"



!

documentation
"
    This class implements a selection list view based on rows and columns.
    It allows for the dynamic editing of this information.

    [author:]
        Claus Atzkern

    [see also:]
        DataSetColumnSpec
        DataSetColumn
        DSVColumnView
"
!

examples
"
    example 1: list with valid rows of type Array
                                                                                [exBegin]
    |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.

    columns := OrderedCollection new.
    rows    := OrderedCollection new.
    bool    := true.
    rdWtSel := #( #at: #at:put: ).

    1 to:1000 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.
                                                                                [exEnd]



    example 2: list with none valid rows; defining #rowIfAbsent: block
                                                                                [exBegin]
    |top scr columns bool rdWtSel|

    top  := StandardSystemView new label:'select'; extent:700@440.
    scr  := DataSetView origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.

    columns := OrderedCollection new.
    bool    := true.
    rdWtSel := #( #at: #at:put: ).

    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 rowIfAbsent:[:i|
        bool := bool not.
        Array with:('text: ', i printString) with:('input: ') with:bool
    ].

    scr columnDescriptors:columns.
    scr list:(Array new:1000).
    top open.
                                                                                [exEnd]



    example 3: list with valid rows of type Structure
                                                                                [exBegin]
    |top scr clDc rows slct list idx bool|

    top  := StandardSystemView new label:'select'; extent:700@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    #( 'foo' 'bar' 'baz' ) ).
    slct := #( #text   #field   #cbox    #clist    #toggle #choices               ).
    idx  := 11.
    bool := true.

    20 timesRepeat:[ |values|
        values := list collect:[:n|
            n isString ifTrue:[n, idx printString]
                      ifFalse:[n == true ifTrue:[bool] ifFalse:[n]]
        ].
        rows add:(Structure newWith:slct values:values).
        bool := bool not.
        idx  := idx + 1.
    ].
    clDc add:( DataSetColumnSpec label:'Text'   editorType:#None        selector:#text ).
    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 last choices:#choices.
    clDc add:( DataSetColumnSpec label:'C-List' editorType:#ComboList   selector:#clist ).
    clDc last choices:#choices.
    clDc add:( DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).

    scr has3Dseparators:true.
    scr columnDescriptors:clDc.
    scr list:rows.
    top open.
                                                                                [exEnd]




    example 4: table includes a row selector and multiple select is enabled
                                                                                [exBegin]
    |top scr clDc rows slct list idx bool|

    top  := StandardSystemView new label:'select'; extent:700@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    #( 'foo' 'bar' 'baz' ) ).
    slct := #( #text   #field   #cbox    #clist    #toggle #choices               ).
    idx  := 11.
    bool := true.

    20 timesRepeat:[ |values|
        values := list collect:[:n|
            n isString ifTrue:[n, idx printString]
                      ifFalse:[n == true ifTrue:[bool] ifFalse:[n]]
        ].
        rows add:(Structure newWith:slct values:values).
        bool := bool not.
        idx  := idx + 1.
    ].
    clDc add:( DataSetColumnSpec rowSelector ).
    clDc add:( DataSetColumnSpec label:'Text'   editorType:#None        selector:#text ).
    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 last choices:#choices.
    clDc add:( DataSetColumnSpec label:'C-List' editorType:#ComboList   selector:#clist ).
    clDc last choices:#choices.
    clDc add:( DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).

    scr has3Dseparators:true.
    scr columnDescriptors:clDc.
    scr multipleSelectOk:true.
    scr list:rows.
    top open.
                                                                                [exEnd]




    example 5: performance test; with valid rows
                                                                                [exBegin]
    |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:false.

    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.
                                                                                [exEnd]



    example 6: performance test; with invalid rows: defining #rowIfAbsent:.
                                                                                [exBegin]
    |t1 top scr clDc rows slct list bool tmArr listModel ctr|

    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 ).
    ctr := 0.

    scr rowIfAbsent:[:i||values|
        bool := bool not.
        ctr := ctr + 1.
        values := list collect:[:n|
            n isString ifTrue:[n, ctr printString]
                      ifFalse:[n == true ifTrue:[bool] ifFalse:[n]]
        ].
        Structure newWith:slct values:values
    ].

    scr columnDescriptors:clDc.
    scr beDependentOfRows:false.
    scr has3Dseparators:true.

    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|
                  listModel add:nil.
                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.
                                                                                [exEnd]



    example 7: images as label
                                                                                [exBegin]

    |lbl top scr clDc rows slct list idx bool|

    top  := StandardSystemView new label:'select'; extent:400@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    #( 'foo' 'bar' 'baz' ) ).
    slct := #( #text   #field   #cbox    #clist    #toggle #choices               ).
    idx  := 11.
    bool := true.

    20 timesRepeat:[ |values|
        values := list collect:[:n|
            n isString ifTrue:[n, idx printString]
                      ifFalse:[n == true ifTrue:[bool] ifFalse:[n]]
        ].
        rows add:(Structure newWith:slct values:values).
        bool := bool not.
        idx  := idx + 1.
    ].
    lbl := Image fromFile:('gifImages/nexthand.gif' ).

    clDc add:( DataSetColumnSpec label:lbl      editorType:#None        selector:#text ).
    clDc add:( DataSetColumnSpec label:'Text'   editorType:#None        selector:#text ).
    clDc add:( DataSetColumnSpec label:'Field'  editorType:#InputField  selector:#field ).

    lbl := Image fromFile:('xpmBitmaps/misc_tools/box_full.xpm' ).
    clDc add:( DataSetColumnSpec label:lbl      editorType:#ComboBox    selector:#cbox ).
    clDc last choices:#choices.
    clDc add:( DataSetColumnSpec label:'C-List' editorType:#ComboList   selector:#clist ).
    clDc last choices:#choices.
    clDc add:( DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).

    scr has3Dseparators:true.
    scr columnDescriptors:clDc.
    scr list:rows.
    top open.
                                                                                [exEnd]



"
! !

!DataSetView class methodsFor:'test'!

test
    |top scr clDc rows slct list bool spc img model idx size|

    top  := StandardSystemView new label:'select'; extent:600@500.
    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    #( 'foo' 'bar' 'baz' ) ).
    slct := #( #text   #field   #cbox    #clist    #toggle #choices               ).
    bool := true.

    10 to:30 do:[:i| |values|
        values := list collect:[:n|
            n isString ifTrue:[n, i printString]
                      ifFalse:[n == true ifTrue:[bool] ifFalse:[n]]
        ].
        rows add:(Structure newWith:slct values:values).
        bool := bool not.
    ].
    clDc add:( spc := DataSetColumnSpec label:'Text'   editorType:#None        selector:#text ).
    spc labelAlignment:#left.

    img := Image fromFile:('xpmBitmaps/misc_tools/box_full.xpm' ).
    clDc add:( spc := DataSetColumnSpec label:img   editorType:#None        selector:#text ).
    spc labelAlignment:#right.

    img := Image fromFile:('xpmBitmaps/misc_tools/box_full.xpm' ).
    clDc add:( spc := DataSetColumnSpec label:img  editorType:#InputField  selector:#field ).
    spc labelAlignment:#left.

    img := Image fromFile:('xpmBitmaps/misc_tools/box_full.xpm' ).
    clDc add:( spc := DataSetColumnSpec label:(LabelAndIcon icon:img string:'Combo')  editorType:#ComboBox    selector:#cbox ).
    spc labelAlignment:#center.
    spc choices:#choices.

    clDc add:( spc := DataSetColumnSpec label:'C-List' editorType:#ComboList   selector:#clist ).
    spc choices:#choices.
    clDc add:( spc := DataSetColumnSpec label:'Toggle' editorType:#CheckToggle selector:#toggle ).
    clDc do:[:el|
        el minWidth:80.
        el labelActionSelector:#dummy.
    ].
    scr has3Dseparators:true.
    model := ValueHolder new.
    model value:clDc.
    scr columnHolder:model.
    "/ scr columnDescriptors:clDc.
    scr list:rows.
    top open.
    Delay waitForSeconds:1.

    idx  := 1.
    size := clDc size.

    [top shown] whileTrue:[|coll|
"/        coll := OrderedCollection new:size.
"/        clDc keysAndValuesDo:[:i :c|
"/            i ~~ idx ifTrue:[coll add:c]
"/        ].
"/        idx == size ifTrue:[idx := 1]
"/                   ifFalse:[idx := idx + 1].
"/        model value:coll.
"/        Delay waitForSeconds:0.5.
        scr showLabels:(scr showLabels not).
        Delay waitForSeconds:2.
        
    ].
    Transcript showCR:'READY'.

! !

!DataSetView methodsFor:'accessing'!

add:aRow
    "add a row; reimplemented caused by add in base class
    "
    ^ columnView add:aRow
!

columnView
    "returns my scrolledView
    "
    ^ columnView
!

labelView
    ^ labelView
!

scrolledView
    "returns my scrolledView
    "
    ^ columnView
!

useIndex
    "specify, if the selected components value or its index in the
     list should be sent to the model. The default is its index.
    "
    ^ useIndex
!

useIndex:aBool
    "specify, if the selected components value or its index in the
     list should be sent to the model. The default is its index.
    "
    useIndex := aBool
! !

!DataSetView methodsFor:'accessing look'!

font:aFont
    "set the font for all rows and labels.
    "
    columnView font:aFont
!

horizontalMini:aBool
    "control the horizontal scrollBar to be either a miniScroller,
     or a full scrollBar.
    "
    scrolledView horizontalMini:aBool.
    self columnsSizeChanged.
!

horizontalScrollable:aBool
    "enable/disable horizontal scrollability.
     If disabled, the horizontal scrollBar is made invisible.
    "
    scrolledView horizontalScrollable:aBool.
    self columnsSizeChanged.
!

isHorizontalScrollable
    "returns true if horizontal scrollable
    "
    ^ scrolledView isHorizontalScrollable
!

isVerticalScrollable
    "returns true if vertical scrollable
    "
    ^ scrolledView isVerticalScrollable
!

showLabels
    "control the labels view to be visible or unvisible
    "
    ^ labelView notNil

!

showLabels:aState
    "control the labels view to be visible or unvisible
    "
    |saveLabel|

    labelView isNil ifTrue:[
        aState ifTrue:[
            labelView := DSVLabelView origin:(0.0 @ 0.0) corner:(1.0 @ 0.0) in:self.
            labelView for:columnView.

            self shown ifTrue:[
                labelView realize
            ].
            columnView columnDescriptors:(columnView columnDescriptors).
        ]
    ] ifFalse:[
        aState ifFalse:[
            saveLabel := labelView.
            labelView := nil.
            saveLabel destroy.
            scrolledView topInset:0
        ]
    ].

!

verticalMini:aBool
    "control the vertical scrollBar to be either a miniScroller,
     or a full scrollBar.
    "
    scrolledView verticalMini:aBool.
    self columnsSizeChanged.

!

verticalScrollable:aBool
    "enable/disable vertical scrollability.
     If disabled, the horizontal scrollBar is made invisible.
    "
    scrolledView verticalScrollable:aBool.
    self columnsSizeChanged
!

viewBackground
    "get the background color of the rows and labels
    "
    ^ columnView backgroundColor.


!

viewBackground:aColor
    "set the background color of the rows and labels
    "
    ^ columnView backgroundColor:aColor.


! !

!DataSetView methodsFor:'accessing menus'!

menuHolder:anObject
    "set the menu holder in the column view too
    "
    super menuHolder:anObject.
    columnView menuHolder:anObject.

!

menuMessage:aSymbol
    "set the menu message in the column view too
    "
    super menuMessage:aSymbol.
    columnView menuMessage:aSymbol.

!

menuPerformer:anObject
    "set the performer in the column view too
    "
    super menuPerformer:anObject.
    columnView menuPerformer:anObject.

! !

!DataSetView methodsFor:'accessing mvc'!

columnAdaptor
    ^ columnView columnAdaptor

    "Modified: / 26.7.1998 / 12:16:17 / cg"
    "Created: / 27.7.1998 / 09:50:58 / cg"
!

columnAdaptor:someone
    columnView columnAdaptor:someone

    "Created: / 26.7.1998 / 12:04:31 / cg"
    "Modified: / 26.7.1998 / 12:16:17 / cg"
!

listAt:index put:newElement
    "kludge callback, when an element hs to be replaced
     due to a col-adaptor returning a new row element"

    listHolder value at:index put:newElement

    "Created: / 7.8.1998 / 22:18:11 / cg"
    "Modified: / 7.8.1998 / 22:21:00 / cg"
!

listHolder:aListHolder
    "set the valueHolder which holds the list of rows
    "
    listHolder ~~ aListHolder ifTrue:[
        listHolder notNil ifTrue:[
            listHolder removeDependent:self
        ].

        (listHolder := aListHolder) notNil ifTrue:[
            listHolder addDependent:self
        ]
    ].
    columnView pushEvent:#list: with:(listHolder value).
!

model:aModel
    "set the valueHolder which holds the selection and maybe the list of rows
    "
    (model respondsTo:#list) ifTrue:[
        (model list == listHolder) ifTrue:[
            self listHolder:nil
        ]
    ].
    super model:aModel.

    aModel notNil ifTrue:[
        (aModel respondsTo:#list) ifTrue:[
            self listHolder:model list
        ]
    ]
! !

!DataSetView methodsFor:'change & update'!

columnsSizeChanged
    "recompute label view
    "
    |pL pR|

    (realized and:[labelView notNil]) ifFalse:[
        ^ self
    ].

    pL := device translatePoint:(0@0) from:(columnView id) to:(self id).
    pR := device translatePoint:((columnView width) @ 0) from:(columnView id) to:(self id).

    labelView leftInset:pL x - 1.
    labelView rightInset:(self width - pR x).

    labelView columnsSizeChanged.
    scrolledView topInset:(labelView height).

!

update:what with:aPara from:chgObj
    "one of my models changed
    "
    |val|

    chgObj == columnView ifTrue:[
        what == #selection ifTrue:[
            model notNil ifTrue:[
                val := columnView selectedRowIndex copy.

                (model respondsTo:#selectionIndex:) ifTrue:[
                    model selectionIndex:val
                ] ifFalse:[
                    useIndex ifFalse:[ model value:(columnView selectedRow) ]
                              ifTrue:[ model value:val ]
                ]
            ].
            ^ self
        ].

        (realized and:[labelView notNil]) ifTrue:[
            what == #sizeOfColumns    ifTrue:[ ^ self columnsSizeChanged ].
            what == #columnsLayout    ifTrue:[ ^ labelView columnsLayoutChanged ].
            what == #originOfContents ifTrue:[ ^ labelView columnsOriginChanged:aPara ].
        ].
        ^ self
    ].

    chgObj == model ifTrue:[
        (what == #selectionIndex or:[what == #selection]) ifTrue:[
            ^ columnView selectRowIndex:(model selectionIndex copy)
        ].
        what == #list ifTrue:[
            ^ self listHolder:model list
        ].
        model == listHolder ifFalse:[
            what == #value ifTrue:[
                columnView selectRowIndex:model value
            ].
            ^ self
        ].
    ].

    "/ listHolder and model could be the same

    chgObj == listHolder ifTrue:[
        what == #at: ifTrue:[
            columnView at:aPara put:(listHolder at:aPara)
        ] ifFalse:[
            (what isNil or:[what == #list or:[what == #size or:[what == #value]]]) ifTrue:[
                ^ self listHolder:listHolder        "/ reread list from model
            ].
            what == #selectionIndex ifTrue:[
                ^ self
            ].
            self perform:what with:aPara
        ]
    ].
! !

!DataSetView methodsFor:'change & update list'!

insert:anIndex
    "raised from listHolder: insert row derived from listHolder at anIndex
    "
    |list|

    list := listHolder value.
    columnView add:(list at:anIndex) beforeIndex:anIndex


!

insertCollection:anArray
    "raised from listHolder: insert collection of rows derived from listHolder
     from start (anArray at:1) to stop (anArray at:2).
    "
    |start stop size list|

    list  := listHolder value.
    start := anArray at:1.
    size  := anArray at:2.

    size ~~ 0 ifTrue:[
        stop := start + size - 1.
        columnView addAll:(list copyFrom:start to:stop) beforeIndex:start
    ]
!

remove:anIndex
    "raised from listHolder: remove row at anIndex
    "
    columnView removeIndex:anIndex


!

removeFrom:anArray
    "raised from listHolder: remove rows from start (anArray at:1) 
     to stop (anArray at:2).
    "
    listHolder value size == 0 ifTrue:[
        columnView list:nil
    ] ifFalse:[
        columnView removeFrom:(anArray at:1) to:(anArray at:2)
    ]
!

replace:anArray
    "raised from listHolder: replace collection of rows derived from listHolder
     from start (anArray at:1) to stop (anArray at:2).
    "
    |start stop list|

    start := anArray at:1.
    stop  := anArray at:2.
    list  := listHolder value.

    start to:stop do:[:anIndex|
        columnView at:anIndex put:(list at:anIndex)
    ].

! !

!DataSetView methodsFor:'error handling'!

doesNotUnderstand:aMessage
    "does not understand message; delegate to column view
    "
    ^ aMessage sendTo:columnView
! !

!DataSetView methodsFor:'initialize'!

destroy
    "remove dependencies
    "
    listHolder notNil ifTrue:[
        listHolder removeDependent:self
    ].
    columnView removeDependent:self.

    super destroy



!

initialize
    "set column area
    "
    super initialize.

    scrolledView := HVScrollableView for:DSVColumnView 
                         miniScrollerH:true
                         miniScrollerV:false
                                origin:(0.0 @ 0.0)
                                corner:(1.0 @ 1.0)
                                     in:self.

    useIndex   := true.
    columnView := scrolledView scrolledView.

    columnView borderWidth:0.
    columnView addDependent:self.
    columnView dataSetView:self. "/ kludge
    self showLabels:true.
!

realize
    "realize view; update labels
    "
    |selection|

    selection := 0.

    model notNil ifTrue:[
        (model respondsTo:#selectionIndex) ifTrue:[
            selection := model selectionIndex
        ] ifFalse:[
            model == listHolder ifFalse:[
                selection := model value
            ]
        ]
    ].
    columnView selectRowIndex:selection.
    super realize.
    self  columnsSizeChanged.
! !

!DataSetView methodsFor:'queries'!

specClass
    "returns my spec class
    "
    ^ DataSetSpec
! !

!DataSetView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.25 1999-02-14 15:46:57 cg Exp $'
! !