PopUpList.st
author claus
Wed, 10 May 1995 04:30:46 +0200
changeset 126 40228f4fd66b
parent 125 3ffa271732f7
child 127 462396b08e30
permissions -rw-r--r--
.

"
 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 9-may-1995 at 12:06:03 pm'!

Button subclass:#PopUpList
	 instanceVariableNames:'menu menuAction values useIndex listMsg'
	 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.13 1995-05-10 02:29:55 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.13 1995-05-10 02:29:55 claus Exp $
"
!

documentation
"
    a PopUpList is basically a button with a popup menu.
    The PopUpLists label is showing the current selection from the
    list.
    When an entry is selected, an actionBlock (if nonNil) is evaluated
    and (if nonNil), the model is notified via the changeMessage.

    The default changeMessage used is #selection:, which allows a
    PopUpList to be used with a SelectionInList as model.
    (if used with some other model, either use an adaptor, or set the
     changeMessage to something else ..)

    Instance variables:

	menu                            helpers for the popup menu
	menuAction 
	values 

	useIndex             <Boolean>  if true, the index of the selected entry
					is passed to the action block and the
					model in a change-message.
					If false (the default), the value is passed.
					Notice that the default changeMessage is
					#selection:, which is not ok to be used
					with useIndex:true and a selectionInList model.
					(set the changeMessage to #selectionIndex: then)

	listMsg              <Symbol>   message to aquire a new list from the
					model. Default is #list.
"
!

examples
"
    example use:

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


    with an initial selection:

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


    with separating lines:

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


    with an action:

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


    sometimes, you may like the index instead of the value:
    (notice, that the separating line counts, so you have take care ...)

     |p|
     p := PopUpList 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


    since the list is actually a popupMenu, you can add double-separators:

     |p|
     p := PopUpList label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 
              '=' 
              'margaritas' 'pina colada'
              '=' 
              'smalltalk' 'c++' 'eiffel').
     p values:#(apples bananas grape lemon 
                nil 
                'mhmh - so good' 'makes headache'
                nil
                'great' 'another headache' 'no bad').
     p selection:'apples'.
     p action:[:what | Transcript show:'you selected: '; showCr:what].
     p open


    with values different from the label strings:

     |p|
     p := PopUpList 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


    with a model:

     |p model|

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

     p := PopUpList label:'healthy fruit'.
     p model:model.
     p open.
     model selectionIndexHolder inspect


    with a model (using numeric selection values):

     |p model|

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

     p := PopUpList label:'healthy fruit'.
     p model:model; useIndex:true; change:#selectionIndex:.
     p open.
     model selectionIndexHolder inspect


    a popupList and a SelectionInListView on the same model:

     |p slv model|

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

     p := PopUpList on:model.
     p useIndex:true; aspect:#selectionIndex; change:#selectionIndex:.
     p open.

     slv := SelectionInListView on:model.
     slv open.

     p inspect.
     model selectionIndexHolder inspect


    two PopUpLists on the same model:

     |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 beer)].

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

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

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

     top open
"
! !

!PopUpList class methodsFor:'defaults'!

defaultAspectMessage
    ^ #selection
!

defaultListMessage
    ^ #list 
!

defaultChangeMessage
    ^ #selection:
! !

!PopUpList methodsFor:'private'!

realize
    super realize.
    model notNil ifTrue:[
        self getListFromModel.
        self getSelectionFromModel.
    ].
!

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
!

createMenuFor:aList
    menu := PopUpMenu
		  labels:aList
	       selectors:#select:
		    args:(1 to:aList size) 
		receiver:self
		     for:self.
! !

!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 turnOffWithoutRedraw. 
	menu font:font.

	"
	 adjust the menus width to my current width
	"
	mv := menu menuView.
	mv create.      "/ stupid: it resizes itself upon first create
	mv width:(self width - (2 * menu margin) - (menu borderWidth*2)).
	mv level:0; borderWidth:0.

	"
	 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:'accessing'!

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

    |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' 'margaritas').
     p selection:'grape'.
     p open 

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

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

    self createMenuFor:aList.
    realized ifTrue:[
	self computeLabelSize
    ]

    "
     |p|
     p := PopUpList label:'fruit ?'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
     p action:[:val | Transcript showCr:'selected: ' , val printString].   
     p open
    "
!

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
!

useIndex:aBoolean 
    "tell the popuplist to pass the index (instead of the value)
     to both the actionBlock and model. Notice, that if you use a model,
     the default changeSelector is not ok for using index and a SelectionInList"

    useIndex := aBoolean

    "
     |p|
     p := PopUpList label:'fruit ?'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
     p action:[:val | Transcript showCr:'selected: ' , val printString].   
     p open.
    "
    "
     |p|
     p := PopUpList label:'fruit ?'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
     p action:[:val | Transcript showCr:'selected: ' , val printString].   
     p useIndex:true.
     p open.
    "
!

contents
    ^ self label
!

contents:con
    ^ self selection:con

!

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

    ^ menu labels
!

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' 'margaritas').
     p values:#(1 2 3 4 'mhmh - good').
     p action:[:val | Transcript showCr:'selected: ' , val printString].   
     p open.
    "
! !

!PopUpList methodsFor:'accessing-mvc'!

getListFromModel
    "if I have a model and a listMsg, get my list from it"

    (model notNil 
    and:[listMsg notNil]) ifTrue:[
	self list:(model perform:listMsg).
    ].
!

getSelectionFromModel
    "if I have a model and an aspectMsg, get my current value from it"

    (model notNil 
    and:[aspectMsg notNil]) ifTrue:[
	self selection:(model perform:aspectMsg).
    ].
!

listMessage:aSelector
    "set the selector by which we ask the model for the list.
     Default is #list."

    listMsg := aSelector
!

addModelInterfaceTo:aDictionary
    "see comment in View>>modelInterface"

    super addModelInterfaceTo:aDictionary.
    aDictionary at:#listMessage put:listMsg
!

listMessage
    "return the selector by which we ask the model for the list.
     Default is #list."

    ^ listMsg
! !

!PopUpList methodsFor:'initialization'!

initialize
    super initialize.

    controller beTriggerOnDown.
    controller action:[self popMenu].
    self adjust:#left.
    useIndex := false.
    self label:'popup'.
    listMsg := self class defaultListMessage.

    onLevel := offLevel.
! !

!PopUpList methodsFor:'user actions'!

select:anEntry
    "this is sent from the popupmenu when an entry was selected"

    |value label|

    label := menu labels at:anEntry.
    values isNil ifTrue:[
	value := anEntry.
	useIndex ifFalse:[
	    value := menu labels at:anEntry.
	]
    ] ifFalse:[
	value := values at:anEntry
    ].

    menuAction notNil ifTrue:[
	menuAction value:value.
    ].
    self sizeFixed:true.
    self label:label printString.
    "
     tell my model - if any
    "
    self sendChangeMessageWith:value 
! !

!PopUpList methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    changedObject == model ifTrue:[
	something == aspectMsg ifTrue:[
	    self getSelectionFromModel.
	    ^ self
	].
	something == listMsg ifTrue:[
	    self getListFromModel.
	].
	^ self
    ].
    super update:something with:aParameter from:changedObject
! !