ExtendedComboBox.st
author Claus Gittinger <cg@exept.de>
Fri, 05 Mar 1999 16:54:58 +0100
changeset 1225 02f9b5ed9aac
parent 1224 f499a42e072d
child 1272 c3eb38fa149d
permissions -rw-r--r--
*** empty log message ***

View subclass:#ExtendedComboBox
	instanceVariableNames:'menuButton menuField menuWrapper adjust menuWidgetHolder
		menuWidget menuHeight isReadOnly usePreferredWidthForMenu'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Interactors'
!

SimpleView subclass:#MenuWrapper
	instanceVariableNames:'shadowView comboBox widget pointerScrollbarView'
	classVariableNames:''
	poolDictionaries:''
	privateIn:ExtendedComboBox
!

!ExtendedComboBox class methodsFor:'documentation'!

examples
"
    example 1: SelectionInListView
                                                                                [exBegin]
    |top menu widget list sidx|

    top  := StandardSystemView extent:200@35.
    menu := ExtendedComboBox origin:5 @ 5 corner:1.0 @ 0.0 in:top.
    list := #('foo' 'bar' 'baz' 'hjh' 'kk' 'claus' 'gjhj').
    sidx := 4.
    menu bottomInset:(menu preferredExtent y negated).
    menu contents:(list at:sidx).

    widget := SelectionInListView new.
    widget list:list.
    widget doubleClickAction:[:i| menu contents:(widget at:i) ].
    widget selection:sidx.
    menu menuWidget:widget.
    top open.
                                                                                [exEnd]



    example 2: FileSelectionTree
                                                                                [exBegin]
    |top menu widget|

    top  := StandardSystemView extent:200@35.
    menu := ExtendedComboBox origin:5 @ 5 corner:1.0 @ 0.0 in:top.
    menu bottomInset:(menu preferredExtent y negated).

    widget := FileSelectionTree new.
    widget directory:(Filename homeDirectory).

    widget doubleClickAction:[:i||n|
        n := widget selectedNode.
        n isDirectory ifFalse:[menu contents:(n pathName)]
    ].
    menu menuHeight:400.
    menu menuWidget:widget.
    top  open.
                                                                                [exEnd]



    example 3: SelectionInListView
                                                                                [exBegin]
    |top menu widget|

    top  := StandardSystemView extent:200@35.
    menu := ExtendedComboBox origin:5 @ 5 corner:1.0 @ 0.0 in:top.
    menu bottomInset:(menu preferredExtent y negated).
    menu contents:'foo'.

    widget := SelectionInTreeView new.
    widget root:(TreeItem newAsTreeFromSmalltalkClass:Object).

    widget doubleClickAction:[:i||n|
        n := widget selectedNode.
        n hasChildren ifFalse:[menu contents:(n name)]
    ].
    menu menuHeight:300.
    menu menuWidget:widget.
    top  open.
                                                                                [exEnd]


"
! !

!ExtendedComboBox class methodsFor:'testing'!

test
"
self test
"
    |top menu|

    top  := StandardSystemView extent:200@35.
    menu := ExtendedComboBox origin:5 @ 5 corner:0.8 @ 0.0 in:top.
    menu bottomInset:(menu preferredExtent y negated).
    menu list:#('foo' 'bar' 'baz' 'hjh' 'kk' 'claus' 'gjhj').
    top  open.
    menu inspect.
!

test1
"
self test1
"
    |top menu|

    top  := StandardSystemView extent:200@35.
    menu := ExtendedComboBox origin:5 @ 5 corner:1.0 @ 0.0 in:top.
    menu bottomInset:(menu preferredExtent y negated).
    menu directory:'.'.
    top  open.

! !

!ExtendedComboBox methodsFor:'accessing'!

contents
    "return the value of the field
    "
    ^ model value
!

contents:aValue
    "set the value of the field
    "
    model value:aValue.
!

menuWidget
    "get the menu widget or nil
    "
    ^ menuWidget


