ComboListView.st
author Claus Gittinger <cg@exept.de>
Sat, 29 Mar 1997 11:56:37 +0100
changeset 332 78dcd3cacbfd
parent 310 15ef4f52f8cf
child 368 c99ef22c72f8
permissions -rw-r--r--
documentation

"
 COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
              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.
"



ComboView subclass:#ComboListView
	instanceVariableNames:'useIndex values'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Interactors'
!

!ComboListView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
              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
"
    A ComboListView combines an label with a drop down list of default inputs;
    choosing any from the pulled list sets the string in the label.

    This is the same as a PopUpList or SelectionInListView, bit looks different.

    The preferred model is a SelectionInList, but a simple valueHolder
    may also be used. 
    If some other model is to be used, the changeMessage and aspectMessage 
    should be defined as appropriate (or an aspectAdaptor should be used).
    If a listHolder is set, that one is assumed to provide the list of
    items in the popped menu; 
    otherwise, if listMessage is nonNil, the model is assumed to also provide the
    list as displayed in the popped menu.

    [author:]
        Claus Gittinger

    [see also:]
        ComboView
        PopUpList SelectionInListView
        ComboBoxView
        PullDownMenu Label EntryField
"
!

examples
"
  non-MVC use; 
    set the list explicitely:
                                                        [exBegin]
     |top comboBox|

     top := StandardSystemView new.
     top extent:(300 @ 200).

     comboBox := ComboListView in:top.
     comboBox origin:(0.0 @ 0.0) corner:(1.0 @ 0.0).
     comboBox bottomInset:(comboBox preferredExtent y negated).

     comboBox list:#('hello' 'world' 'this' 'is' 'st/x').
     top open.
                                                                [exEnd]



    with callBack:
                                                                [exBegin]
     |top b|

     top := StandardSystemView new.
     top extent:(300 @ 200).

     b := ComboListView in:top.
     b origin:(0.0 @ 0.0) corner:(1.0 @ 0.0).
     b bottomInset:(b preferredExtent y negated).

     b list:#('hello' 'world' 'this' 'is' 'st/x').
     b action:[:selected | Transcript showCR:selected].
     top open.
                                                                [exEnd]



    with values different from the label strings:
                                                                        [exBegin]
     |p|
     p := ComboListView label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
     p selection:'apples'.
     p values:#(10 20 30 40 nil 50).
     p action:[:what | Transcript show:'you selected: '; showCR:what].
     p open
                                                                        [exEnd]


    with separating lines:
                                                                [exBegin]
     |p|
     p := ComboListView label:'fruit'.
     p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
     p selection:'apples'.
     p open
                                                                [exEnd]




    sometimes, you may like the index instead of the value:
    (notice, that the separating line counts, so you have to take care ...)
                                                                [exBegin]
     |p|
     p := ComboListView label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
     p selection:'apples'.
     p action:[:what | Transcript show:'you selected: '; showCR:what].
     p useIndex:true.
     p open
                                                                [exEnd]



    since the list is actually represented by a menuView,
    which itself is inheriting from listView, which itself can display
    things different from strings, arbitrary lists can be constructed:
    (see ListEntry, LabelAndIcon and Text classes)
                                                                        [exBegin]
     |p l|
     p := ComboListView label:'dummy'.

     l := OrderedCollection new.
     l add:(Text string:'apples' color:Color red).
     l add:(Text string:'bananas' color:Color red).
     l add:(Text string:'grape' color:Color red).
     l add:(Text string:'lemon' color:Color red).
     l add:'='.
     l add:(Text string:'margaritas' color:Color green darkened darkened).
     l add:(Text string:'pina colada' color:Color green darkened darkened).
     l add:'='.
     l add:(Text string:'smalltalk' color:Color blue).
     l add:(Text string:'c++' color:Color blue).
     l add:(Text string:'eiffel' color:Color blue).
     l add:(Text string:'java' color:Color blue).
     p list:l.
     p values:#(apples bananas grape lemon 
                nil 
                'mhmh - so good' 'makes headache'
                nil
                'great' 'another headache' 'not bad' 'neat').
     p selection:'apples'.
     p action:[:what | Transcript show:'you selected: '; showCR:what].
     p open
                                                                        [exEnd]

    with values different from the label strings:
                                                                        [exBegin]
     |p|

     p := PopUpList label:'language selection'.
     p list:( #(
                'usa'
                'uk'
                'france'
                'germany'       
                'italy'
               ) collect:[:country |
                            LabelAndIcon 
                                icon:(Image fromFile:'bitmaps/xpmBitmaps/countries/' , country , '.xpm')
                                string:country
                         ]
            ).
     p values:#(us england france germany italy).

     p action:[:what | Transcript show:'you selected: '; showCR:what].
     p open
                                                                        [exEnd]


  with a model (see in the inspector, how the index-holders value changes)
  the defaults are setup to allow a SelectionInList directly as model:
                                                                        [exBegin]
     |p model|

     model := SelectionInList with:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').

     p := ComboListView label:'healthy fruit'.
     p model:model.
     p open.
     model inspect
                                                                        [exEnd]

  model provides selection; list is explicit:
                                                                [exBegin]
     |model top b|

     model := 'foo' asValue.

     top := StandardSystemView new.
     top extent:(300 @ 200).

     b := ComboListView in:top.
     b origin:(0.0 @ 0.0) corner:(1.0 @ 0.0).
     b bottomInset:(b preferredExtent y negated).

     b list:#('hello' 'world' 'this' 'is' 'st/x').
     b model:model.

     top openModal.
     Transcript showCR:('comboBox''s value: ' , model value).
                                                                [exEnd]


    a comboListView and a SelectionInListView on the same model:
                                                                        [exBegin]
     |p slv model|

     model := SelectionInList with:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
     model selection:'apples'.

     p := ComboListView on:model.
     p open.

     slv := SelectionInListView on:model.
     slv open.
                                                                        [exEnd]


    two comboListViews on the same model, different aspects:
                                                                        [exBegin]
     |top panel p model|

     model := Plug new.
     model respondTo:#eat: with:[:val | Transcript showCR:'eat: ' , val].
     model respondTo:#drink: with:[:val | Transcript showCR:'drink: ' , val].
     model respondTo:#meals with:[#(taco burrito enchilada)].
     model respondTo:#drinks with:[#(margarita water corona)].

     top := StandardSystemView new.
     top extent:(150@150).
     panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
     panel horizontalLayout:#fitSpace.

     p := ComboListView label:'meals'.
     p model:model; listMessage:#meals; aspect:nil; change:#eat:.
     panel add:p.

     p := ComboListView label:'drinks'.
     p model:model; listMessage:#drinks; aspect:nil; change:#drink:.
     panel add:p.

     top open
                                                                        [exEnd]




    with separate list- and indexHolders:
                                                                        [exBegin]
     |p selectionHolder listHolder|

     listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
     selectionHolder := 'apples' asValue.

     p := ComboListView label:'healthy fruit'.
     p listHolder:listHolder.
     p model:selectionHolder.
     p open.
     selectionHolder inspect
                                                                        [exEnd]

    using different values:
                                                                        [exBegin]
     |p selectionHolder listHolder values|

     listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
     values := #(apples bananas grape lemon alcohol).

     selectionHolder := #alcohol asValue.

     p := ComboListView label:'healthy fruit'.
     p listHolder:listHolder.
     p model:selectionHolder.
     p values:values.
     p open.
     selectionHolder inspect
                                                                        [exEnd]


  in a dialog:
                                                                [exBegin]
     |model1 model2 dialog b|

     model1 := 'foo' asValue.
     model2 := 'bar' asValue.

     dialog := Dialog new.
     (dialog addTextLabel:'ComboList example:') adjust:#left.
     dialog addVerticalSpace.

     (b := dialog addComboListOn:model1 tabable:true).
     b list:#('fee' 'foe' 'foo').
     dialog addVerticalSpace.

     (b := dialog addComboListOn:model2 tabable:true).
     b list:#('bar' 'baz' 'baloo').
     dialog addVerticalSpace.

     dialog addOkButton.

     dialog open.

     Transcript showCR:('1st comboBox''s value: ' , model1 value).
     Transcript showCR:('2nd comboBox''s value: ' , model2 value).
                                                                [exEnd]
