ComboView.st
author Claus Gittinger <cg@exept.de>
Thu, 11 Sep 1997 04:06:08 +0200
changeset 525 d0731a41d19f
parent 512 97beb6e8acbe
child 581 97189b5cd27c
permissions -rw-r--r--
cache the pull-button image

"
 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.
"



'From Smalltalk/X, Version:3.1.9 on 11-sep-1997 at 5:18:37 pm'                  !

View subclass:#ComboView
	instanceVariableNames:'field pullDownButton list listHolder listMsg action'
	classVariableNames:'DefaultButtonForm'
	poolDictionaries:''
	category:'Views-Interactors'
!

!ComboView 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 ComboView combines some field (typically an enterField or Label)
    with a drop down list of default inputs;
    ComboView is abstract, providing protocol common to ComboBoxView and
    ComboListView. See documentation & examples there.

    [author:]
        Claus Gittinger

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

examples
"
  see examples in ComboListView and ComboBoxView
"
! !

!ComboView class methodsFor:'defaults'!

buttonForm
    "return the pull-buttons image"

    <resource: #style (#comboViewDownForm #comboViewDownFormFile)>

    |fileName form|

    DefaultButtonForm notNil ifTrue:[
        ^ DefaultButtonForm
    ].

    form := StyleSheet at:'comboViewDownForm' default:nil.
    form isNil ifTrue:[
        fileName := StyleSheet at:'comboViewDownFormFile' default:'ComboDn_win.xbm'.
        form := Image fromFile:fileName.
    ].
    form isNil ifTrue:[
        form  := Form width:16 height:16 
                      fromArray:#[2r00000000 2r00000000
                                  2r00000000 2r00000000
                                  2r00000011 2r11000000
                                  2r00000011 2r11000000
                                  2r00000011 2r11000000
                                  2r00000011 2r11000000
                                  2r00000011 2r11000000
                                  2r00011111 2r11111000
                                  2r00001111 2r11110000
                                  2r00000111 2r11100000
                                  2r00000011 2r11000000
                                  2r00000001 2r10000000
                                  2r00000000 2r00000000
                                  2r00011111 2r11111000
                                  2r00000000 2r00000000
                                  2r00000000 2r00000000]
                      on:Display.
    ].
    form notNil ifTrue:[
        form := DefaultButtonForm := form onDevice:Display.
        ^ form
    ].
    ^ nil

    "Modified: 11.9.1997 / 05:17:58 / cg"
!

defaultFont
    "/ for now - should come from the styleSheet

    ^ SelectionInListView defaultFont.

    "Created: 4.6.1997 / 15:44:17 / cg"
!

defaultListMessage
    ^ #list

    "Created: 26.2.1997 / 19:34:50 / cg"
! !

!ComboView methodsFor:'accessing - look'!

font:aFont
    super font:aFont.
    field font:aFont.
! !

!ComboView methodsFor:'accessing-behavior'!

action:aBlock
    "specify, a block, which is evaluated when the lists selection changes.
     This is an additional hook - normally, you would communicate with the model
     alone"

    action := aBlock.

    "Created: 26.7.1996 / 17:44:18 / cg"
    "Modified: 26.2.1997 / 19:37:18 / cg"
!

disable
    "disable components
    "
    (field respondsTo:#disable) ifTrue:[
        field disable
    ].

    (pullDownButton respondsTo:#disable) ifTrue:[
        pullDownButton disable
    ].
!

enable
    "enable components
    "
    (field respondsTo:#enable) ifTrue:[
        field enable
    ].

    (pullDownButton respondsTo:#enable) ifTrue:[
        pullDownButton enable
    ].
!

enabled
    "return true, if is enabled
    "
    (field respondsTo:#enabled) ifTrue:[
        ^ field enabled
    ].

    (pullDownButton respondsTo:#enabled) ifTrue:[
        ^ pullDownButton enabled
    ].
  ^ true
! !

!ComboView methodsFor:'accessing-channels'!

enableChannel 
    "return a valueHolder for enable/disable
    "
    (field respondsTo:#enableChannel) ifTrue:[
        ^ field enableChannel
    ].
    (pullDownButton respondsTo:#enableChannel) ifTrue:[
        ^ pullDownButton enableChannel
    ].
  ^ nil

