DataSetView.st
author ca
Fri, 14 Nov 1997 10:25:05 +0100
changeset 619 4a919c3f5f04
parent 611 7fb299f3f542
child 637 e56ec99923ae
permissions -rw-r--r--
add examples

"
 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:'columnView labelView listHolder useIndex'
	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 methodsFor:'accessing'!

useIndex
    ^ useIndex
!

useIndex:aBool
    useIndex := aBool
! !

!DataSetView methodsFor:'accessing menus'!

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

!

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

!

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

! !

!DataSetView methodsFor:'accessing visibility'!

font:aFont
    columnView font:aFont
!

horizontalMini:aBool
    ^ columnView superView horizontalMini:aBool
!

horizontalScrollable:aBool
    ^ columnView superView horizontalScrollable:aBool
!

isHorizontalScrollable
    ^ columnView superView isHorizontalScrollable
!

isVerticalScrollable
    ^ columnView superView isVerticalScrollable
!

verticalMini:aBool
    columnView superView verticalMini:aBool.
!

verticalScrollable:aBool
    columnView superView verticalScrollable:aBool.

!

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


!

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


! !

!DataSetView methodsFor:'adding & removing rows'!

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

!DataSetView methodsFor:'change & update'!

listHolder:aListHolder
    "set listholder and update list.
    "
    |list|

    listHolder ~~ aListHolder ifTrue:[
        listHolder notNil ifTrue:[
            listHolder removeDependent:self
        ].

        (listHolder := aListHolder) notNil ifTrue:[
            listHolder addDependent:self
        ]
    ].

    (list := listHolder value) notNil ifTrue:[
        columnView list:(list collect:[:el| el ])
    ] ifFalse:[
        columnView list:nil.
    ].
!

model:aModel
    "update model and list holder (derived from model).
    "
    (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
        ]
    ]
!

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

    chgObj == columnView ifFalse:[
        chgObj == model ifTrue:[
            (what == #selectionIndex or:[what == #selection]) ifTrue:[
                ^ columnView selectRowIndex:(model selectionIndex)
            ].
            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]]) ifTrue:[
                    ^ self listHolder:listHolder        "/ reread list from model
                ].
                self perform:what with:aPara
            ]
        ].
        ^ self
    ].

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

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

!DataSetView methodsFor:'change & update model'!

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 first.
    size  := anArray last.

    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).
    "
    |start stop|

    start := anArray first.
    stop  := anArray last.

    listHolder value size == 0 ifTrue:[
        columnView list:nil
    ] ifFalse:[
        (stop - start + 1) timesRepeat:[
            columnView removeIndex:start
        ]
    ]
!

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 first.
    stop  := anArray last.
    list  := listHolder value.

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

! !

!DataSetView methodsFor:'error handling'!

doesNotUnderstand:aMessage
    ^ aMessage sendTo:columnView
! !

!DataSetView methodsFor:'initialize'!

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



!

initialize
    "set column area
    "
    super initialize.

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

    labelView := DSVLabelView origin:(0.0 @ 0.0)
                              corner:(1.0 @ 0.0)
                                  in:self.
    useIndex := true.
    columnView := columnView scrolledView.
    labelView columnView:columnView.
    columnView borderWidth:0.
    columnView addDependent:self.
!

realize
    super realize.
    self bitGravity:#NorthWest.

! !

!DataSetView methodsFor:'queries'!

specClass
    ^ DataSetSpec
! !

!DataSetView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/DataSetView.st,v 1.6 1997-11-14 09:25:05 ca Exp $'
! !