!

menuWidget:aWidgetOrNil
    "set the menu widget or nil
    "
    menuWidget ~~ aWidgetOrNil ifTrue:[
        menuWrapper notNil ifTrue:[
            self closeMenu.
            menuWrapper destroy.
            menuWrapper := nil.
        ].
        menuWidget := aWidgetOrNil.
    ].
! !

!ExtendedComboBox methodsFor:'accessing default widgets'!

directory:aDirectory
    "creates a FileSelectionTree - menu,
     setting the root to the directory
    "
    menuWidget isNil ifTrue:[
        menuWidget := FileSelectionTree new.

        menuWidget doubleClickAction:[:aDummy||node|
            node := menuWidget selectedNode.

            node isDirectory ifFalse:[
                self contents:(node pathName)
            ]
        ]
    ].
    self menuHeight:400.
    menuWidget directory:aDirectory.
!

list:aList
    "creates a SelectionInListView - menu
     setting the list
    "
    menuWidget isNil ifTrue:[
        menuWidget := SelectionInListView new.

        menuWidget doubleClickAction:[:anIndex| 
            self contents:(menuWidget at:anIndex)
        ]
    ].
    menuWidget list:aList
! !

!ExtendedComboBox methodsFor:'accessing-behavior'!

disable
    "disable components
    "
    self closeMenu.

    (menuField respondsTo:#disable) ifTrue:[
        menuField disable
    ].
    menuButton disable

!

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


!

enabled
    "returns true, if is enabled
    "
    ^ menuButton enabled


! !

!ExtendedComboBox methodsFor:'accessing-channels'!

enableChannel 
    "return a valueHolder for enable/disable
    "
    ^ menuButton enableChannel


!

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


!

menuWidgetHolder
    "returns the menu widget or nil
    "
    ^ menuWidgetHolder
!

menuWidgetHolder:aHolder
    "returns the menu widget or nil
    "
    menuWidgetHolder notNil ifTrue:[
        menuWidgetHolder removeDependent:self
    ].
    menuWidgetHolder notNil ifTrue:[
        menuWidgetHolder addDependent:self
    ].
    self menuWidget:(menuWidgetHolder value).
!

model:aModel
    "set the model
    "
    super model:(aModel ? ValueHolder new).
    menuField notNil ifTrue:[ menuField model:model ].
! !

!ExtendedComboBox methodsFor:'accessing-dimension'!

menuHeight
    "get the maximum height of the menu widget or nil
    "
    ^ menuHeight
!

menuHeight:aHeight
    "set the maximum height of the menu widget or nil
    "
    menuHeight := aHeight.
!

preferredExtent
    "compute & return the preferredExtent from the components' preferrences
    "
    |fieldPref buttonPref m w h f|

    "/ If I have an explicit preferredExtent ..

    preferredExtent notNil ifTrue:[
        ^ preferredExtent
    ].
    fieldPref  := menuField preferredExtent.
    buttonPref := menuButton preferredExtent.
    f := 2 + font maxHeight + (font maxDescent * 2) + (menuField margin * 2).
    h := (fieldPref y max:f) max:buttonPref y.
    m := margin max:1.
    h := h + m + m.

    w := (fieldPref x max:100) + buttonPref x.

    menuWidget notNil ifTrue:[
        f := menuWidget widthOfContents + buttonPref x + 20.
        w := f max:w
    ].
    w := w + margin + margin.

    ^ w @ h

!

usePreferredWidthForMenu
    "returns true if th menu is opened with its menu preferred width
    "
    ^ usePreferredWidthForMenu

!

usePreferredWidthForMenu:aBoolean
    "open the menu with its menu preferred width
    "
    usePreferredWidthForMenu := aBoolean
! !

!ExtendedComboBox methodsFor:'accessing-look'!

adjust
    "returns the button adjust symbol, which is one of
         #left  -> left adjust  button
         #right -> right adjust button
    "
    ^ adjust

