ComboView.st
author ca
Fri, 17 Mar 2006 16:37:38 +0100
changeset 2950 431dafff127d
parent 2892 42ba7f03313b
child 3231 5dd5dd610d50
permissions -rw-r--r--
cash comboButtonForms

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



"{ Package: 'stx:libwidg2' }"

View subclass:#ComboView
	instanceVariableNames:'field pullDownButton list listHolder listMsg action resizableMenu'
	classVariableNames:'DefaultButtonForm ComboButtonForms'
	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 ExtendedComboBox
        PullDownMenu Label EntryField
"
!

examples
"
  see examples in ComboListView and ComboBoxView
"
! !

!ComboView class methodsFor:'defaults'!

buttonForm
    "return the pull-buttons image"

    <resource: #style (#'comboView.downForm' 
                       #'comboView.downFormFile')>

    |fileName form|

    DefaultButtonForm notNil ifTrue:[
        ^ DefaultButtonForm
    ].

    form := StyleSheet at:#'comboView.downForm'.
    form isNil ifTrue:[
        fileName := StyleSheet at:#'comboView.downFormFile' "default:'ComboDn.14.xbm'".
        fileName notNil ifTrue:[
            form := Smalltalk imageFromFileNamed:fileName forClass:self.
            form isNil ifTrue:[
                form := Smalltalk imageFromFileNamed:fileName inPackage:'stx:libwidg'.
            ]
        ].
    ].
    form isNil ifTrue:[
        form  := Form width:12 height:12 
                      fromArray:#[2r00000000 2r00000000
                                  "/ 2r00001111 2r00000000
                                  "/ 2r00001111 2r00000000
                                  2r00001111 2r00000000
                                  2r00001111 2r00000000
                                  2r00001111 2r00000000
                                  2r01111111 2r11100000
                                  2r00111111 2r11000000
                                  2r00011111 2r10000000
                                  2r00001111 2r00000000
                                  2r00000110 2r00000000
                                  2r00000000 2r00000000
                                  2r01111111 2r11100000
                                  2r00000000 2r00000000]
                      on:Display.
    ].
    form notNil ifTrue:[
        form := DefaultButtonForm := form onDevice:Display.
        ^ form
    ].
    ^ nil

    "Modified: / 28.4.1999 / 12:49:42 / cg"
!

comboButtonFor:anInstance
    <resource: #style (#'comboView.disabledDownForm' 
                       #'comboView.disabledDownFormFile'
                       #'comboView.activeDownFormFile'
                       #'comboView.button.activeForegroundColor'
                       #'comboView.button.activeBackgroundColor'
                       #'comboView.button.activeLevel'
                       #'comboView.button.passiveLevel'  )>

    |pullDownButton fn logo disabledLogo activeLogo enteredLogo lvl clr|

    pullDownButton := ComboBoxButton in:anInstance.
    pullDownButton controller beTriggerOnDown.
    pullDownButton label:(logo := self buttonForm).

    ComboButtonForms isNil ifTrue:[
        ComboButtonForms := IdentityDictionary new.
    ].

    disabledLogo := ComboButtonForms at:disabledLogo ifAbsentPut:[|logo|
        logo := StyleSheet at:#'comboView.disabledDownForm'.

        logo isNil ifTrue:[
            fn := StyleSheet at:#'comboView.disabledDownFormFile'.
            fn notNil ifTrue:[
                logo := Smalltalk imageFromFileNamed:fn forClass:self.
                logo isNil ifTrue:[
                    logo := Smalltalk imageFromFileNamed:fn inPackage:'stx:libwidg'.
                ]
            ]
        ].
        logo
    ].    

    activeLogo := ComboButtonForms at:#activeLogo ifAbsentPut:[|logo|
        logo := StyleSheet at:#'comboView.activeDownForm'.

        logo isNil ifTrue:[
            fn := StyleSheet at:#'comboView.activeDownFormFile'.
            fn notNil ifTrue:[
                logo := Smalltalk imageFromFileNamed:fn forClass:self.
                logo isNil ifTrue:[
                    logo := Smalltalk imageFromFileNamed:fn inPackage:'stx:libwidg'.
                ]
            ]
        ].
        logo
    ].    

    enteredLogo := ComboButtonForms at:#enteredLogo ifAbsentPut:[|logo|
        logo := StyleSheet at:#'comboView.enteredDownForm'.

        logo isNil ifTrue:[
            fn := StyleSheet at:#'comboView.enteredDownFormFile'.
            fn notNil ifTrue:[
                logo := Smalltalk imageFromFileNamed:fn forClass:self.
                logo isNil ifTrue:[
                    logo := Smalltalk imageFromFileNamed:fn inPackage:'stx:libwidg'.
                ]
            ]
        ].    
        logo
    ].

    disabledLogo notNil ifTrue:[
        pullDownButton passiveLogo:logo.
        pullDownButton activeLogo:logo.
        pullDownButton disabledLogo:disabledLogo.
    ].

    pullDownButton showLamp:false.

    activeLogo notNil ifTrue:[
        pullDownButton activeLogo:activeLogo.
        pullDownButton passiveLogo:logo.
        pullDownButton label:logo.
    ].

    enteredLogo notNil ifTrue:[
        pullDownButton enteredLogo:enteredLogo.
    ].

    (lvl := StyleSheet at:#'comboView.button.activeLevel') notNil ifTrue:[
        pullDownButton activeLevel:lvl
    ].
    (lvl := StyleSheet at:#'comboView.button.passiveLevel') notNil ifTrue:[
        pullDownButton passiveLevel:lvl
    ].

    (clr := StyleSheet colorAt:#'comboView.button.activeForegroundColor') notNil ifTrue:[
        pullDownButton activeForegroundColor:clr
    ].
    (clr := StyleSheet colorAt:#'comboView.button.activeBackgroundColor') notNil ifTrue:[
        pullDownButton activeBackgroundColor:clr
    ].

    pullDownButton activeLevel == pullDownButton passiveLevel ifTrue:[
        pullDownButton activeLevel:0.
    ].
    ^ pullDownButton.