!

enableChannel:aValueHolder 
    "set a valueHolder for enable/disable for the components
    "
    (field respondsTo:#enableChannel:) ifTrue:[
        field enableChannel:aValueHolder
    ].
    (pullDownButton respondsTo:#enableChannel:) ifTrue:[
        pullDownButton enableChannel:aValueHolder
    ].

! !

!ComboView methodsFor:'accessing-components'!

menuButton
    "return the menuButton component"

    ^ pullDownButton

    "Created: 28.2.1996 / 15:03:14 / cg"
! !

!ComboView methodsFor:'accessing-contents'!

contents
    "get the contents of my field"

    ^ field model value

    "Created: 14.5.1996 / 13:05:16 / cg"
    "Modified: 26.2.1997 / 16:55:43 / cg"
!

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

    |m|

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

    "Created: 14.5.1996 / 13:05:33 / cg"
    "Modified: 26.2.1997 / 16:56:08 / cg"
!

list:aList
    "set the list explicitely; used internally or 
     to be send from the outside if no model/listHolder is used."

    list := aList.

    (list notNil and:[list notEmpty]) ifTrue:[
        pullDownButton enable
    ] ifFalse:[
        pullDownButton disable
    ].

    "Created: 28.2.1996 / 15:03:14 / cg"
    "Modified: 26.2.1997 / 16:55:09 / cg"
! !

!ComboView methodsFor:'accessing-mvc'!

listHolder:aValueHolder
    "set the listHolder.
     If not set, the list is supposed to be set explicitely"

    listHolder notNil ifTrue:[
        listHolder removeDependent:self.
    ].
    listHolder := aValueHolder.
    listHolder notNil ifTrue:[
        aValueHolder addDependent:self.
    ].
    realized ifTrue:[
        self getListFromModel.
    ]

    "Modified: 26.2.1997 / 19:32:09 / cg"
!

listMessage:aSymbol
    "define the message selector sent to the model, to fetch
     the list. If not defined, #list is used"

    listMsg := aSymbol

    "Created: 14.2.1997 / 19:16:52 / cg"
    "Modified: 26.2.1997 / 19:33:09 / cg"
!

model:aModel
    "set the model, which is supposed to provide the boxes value.
     If a listMessage was defined, it is also responsible for providing
     the list"

    super model:aModel.

    self getListFromModel.
    self getValueFromModel.

    "Modified: 28.2.1997 / 19:08:45 / cg"
! !

!ComboView methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    changedObject == model ifTrue:[
        listHolder isNil ifTrue:[
            self getListFromModel.
        ].
        self getValueFromModel.
        ^ self
    ].
    changedObject == listHolder ifTrue:[
        self getListFromModel.
        ^ self
    ].

    super update:something with:aParameter from:changedObject

    "Created: 15.7.1996 / 12:26:49 / cg"
    "Modified: 28.2.1997 / 13:48:51 / cg"
! !

!ComboView methodsFor:'initialization'!

initialize
    |prefExt leftInset rightInset prefWidth halfSpacing l|

    super initialize.

    listMsg := self class defaultListMessage.
    aspectMsg := self class defaultAspectMessage.
    changeMsg := self class defaultChangeMessage.

    self initializeField.
    field origin:0@0 corner:1.0@1.0.

    self initializeButton.
    prefExt := pullDownButton preferredExtent.
    prefWidth := prefExt x.

    pullDownButton origin:1.0@0.0 corner:1.0@1.0.
    styleSheet is3D ifTrue:[
        halfSpacing := ViewSpacing // 2.
        leftInset := rightInset := prefWidth + halfSpacing.
        (l := styleSheet at:'comboViewLevel' default:nil) notNil ifTrue:[
            self level:l.
            field level:0.
            field rightInset:margin.
        ] ifFalse:[
            pullDownButton rightInset:halfSpacing.
            field leftInset:halfSpacing
        ].
    ] ifFalse:[
        leftInset := prefWidth + pullDownButton borderWidth.
        rightInset := prefWidth.
    ].
    pullDownButton leftInset:leftInset negated.
    field rightInset:rightInset.

    self initialHeight:field preferredExtent y + ViewSpacing.

    "
     |b|

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

    "Created: 28.2.1996 / 15:03:17 / cg"
    "Modified: 24.6.1997 / 18:53:10 / cg"