"
! !

!ComboListView class methodsFor:'defaults'!

defaultAspectMessage
    ^ #selection

    "Created: 27.2.1997 / 15:23:13 / cg"
!

defaultChangeMessage
    ^ #selection:

    "Created: 27.2.1997 / 15:23:18 / cg"
! !

!ComboListView methodsFor:'accessing-behavior'!

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

    useIndex := aBoolean.

    "Created: 26.7.1996 / 17:44:18 / cg"
!

values:aCollection
    "specify, which values are to be stuffed into the model or
     passed via the actionBlock."

    values := aCollection.

    "Created: 27.2.1997 / 15:10:12 / cg"
! !

!ComboListView methodsFor:'accessing-components'!

label 
    "return the label component"

    ^ field

    "Modified: 28.2.1996 / 15:10:50 / cg"
    "Created: 28.2.1996 / 15:13:51 / cg"
! !

!ComboListView methodsFor:'accessing-contents'!

contents:something
    "set the current value - either in the fields model
     or directly"

    |m|

    (m := field model) notNil ifTrue:[
        m value:something
    ] ifFalse:[
        field label:something
    ]

    "Created: 15.7.1996 / 13:16:49 / cg"
    "Modified: 5.1.1997 / 00:05:04 / cg"
!

selection:something
    "set the contents of my field; questionable"

    self contents:something

    "Created: 27.2.1997 / 15:07:37 / cg"