!

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

updateStyleCache
    DefaultButtonForm := ComboButtonForms := nil.

    "Created: / 3.11.1997 / 15:28:48 / cg"
! !

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

enabled
    "return true, if is enabled"
    
    enableChannel isNil ifTrue:[^ true].
    ^ enableChannel value
!

enabled:aBoolean
    "enable/disable components"

    self enableChannel value:aBoolean.

    "Modified: / 30.3.1999 / 14:56:18 / stefan"
!

resizableMenu
    "return true, if the menu is to be resizable.
     This feature is as yet unimplemented."
    
    ^ resizableMenu ? false
!

resizableMenu:aBoolean
    "enable/disable, if the menu is to be resizable.
     This feature is as yet unimplemented."
    
    resizableMenu := aBoolean
! !

!ComboView methodsFor:'accessing-channels'!

enableChannel 
    "return a valueHolder for enable/disable"

    enableChannel isNil ifTrue:[
        self enableChannel:(true asValue).
    ].
    ^ enableChannel

    "Modified: / 30.3.1999 / 16:20:25 / stefan"
! !

!ComboView methodsFor:'accessing-components'!

field
    "return the field (input or label) component.
     For knowledgable users only."

    ^ field

    "Created: / 26.9.1999 / 13:33:15 / cg"
!

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
    "return the list"

    ^ list

    "Created: / 18.5.1998 / 18:58: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 isNil or:[list isSequenceable]) ifFalse:[
        self error:'Need an ordered collection' mayProceed:true.
    ].
    self enableStateChanged.

    "Modified: / 30.3.1999 / 14:17:38 / stefan"
! !

!ComboView methodsFor:'accessing-look'!

backgroundColor

    ^field backgroundColor
!

backgroundColor:aColor

    field backgroundColor:aColor
!

font:aFont

    super font:aFont.
    self setFieldsFont:aFont.
!

foregroundColor

    ^field foregroundColor
!

foregroundColor:aColor

    field foregroundColor:aColor
! !

!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"
    "Modified: / 30.3.1999 / 14:17:55 / stefan"
! !

!ComboView methodsFor:'event handling'!

enableStateChanged
    "the enable state has changed - pass this to my field and pullDownButton"

    |msg|

    (enableChannel isNil or:[enableChannel value]) ifTrue:[
        msg := #enable
    ] ifFalse:[
        msg := #disable
    ].
    field perform:msg ifNotUnderstood:nil.

    (list size == 0) ifTrue:[
        msg := #disable
    ].
    pullDownButton perform:msg ifNotUnderstood:nil.

    "Modified: / 22.2.1999 / 00:47:46 / cg"
    "Modified: / 30.3.1999 / 14:17:10 / stefan"
!