!

initializeButton
    pullDownButton := ComboBoxButton in:self.
    pullDownButton controller beTriggerOnDown.
    pullDownButton label:(self class buttonForm).
    pullDownButton showLamp:false.
    pullDownButton activeLevel == pullDownButton passiveLevel ifTrue:[
        pullDownButton activeLevel:0.
    ].
    pullDownButton disable.
    pullDownButton pressAction:[self pullMenu].

    "Modified: 30.8.1997 / 02:39:45 / cg"
!

initializeField
    self subclassResponsibility

    "Created: 29.3.1997 / 11:17:14 / cg"
! !

!ComboView methodsFor:'message delegation'!

doesNotUnderstand:aMessage
    (field respondsTo:aMessage selector) ifTrue:[
	^ aMessage sendTo:field
    ].
    ^ super doesNotUnderstand:aMessage

    "Created: 28.2.1996 / 15:03:17 / cg"
    "Modified: 28.2.1996 / 15:06:09 / cg"
!

respondsTo:aSymbol
    ^ (field respondsTo:aSymbol) or:[super respondsTo:aSymbol]

    "Created: 2.5.1996 / 16:57:34 / stefan"
! !

!ComboView methodsFor:'private'!

getListFromModel
    "fetch the list - either from the listHolder, or
     from the model. If no listMessage was defined, fetch it
     using #list."

    listHolder notNil ifTrue:[
        self list:listHolder value
    ] ifFalse:[
        (model notNil and:[listMsg notNil]) ifTrue:[
            (model respondsTo:listMsg) ifTrue:[
                self list:(model perform:listMsg)
            ]
        ]
    ].

    "Created: 15.7.1996 / 12:22:56 / cg"
    "Modified: 26.2.1997 / 19:40:58 / cg"
!

getValueFromModel

    "Modified: 15.7.1996 / 12:28:59 / cg"
! !

!ComboView methodsFor:'queries'!

preferredExtent
    "compute & return the boxes preferredExtent from the components' preferrences"

    |fieldPref buttonPref m menuPrefX w h|

    "/ If I have an explicit preferredExtent ..

    preferredExtent notNil ifTrue:[
        ^ preferredExtent
    ].

    list isNil ifTrue:[
        self getListFromModel
    ].

    list isNil ifTrue:[
        menuPrefX := 0
    ] ifFalse:[
        m := MenuView labels:list.
        menuPrefX := m preferredExtent x.
    ].

    fieldPref := field preferredExtent.
    buttonPref := pullDownButton preferredExtent.

    w := ((fieldPref x max:menuPrefX) max:50) + buttonPref x.
    w := w + margin + margin.
    h := fieldPref y max:buttonPref y.
    h := h + margin + margin.
    ^ w @ h

    "Created: 28.2.1996 / 15:03:17 / cg"
    "Modified: 7.3.1997 / 16:42:15 / cg"
! !

!ComboView methodsFor:'user interaction'!

pullMenu
    "pull the menu - triggered from the button"

    |m org|

    self getListFromModel.
    (list notNil and:[list notEmpty]) ifTrue:[
        m := PopUpMenu
                    labels:list
                    selectors:#select:
                    args:(1 to:list size)
                    receiver:self.

        m font:font.
        m menuView font:font.
        m menuView resize.
        m resize.
        m menuView width:(self width).
        m menuView sizeFixed:true.
        m hideOnRelease:false.
        m resize.

        org := device translatePoint:(0 @ self height) 
                                from:(self id)
                                  to:(device rootView id).

        m showAt:org.
    ].

    pullDownButton turnOff.

    "Created: 28.2.1996 / 15:03:18 / cg"
    "Modified: 27.2.1997 / 15:18:00 / cg"
!

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

    self subclassResponsibility

    "Modified: 27.2.1997 / 15:19:07 / cg"
! !

!ComboView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ComboView.st,v 1.33 1997-09-11 02:06:08 cg Exp $'
! !