! !

!ComboListView methodsFor:'initialization'!

initialize
    useIndex isNil ifTrue:[useIndex := false].

    super initialize.

    "Created: 26.7.1996 / 17:44:57 / cg"
    "Modified: 27.2.1997 / 15:23:24 / cg"
!

initializeField
    field := Label in:self.
    field level:-1.
    field adjust:#left.

    "
     |b|

     b := ComboListView new.
     b list:#('hello' 'world' 'this' 'is' 'st/x').
     b open
    "

    "Created: 28.2.1996 / 15:13:46 / cg"
    "Modified: 28.2.1996 / 15:18:40 / cg"
! !

!ComboListView methodsFor:'private'!

getValueFromModel
    |selection idx aspect|

    (model notNil and:[aspectMsg notNil]) ifTrue:[
        "/ kludge - try #value if aspect is the default and
        "/ not understood by the model
        "/ this allows a valueHolder to be used, even
        "/ if the aspectMessage was not setup correctly.

        aspect := aspectMsg.
        aspect == self class defaultAspectMessage ifTrue:[
            (model respondsTo:aspect) ifFalse:[
                aspect := #value
            ]
        ].

        selection := model perform:aspect.
        selection notNil ifTrue:[
            values notNil ifTrue:[
                idx := values indexOf:selection
            ] ifFalse:[
                useIndex ifTrue:[
                    idx := selection
                ] ifFalse:[
                    self contents:selection.
                    ^ self.
                ]
            ].

            self contents:(list at:idx)
        ]
    ].

    "Created: 15.7.1996 / 12:28:53 / cg"
    "Modified: 28.2.1997 / 13:41:02 / cg"
! !

!ComboListView methodsFor:'queries'!

specClass
    self class == ComboListView ifTrue:[
        ^ ComboListSpec
    ].
    ^ super specClass


! !

!ComboListView methodsFor:'user interaction'!

select:anIndex
    "sent from the popped menu, when an item was selected"

    |what label value chg|

    values isNil ifTrue:[
        value := anIndex.
        useIndex ifFalse:[
            value := list at:anIndex.
        ]
    ] ifFalse:[
        value := values at:anIndex
    ].

    label := list at:anIndex.

    field label:label.

    "
     ST-80 style model notification ...
     this updates the model (typically, a ValueHolder)
    "
    (model notNil and:[changeMsg notNil]) ifTrue:[
        "/ kludge - try #value: if changeMsg is the default and
        "/ not understood by the model
        "/ this allows a valueHolder to be used, even
        "/ if the aspectMessage was not setup correctly.

        chg := changeMsg.
        chg == self class defaultChangeMessage ifTrue:[
            (model respondsTo:chg) ifFalse:[
                chg := #value:
            ]
        ].

        self sendChangeMessage:chg with:value
    ].
    pullDownButton turnOff.

    "
     ST/X style actionBlock evaluation ...
    "
    action notNil ifTrue:[
        action value:value
    ].

    "Created: 27.2.1997 / 15:18:44 / cg"
    "Modified: 28.2.1997 / 13:50:17 / cg"
! !

!ComboListView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ComboListView.st,v 1.20 1997-03-29 10:56:37 cg Exp $'
! !