keyPress:key x:x y:y
    "pull the menu on space and return keys"

    <resource: #keyboard (#Return)>

    (key == Character space or:[key == #Return]) ifTrue:[
        self pullMenu.
        ^ self.
    ].

    ^ super keyPress:key x:x y:y

    "Modified: / 21.4.1998 / 20:10:05 / cg"
! !

!ComboView methodsFor:'initialization & release'!

initialize
    |prefExt leftInset rightInset prefWidth halfSpacing nm lvl|

    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 shadowColor:(field shadowColor).

    self initializeButton.
    pullDownButton pressAction:[self pullMenu].
    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.
        (lvl := styleSheet at:#'comboView.level' default:nil) notNil ifTrue:[
            self level:lvl.
            field level:0.
            field rightInset:margin.
        ] ifFalse:[
            pullDownButton rightInset:halfSpacing.
            field leftInset:halfSpacing
        ].
    ] ifFalse:[
        leftInset := prefWidth + pullDownButton borderWidth.
        rightInset := prefWidth.
    ].

    nm := styleSheet name.
    (nm = #win95 or:[nm = #win98 or:[nm = #winXP or:[nm = #st80]]]) ifTrue:[
        field level:0.
        lvl isNil ifTrue:[self level:-1].
        pullDownButton rightInset:0.
        nm ~= #st80 ifTrue:[
            leftInset := (ArrowButton new preferredExtent x).
            rightInset := leftInset.
        ].
        field origin:0.0@0.0.
        field leftInset:0.
"/        field topInset:1; bottomInset:1.
"/        nm = #winXP ifTrue:[
"/            self borderWidth:1.
"/            self borderColor:(Color blue lightened).
"/        ].
    ].
    field rightInset:rightInset.
    pullDownButton leftInset:leftInset negated.

    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: / 8.9.1998 / 20:33:22 / cg"
!

initializeButton
    pullDownButton := self class comboButtonFor:self.
    pullDownButton disable.
!

initializeField
    self subclassResponsibility

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

release
    listHolder notNil ifTrue:[
        listHolder removeDependent:self.
        listHolder := nil.
    ].
    super release
! !

!ComboView methodsFor:'menu interaction'!

createPullDownMenuForList:aList
    "pull the menu - triggered from the button"

    |menu index|

    menu := MenuPanel labels:aList.

    index := 1.

    menu do:[:el |
        el value:#select: argument:index.
        index := index + 1.
    ].
    menu receiver:self.
    menu font:font.
    menu preferredWidth:(self width).

    ^ menu
!

pullMenu
    "pull the menu - triggered from the button"

    |menu origin|

    self getListFromModel.

    list notEmptyOrNil ifTrue:[
        menu := self createPullDownMenuForList:list.
        origin := device translatePoint:(0 @ self height) fromView:self toView:nil.
        menu showAt:origin.
    ].

    pullDownButton turnOff.

    "Created: / 10.10.2001 / 14:47:25 / cg"
    "Modified: / 10.10.2001 / 15:04:44 / cg"
!

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

    self subclassResponsibility

    "Modified: 27.2.1997 / 15:19:07 / 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"
!

flash
    field flash
!

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

setFieldsFont:aFont
    field font:aFont.
! !

!ComboView methodsFor:'queries'!

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

    |fieldPref buttonPref m menuPrefX menuPrefY w h|

    "/ If I have an explicit preferredExtent ..

    preferredExtent notNil ifTrue:[
        ^ preferredExtent
    ].

    list isNil ifTrue:[
        self getListFromModel
    ].

    list isNil ifTrue:[
        menuPrefX := menuPrefY := 0
    ] ifFalse:[
        m := (MenuView onDevice:device ? Screen current) labels:list.
        menuPrefX := m preferredExtent x.

        "/ the menuView returns rubbish ...
"/        menuPrefY := (m preferredExtentForLines:1 cols:10) y
        
        "/ any non-strings ?
        menuPrefY := list 
            inject:('X' heightOn:self) 
            into:[:max :el | el isString ifTrue:[
                                max
                              ] ifFalse:[
                                max max:(el heightOn:self) 
                              ]
                 ].
    ].

    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) max:menuPrefY.
    h := h + margin + margin.
    ^ w @ h

    "Created: / 28.2.1996 / 15:03:17 / cg"
    "Modified: / 29.4.1999 / 11:27:54 / cg"
! !

!ComboView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ComboView.st,v 1.80 2006-03-17 15:37:38 ca Exp $'
! !