PopUpList.st
author claus
Sat, 18 Mar 1995 06:16:50 +0100
changeset 105 3d064ba4a0cc
parent 95 7535cfca9509
child 119 59758ff5b841
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1994 by 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:2.10.5 on 14-mar-1995 at 11:16:49 am'!

Button subclass:#PopUpList
	 instanceVariableNames:'menu menuAction values'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Interactors'
!

PopUpList comment:'
COPYRIGHT (c) 1994 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/PopUpList.st,v 1.8 1995-03-18 05:15:33 claus Exp $
'!

!PopUpList class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 by 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.
"
!

version
"
$Header: /cvs/stx/stx/libwidg/PopUpList.st,v 1.8 1995-03-18 05:15:33 claus Exp $
"
!

documentation
"
    a PopUpList is basically a button with a popup menu.
    The PopUpLists label is showing the current selection from the
    list.
"
!

examples
"
    example use:

     |p|
     p := PopUpList label:'healthy fruit'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margarithas').
     p open


    with an initial selection:

     |p|
     p := PopUpList label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margarithas').
     p selection:'apples'.
     p open


    with separating lines:

     |p|
     p := PopUpList label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margarithas').
     p selection:'apples'.
     p open


    with an action:

     |p|
     p := PopUpList label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margarithas').
     p selection:'apples'.
     p action:[:what | Transcript showCr:'you selected: ' , what].
     p open


    with values different from the label strings:

     |p|
     p := PopUpList label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margarithas').
     p selection:'apples'.
     p values:#(10 20 30 40 nil 50).
     p action:[:what | Transcript show:'you selected: '; showCr:what].
     p open
"
! !

!PopUpList methodsFor:'drawing'!

drawWith:fgColor and:bgColor
    |mmH mmV mW mH|

    controller pressed ifTrue:[
	super drawWith:enteredFgColor and:enteredBgColor
    ] ifFalse:[
	super drawWith:fgColor and:bgColor.
    ].
    mmH := device horizontalPixelPerMillimeter rounded.
    mmV := device verticalPixelPerMillimeter rounded.
    mW := (device horizontalPixelPerMillimeter * 2.5) rounded.
    mH := (device verticalPixelPerMillimeter * 1.5) rounded.

    self drawEdgesForX:(width - mW - (hSpace*2)) y:(height - mmV // 2)
		 width:mW height:mH level:2
! !

!PopUpList methodsFor:'event handling'!

popMenu
    |org mv|

    menu notNil ifTrue:[
	self turnOff. 
	menu font:font.

	"
	 adjust the menus width to my current width
	"
	mv := menu menuView.
	mv width:(self width - (2 * menu margin) - (menu borderWidth*2)).
	mv level:0; borderWidth:0.
	mv fixSize.
	"
	 the popupMenu wants Display coordinates in its showAt: method
	"
	org := device translatePoint:0@0 
				from:(self id)
				  to:(DisplayRootView new id).

	menu showAt:org "resizing:false"
    ].
! !

!PopUpList methodsFor:'initialization'!

initialize
    super initialize.
    controller beTriggerOnDown.
    controller action:[self popMenu].
    self adjust:#left
! !

!PopUpList methodsFor:'accessing'!

contents
    ^ self label
!

contents:con
    ^ self selection:con

!

model:aModel
    "set the model - this is forwarded to my menu. 
     The popuplist itself has no model"

    menu model:aModel
!

model
    "return the model - this is forwarded to my menu. 
     The popuplist itself has no model"

    ^ menu model
!

change:aSymbol
    "set the change symbol - this is forwarded to my menu. 
     The popuplist itself has no model"

    menu change:aSymbol
!

changeSymbol
    "return the change symbol - this is forwarded to my menu. 
     The popuplist itself has no model"

    ^ menu changeSymbol
!

action:aOneArgBlock
    "set the action to be performed on selection changes;
     the argument, aOneArgBlock will be evaluated with the
     selection-value as argument"

    menuAction := aOneArgBlock
!

list
    "return the list - i.e. the values shown in the pop-up list"

    ^ menu labels
!

list:aList
    "set the list - i.e. the values shown in the pop-up list"

    menu := PopUpMenu
		  labels:aList
	       selectors:(Array new:(aList size) withAll:#select:)
		    args:aList
		receiver:self
		     for:self.
    realized ifTrue:[
	self computeLabelSize
    ]

    "
     |p|
     p := PopUpList label:'fruit ?'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margarithas').
     p open
    "
!

values:aList
    "set a value list - these are reported via the action or changeSymbol instead of
     the labe strings."

    values := aList.
    menu args:(1 to:aList size).

    "
     |p|
     p := PopUpList label:'fruit ?'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margarithas').
     p values:#(1 2 3 4 'mhmh - good').
     p open
    "
!

selection:indexOrString
    "set (force) a selection - usually done to set
     an initial selection"

    |index|

    index := menu labels indexOf:indexOrString.
    index == 0 ifTrue:[^ self].
    self label:(menu labels at:index)

    "
     |p|
     p := PopUpList label:'what fruit ?'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margarithas').
     p selection:'grape'.
     p open 

     |p|
     p := PopUpList label:'what fruit ?'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margarithas').
     p selection:'blabla'.
     p open
    "
! !

!PopUpList methodsFor:'private'!

computeLabelSize
    "compute the extent needed to hold the label plus the mark"

    |mmH mmV savedLogo longest longestWidth|

    menu isNil ifTrue:[
	super computeLabelSize
    ] ifFalse:[
	"hack: simulate logo change to longest menu entry"

	font := font on:device.
	longest := logo.
	longestWidth := font widthOf:logo.
	menu labels do:[:entry |
	    |this|

	    this := font widthOf:entry printString.
	    this > longestWidth ifTrue:[
		longest := entry.
		longestWidth := this
	    ].
	].
	savedLogo := logo.
	logo := longest.
	super computeLabelSize.
	logo := savedLogo.
"self halt.     "
    ].
    mmH := device horizontalPixelPerMillimeter.
    mmV := device verticalPixelPerMillimeter.
    labelWidth := labelWidth + hSpace + (mmH * 2.5) rounded + hSpace.
    labelHeight := labelHeight max: (mmV * 2) rounded
! !

!PopUpList methodsFor:'user actions'!

select:anEntry
    |value label|

"/ 'selected:' print. anEntry printNewline.
    values isNil ifTrue:[
	label := value := anEntry
    ] ifFalse:[
	label := menu labels at:anEntry.
	value := values at:anEntry
    ].

    menuAction notNil ifTrue:[
	menuAction value:value.
    ].
    self sizeFixed:true.
    self label:label printString.
    self sendChangeMessageWith:value 
! !