!

adjust:how
    "set the button adjust, which must be one of
         #left  -> left adjust  button
         #right -> right adjust button
    "
    |rightInset|

    (adjust ~~ how and:[(how == #left or:[how == #right])]) ifTrue:[
        (adjust := how) == #left ifTrue:[
            menuButton origin:0.0@0.0 corner:0.0@1.0
        ] ifFalse:[
            menuButton origin:1.0@0.0 corner:1.0@1.0
        ].

        rightInset := menuButton leftInset.
        menuButton leftInset:(menuButton rightInset).
        menuButton rightInset:rightInset.

        rightInset := menuField leftInset.
        menuField  leftInset:(menuField rightInset).
        menuField rightInset:rightInset.
    ].
!

backgroundColor
    "get the background color of the menu field
    "
    ^ menuField backgroundColor


!

backgroundColor:aColor
    "set the background color of the menu field
    "
    menuField backgroundColor:aColor

!

font:aFont
    "set the font of the menu field
    "
    super font:aFont.
    menuField font:aFont.



!

foregroundColor
    "set the foreground color of the menu field
    "
    ^ menuField foregroundColor

!

foregroundColor:aColor
    "set the foreground color of the menu field
    "
    menuField foregroundColor:aColor

!

readOnly
    "returns true if the menuField is readonly, a label
    "
    ^ isReadOnly
!

readOnly:aState
    "set the menuField to readonly or writable
    "
    |newField|

    isReadOnly == aState ifTrue:[ ^ self ].
    isReadOnly := aState.

    aState ifTrue:[
        newField := Label in:self.
        newField level:-1.
        newField adjust:#left.
        newField labelMessage:#value.
    ] ifFalse:[
        newField := EditField in:self
    ].

    newField origin:0.0 @ 0.0 corner:1.0 @ 1.0.

    menuField notNil ifTrue:[
        newField      level:(menuField level).
        newField  leftInset:(menuField leftInset).
        newField rightInset:(menuField rightInset).

        menuField destroy.
    ] ifFalse:[
        styleSheet is3D ifTrue:[
            (styleSheet at:'comboViewLevel' default:nil) notNil ifTrue:[
                newField level:0.
            ] ifFalse:[
                newField leftInset:(ViewSpacing // 2).
            ]
        ].
        (styleSheet name = #win95 or:[styleSheet name = #st80]) ifTrue:[
            newField level:0.
            newField leftInset:0.
        ].
        newField rightInset:(menuButton leftInset negated).
    ].

    menuField := newField.
    menuField model:model.
    menuField  font:font.
    self shown ifTrue:[ menuField realize ].


! !

!ExtendedComboBox methodsFor:'event handling'!

doesNotUnderstand:aMessage
    "does not understand message; delegate to widget
    "
    ^ aMessage sendTo:menuWidget


!

keyPress:key x:x y:y
    "handle a key press event
    "
    (key == Character space or:[key == #Return]) ifTrue:[
        self enabled ifTrue:[
            self openMenu
        ]
    ] ifFalse:[
        super keyPress:key x:x y:y
    ]

!

update:what with:aPara from:aModel
    "one of my models changed
    "
    aModel == self model ifTrue:[
        ^ self closeMenu
    ].
    aModel == self menuWidgetHolder ifTrue:[
        ^ self menuWidget:(menuWidgetHolder value)
    ].
    super update:what with:aPara from:aModel


! !

!ExtendedComboBox methodsFor:'initialization'!

destroy
    "destroy the menuWrapper and release dependencies
    "
    menuWidgetHolder notNil ifTrue:[
        menuWidgetHolder removeDependent:self
    ].
    self  menuWidget:nil.
    super destroy.
!

initialize
    "setup defaults
    "
    |prefExt leftInset halfSpacing l|

    super initialize.

    menuButton := ComboBoxButton origin:1.0@0.0 corner:1.0@1.0 in:self.
    menuButton controller beTriggerOnDown.
    menuButton label:(ComboView buttonForm).
    menuButton showLamp:false.

    menuButton activeLevel == menuButton passiveLevel ifTrue:[
        menuButton activeLevel:0.
    ].
    menuButton pressAction:[self openMenu].

    prefExt := menuButton preferredExtent.

    styleSheet is3D ifTrue:[
        halfSpacing := ViewSpacing // 2.
        leftInset   := prefExt x + halfSpacing.

        (l := styleSheet at:'comboViewLevel' default:nil) notNil ifTrue:[
            self level:l.
        ] ifFalse:[
            menuButton rightInset:halfSpacing.
        ]
    ] ifFalse:[
        leftInset := prefExt x + menuButton borderWidth.
    ].

    (styleSheet name = #win95 or:[styleSheet name = #st80]) ifTrue:[
        self level:-1.
        menuButton rightInset:0.

        styleSheet name = #win95 ifTrue:[
            leftInset := (ArrowButton new preferredExtent x).
        ].
    ].
    menuButton leftInset:leftInset negated.
    self model:nil.

    adjust                   := #right.
    usePreferredWidthForMenu := false.
    isReadOnly               := false.
    self readOnly:true.

! !

!ExtendedComboBox methodsFor:'user interactions'!

closeMenu
    "close the menu
    "
    |id|

    menuWrapper notNil ifTrue:[
        menuWrapper realized ifFalse:[
            (id := menuWrapper id) notNil ifTrue:[
                device unmapWindow:id
            ]
        ] ifTrue:[
           menuWrapper unmap
        ].
        menuWrapper windowGroup:nil.
        self windowGroup removeView:menuWrapper.
    ].
    menuButton turnOff.

!

openMenu
    "pull the menu - triggered from the button
    "
    |winGroup h w menuOrigin menuPrfExt useableExt|

    menuWrapper isNil ifTrue:[
        menuWidget isNil ifTrue:[^ self].
        menuWrapper := MenuWrapper for:menuWidget in:self
    ].
    menuButton turnOn.

    (winGroup := self windowGroup) notNil ifTrue:[
        menuWrapper windowGroup:winGroup.
        winGroup  addTopView:menuWrapper.
    ].

    menuOrigin := device translatePoint:(0@height) from:(self id) to:(device rootWindowId).
    useableExt := device usableExtent.
    menuPrfExt := menuWrapper preferredExtent.

    menuHeight isNil ifTrue:[
        menuHeight := (5 + menuPrfExt y) min:(useableExt y // 2).
    ].
    h := (useableExt y - menuOrigin y - 4) min:menuHeight.

    usePreferredWidthForMenu ifFalse:[
        w := width
    ] ifTrue:[
        (w := menuPrfExt x) <= width ifTrue:[
            w := width
        ] ifFalse:[
            (w + menuOrigin x) > useableExt x ifTrue:[
                menuOrigin x:((useableExt x - w) max:0)
            ]
        ]
    ].
    menuWrapper origin:menuOrigin extent:(w @ h).

    menuWrapper realized ifFalse:[
        menuWrapper realize. 
    ] ifTrue:[
        device mapWindow:menuWrapper id.
    ].
    menuWrapper makeFullyVisible.
! !

!ExtendedComboBox::MenuWrapper class methodsFor:'instance creation'!

for:aWidget in:aReceiver
    ^ self new for:aWidget in:aReceiver.
! !

!ExtendedComboBox::MenuWrapper methodsFor:'accessing'!

application
    "return the application, under which this view was opened,
     or nil, if there is no application
    "
    ^ comboBox application

!

preferredExtent
    "compute & return the preferredExtent from the components' preferrences
    "
    |x y|

    x := widget widthOfContents  + 8.
    y := widget heightOfContents + 8.
  ^ x @ y
!

widget
    "returns the widget wrapped by the menuView
    "
    ^ widget
! !

!ExtendedComboBox::MenuWrapper methodsFor:'event handling'!

buttonMotion:button x:x y:y
    "handle a button motion event
    "
    |p view|

    pointerScrollbarView notNil ifTrue:[
        "the pointer was pressed in the scrollbar and yet not released"
        "therefore send all motion events to the scrollbar"
        p := device translatePoint:(x@y) from:(self id) to:(pointerScrollbarView id).
        pointerScrollbarView buttonMotion:button x:p x y:p y
    ]ifFalse:[
        (view := self detectViewAtX:x y:y) notNil ifTrue:[
            p := device translatePoint:(x@y) from:(self id) to:(view id).

            (view controller notNil and:[view controller ~~ view]) ifTrue:[
                view controller buttonMotion:button x:p x y:p y 
            ] ifFalse:[
                view buttonMotion:button x:p x y:p y
            ]
        ].
    ].
!

buttonMultiPress:button x:x y:y
    "handle a multi press event
    "
    |p view|

    (view := self detectViewAtX:x y:y) isNil ifTrue:[
        comboBox closeMenu
    ] ifFalse:[
        p := device translatePoint:(x@y) from:(self id) to:(view id).

        (view controller notNil and:[view controller ~~ view]) ifTrue:[
            view controller buttonMultiPress:button x:p x y:p y 
        ] ifFalse:[
            view buttonMultiPress:button x:p x y:p y
        ]
    ].

    "Created: / 5.12.1998 / 14:20:02 / ps"
    "Modified: / 5.12.1998 / 14:27:16 / ps"
!

buttonPress:button x:x y:y
    "handle a button press event
    "
    |p view|

    (view := self detectViewAtX:x y:y) isNil ifTrue:[
        comboBox closeMenu
    ] ifFalse:[
        (view isKindOf:Scroller) ifTrue:[
            pointerScrollbarView := view.
        ].
        p := device translatePoint:(x@y) from:(self id) to:(view id).

        (view controller notNil and:[view controller ~~ view]) ifTrue:[
            view controller buttonPress:button x:p x y:p y 
        ] ifFalse:[
            view buttonPress:button x:p x y:p y
        ]
    ]
!

buttonRelease:button x:x y:y
    "handle a button release event
    "
    |p view t|

    (view := pointerScrollbarView) notNil ifTrue:[
        "if the pointer was pressed in the scrollbar, set the pressed flag to false"
        "and indicate the scrollbar the release of the button"
        pointerScrollbarView := nil.
        view buttonRelease:button x:x y:y.
        ^ self
    ].

    (view := self detectViewAtX:x y:y) notNil ifTrue:[
        p := device translatePoint:(x@y) from:(self id) to:(view id).

        (view controller notNil and:[view controller ~~ view]) ifTrue:[
            view controller buttonRelease:button x:p x y:p y
        ] ifFalse:[
            view buttonRelease:button x:p x y:p y
        ]
    ].
!

keyPress:key x:x y:y
    "handle a key press event
    "
    |view|

    (key == #Tab or:[key == #ISO_Left_Tab]) ifTrue:[
        comboBox closeMenu
    ] ifFalse:[
        view := (self detectViewAtX:x y:y) ? widget.
        view keyPress:key x:x y:y.
    ]
! !

!ExtendedComboBox::MenuWrapper methodsFor:'grabbing'!

grabMouseAndKeyboard
    "get exclusive access to pointer and keyboard.
    "
    |sensor|

    realized ifTrue:[
        sensor := self sensor.

        device activePointerGrab ~~ self ifTrue:[
            sensor notNil ifTrue:[
                sensor flushMotionEventsFor:nil.
            ].

            (device grabPointerInView:self) ifFalse:[
                Delay waitForSeconds:0.1.
                (device grabPointerInView:self) ifFalse:[
                    "give up"
                    self unmap
                ]
            ]
        ].

        device activeKeyboardGrab ~~ self ifTrue:[
            sensor notNil ifTrue:[
                device sync.
                sensor flushKeyboardFor:nil
            ].
            device grabKeyboardInView:self.
            self getKeyboardFocus.
        ]
    ]
!

ungrabMouseAndKeyboard
    "ungrab resources (mouse and keyboard)
    "
    |sensor|

    device ungrabPointer.

    (sensor := self sensor) notNil ifTrue:[
        "/ make certain all X events have been received
        device sync.
        "/ now all events have been received.
        "/ now, flush all pointer events
        sensor flushKeyboardFor:nil
    ].
    device ungrabKeyboard.

! !

!ExtendedComboBox::MenuWrapper methodsFor:'initialization'!

create
    "create the shadow view for a none contained submenu
    "
    super create.
    (PopUpView styleSheet at:'popup.shadow' default:false) ifTrue:[
        shadowView isNil ifTrue:[
            shadowView := (ShadowView onDevice:device) for:self
        ] ifFalse:[
            self saveUnder:true.
        ].
    ]


!

destroy
    "ungrab resources (mouse and keyboard)
    "
    self  ungrabMouseAndKeyboard.
    super destroy.
    shadowView notNil ifTrue:[shadowView destroy].

!

for:aWidget in:aReceiver 
    "create a wrapper for a widget and the receiver, an extented comboBox
    "
    comboBox := aReceiver.

    aWidget isScrollWrapper ifFalse:[
        widget := ScrollableView forView:aWidget miniScrollerH:true
    ] ifTrue:[
        widget := aWidget
    ].
    widget autoHideScrollBars:true.
    widget origin:0.0 @ 0.0 corner:1.0 @ 1.0.
    self add:widget.
    widget := widget scrolledView.
!

initialize
    "setup default; set width of border to 0
    "
    super initialize.
    self borderWidth:0.

!

mapped
    "grab resources (mouse and keyboard)
    "
    pointerScrollbarView := nil.
    super mapped.
    self  grabMouseAndKeyboard.
!

realize
    "realize menu view and shadowView.
     Because of #saveUnder of ShadowView the order of realize is significant:
     shadowView must be realized before self
    "
    self hiddenOnRealize:true.
    super realize.
    self  resize.

    shadowView notNil ifTrue:[
        shadowView realize.
    ].
    super map.
    self raise.

!

unmap
    "ungrab resources (mouse and keyboard)
    "
    self  ungrabMouseAndKeyboard.
    super unmap.
    shadowView notNil ifTrue:[shadowView unmap].
! !

!ExtendedComboBox::MenuWrapper methodsFor:'queries'!

isPopUpView
    "return true, since I want to come up without decoration
    "
    ^ true
!

raiseDeiconified
    ^ self raise

!

type
    ^ nil.


! !

!ExtendedComboBox::MenuWrapper methodsFor:'searching'!

detectViewAtX:x y:y
    "detect view at x@y. if no view is detected or
     the it is my view nil is returned
    "
    |v|

    (x notNil or:[y notNil]) ifTrue:[
        ((x between:0 and:width) and:[y between:0 and:height]) ifTrue:[
            v := self detectViewAtX:x y:y in:self.
            v ~~ self ifTrue:[^ v].
        ]
    ].
    ^ nil
!

detectViewAtX:x y:y in:aTopView
    "detect view at x@y in a top view; if no view is detected
     the topview is returned
    "
    |subviews|

    (subviews := aTopView subViews) notNil ifTrue:[
        subviews do:[:v||p|
            (    (x between:(v left) and:(v right))
             and:[y between:(v top)  and:(v bottom)]
            ) ifTrue:[
                p := device translatePoint:(x@y) from:(aTopView id) to:(v id).
                ^ self detectViewAtX:p x y:p y in:v.
            ]
        ]
    ].
    ^ aTopView
! !

!ExtendedComboBox class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ExtendedComboBox.st,v 1.3 1999-03-05 15:54:58 cg Exp $'
! !