PopUpList.st
author Claus Gittinger <cg@exept.de>
Tue, 25 Feb 1997 15:51:44 +0100
changeset 1052 59f182d1304f
parent 1035 c7cfaead1621
child 1063 b315e2580bc7
permissions -rw-r--r--
added list- and selectionHolders

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

Button subclass:#PopUpList
	instanceVariableNames:'menu menuAction values useIndex listMsg defaultLabel
			       listHolder selectionHolder'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Interactors'
!

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

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.

    If no model is set, the list is assumed to be a static list, which
    is defined via #list:, and the popUpList evaluates the action block,
    as defined via #action:.

    If a model is provided, it should return the list from the listMsg (default
    is #list) and the current selected items index via 
    #selection or: #selectionIndex (depending on the setting of useIndex).

    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.


	listHolder           <Object>   if non-nil, this object is assumed to return the
					list via the listMsg (instead of the model).
					Default is nil.

	selectionHolder      <Object>   if non-nil, this object is assumed to return the
					selection via the changeMsg (instead of the model).
					UseIndex specifies if its numeric (i.e. a selectionindex) 
					Default is nil.

    [see also:]
	SelectionInListView
	SelectionInList

    [author:]
	Claus Gittinger
"
!

examples
"
    example use:
									[exBegin]
     |p|
     p := PopUpList label:'healthy fruit'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
     p open
									[exEnd]


    with an initial selection:
									[exBegin]
     |p|
     p := PopUpList label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
     p selection:'apples'.
     p open
									[exEnd]


    with separating lines:
									[exBegin]
     |p|
     p := PopUpList label:'fruit'.
     p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
     p selection:'apples'.
     p open
									[exEnd]


    with an action:
									[exBegin]
     |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
									[exEnd]


    sometimes, you may like the index instead of the value:
    (notice, that the separating line counts, so you have to take care ...)
									[exBegin]
     |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
									[exEnd]


    since the list is actually a popupMenu, you can add double-separators:
									[exBegin]
     |p|
     p := PopUpList label:'dummy'.
     p list:#('apples' 'bananas' 'grape' 'lemon' 
	      '=' 
	      'margaritas' 'pina colada'
	      '=' 
	      'smalltalk' 'c++' 'eiffel' 'java').
     p values:#(apples bananas grape lemon 
		nil 
		'mhmh - so good' 'makes headache'
		nil
		'great' 'another headache' 'not bad' 'neat').
     p selection:'apples'.
     p action:[:what | Transcript show:'you selected: '; showCR:what].
     p open
									[exEnd]


    since the list is actually represented by a menuView,
    which itself is inheriting from listView, which itself can display
    things different from strings, arbitrary lists can be constructed:
    (see ListEntry classes)
									[exBegin]
     |p l|
     p := PopUpList label:'dummy'.
     l := OrderedCollection new.
     l add:(ColoredListEntry string:'apples' color:Color red).
     l add:(ColoredListEntry string:'bananas' color:Color red).
     l add:(ColoredListEntry string:'grape' color:Color red).
     l add:(ColoredListEntry string:'lemon' color:Color red).
     l add:'='.
     l add:(ColoredListEntry string:'margaritas' color:Color green darkened darkened).
     l add:(ColoredListEntry string:'pina colada' color:Color green darkened darkened).
     l add:'='.
     l add:(ColoredListEntry string:'smalltalk' color:Color blue).
     l add:(ColoredListEntry string:'c++' color:Color blue).
     l add:(ColoredListEntry string:'eiffel' color:Color blue).
     l add:(ColoredListEntry string:'java' color:Color blue).
     p list:l.
     p values:#(apples bananas grape lemon 
		nil 
		'mhmh - so good' 'makes headache'
		nil
		'great' 'another headache' 'not bad' 'neat').
     p selection:'apples'.
     p action:[:what | Transcript show:'you selected: '; showCR:what].
     p open
									[exEnd]


    with values different from the label strings:
									[exBegin]
     |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
									[exEnd]


    with a model (see in the inspector, how the valueHolders index-value changes):
									[exBegin]
     |p model|

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

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


    a popupList and a SelectionInListView on the same model:
									[exBegin]
     |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
									[exEnd]


    two PopUpLists on the same model, different aspects:
									[exBegin]
     |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 corona)].

     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
									[exEnd]


    with separate list- and indexHolders:
									[exBegin]
     |p selectionHolder listHolder|

     listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
     selectionHolder := 'apples' asValue.

     p := PopUpList label:'healthy fruit'.
     p listHolder:listHolder.
     p selectionHolder:selectionHolder.
     p open.
     selectionHolder inspect
									[exEnd]

    same, using index:
									[exBegin]
     |p selectionIndexHolder listHolder|

     listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
     selectionIndexHolder := 3 asValue.

     p := PopUpList new.
     p listHolder:listHolder.
     p selectionHolder:selectionIndexHolder.
     p useIndex:true.
     p open.
     selectionIndexHolder inspect
									[exEnd]


"
! !

!PopUpList class methodsFor:'defaults'!

defaultAspectMessage
    ^ #selection
!

defaultChangeMessage
    ^ #selection:
!

defaultListMessage
    ^ #list 
! !

!PopUpList methodsFor:'accessing'!

contents
    ^ self label
!

contents:con
    ^ self selection:con

    "Modified: 25.5.1996 / 14:20:57 / cg"
!

defaultLabel:aString
    "set the defaultLabel, to be shown if nothing is selected"

    defaultLabel := aString
!

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"

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

listHolder
    "return the listHolder if any"

    ^ listHolder
!

listHolder:aValueHolder
    "set the listHolder and change the listMessage to #value."

    listHolder notNil ifTrue:[
	listHolder removeDependent:self.
    ].
    listHolder := aValueHolder.
    listHolder notNil ifTrue:[
	listHolder addDependent:self.
    ].
    listMsg := #value.
    shown ifTrue:[
	self getListFromModel
    ]
!

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

    |index wasFix|

    menu isNil ifTrue:[
	self getListFromModel.
    ].
    menu isNil ifTrue:[^ self].

    index := menu indexOf:indexOrString.
    index == 0 ifTrue:[
	self label:defaultLabel.
	^ self
    ].

    "kludge: dont want label to resize ..."
    wasFix := fixSize. fixSize := true.
    self label:(menu labels at:index) printString.
    fixSize := wasFix

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

    "Modified: 8.2.1996 / 12:55:01 / cg"
!

selectionHolder
    "return the selectionHolder if any"

    ^ selectionHolder
!

selectionHolder:aValueHolder
    "set the selectionHolder and change the aspect/changeMessage to #value / #value:"

    selectionHolder notNil ifTrue:[
	selectionHolder removeDependent:self.
    ].
    selectionHolder := aValueHolder.
    selectionHolder notNil ifTrue:[
	selectionHolder addDependent:self.
    ].
    aspectMsg := #value.
    changeMsg := #value:.
    shown ifTrue:[
	self getSelectionFromModel
    ]
!

values:aList
    "set a value list - these are reported via the action or changeSymbol instead of
     the label 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-behavior'!

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

!PopUpList methodsFor:'accessing-mvc'!

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

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

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

    |l|

    listMsg notNil ifTrue:[
	listHolder notNil ifTrue:[
	    l := listHolder perform:listMsg
	] ifFalse:[
	    model notNil ifTrue:[
		l := model perform:listMsg.
	    ]
	].
	self list:l
    ]
!

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

    |sel|

    aspectMsg notNil ifTrue:[
	selectionHolder notNil ifTrue:[
	    sel := selectionHolder perform:aspectMsg
	] ifFalse:[
	    model notNil ifTrue:[
		sel := model perform:aspectMsg.
	    ]
	].
	self selection:sel
    ].

    "Modified: 25.5.1996 / 14:21:07 / cg"
!

listMessage
    "return the selector by which we ask the model for the list.
     The default is #list if used with a model 
     or #value, if used with a listHolder."

    ^ listMsg
!

listMessage:aSelector
    "set the selector by which we ask the model for the list.
     The default is #list if used with a model 
     or #value, if used with a listHolder."

    listMsg := aSelector
! !

!PopUpList methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    changedObject == listHolder ifTrue:[
	self getListFromModel.
	^ self
    ].
    changedObject == selectionHolder ifTrue:[
	self getSelectionFromModel.
	^ self
    ].

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

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

showActive
    "no need to redraw - will pop menu ontop of me anyway ..."

    ^ self
!

showPassive
    "no need to redraw - will redraw from unpopped menu anyway ..."

    ^ self
! !

!PopUpList methodsFor:'event handling'!

popMenu
    |org mv w|

    menu notNil ifTrue:[
	self turnOffWithoutRedraw. 

	menu labels size == 0 ifTrue:[
	    ^ self
	].

	menu font:font.

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

	"
	 the popupMenu wants Display coordinates in its showAt: method
	"
	org := device translatePoint:0@0 
				from:(self id)
				  to:(device rootView id).

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

!PopUpList methodsFor:'initialization'!

defaultControllerClass
    ^ PopUpListController
!

initialize
    super initialize.

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

    onLevel := offLevel.
! !

!PopUpList methodsFor:'private'!

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

    |mmH mmV savedLogo longest longestWidth labels|

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

	font := font on:device.
	longest := logo.
	logo isNil ifTrue:[
	    longestWidth := 0
	] ifFalse:[
	    longestWidth := font widthOf:logo.
	].
	labels := menu labels.
	labels notNil ifTrue:[
	    labels do:[:entry |
		|this|

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

    "Modified: 8.2.1996 / 13:00:33 / cg"
!

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

realize
    super realize.
    (model notNil or:[listHolder notNil]) ifTrue:[
        self getListFromModel.
    ].
    (model notNil or:[selectionHolder notNil]) ifTrue:[
        self getSelectionFromModel.
    ]
! !

!PopUpList methodsFor:'private-controller access'!

menu
    "return the menu component"

    ^ menu
! !

!PopUpList methodsFor:'queries'!

preferredExtent
    "redefined to make certain that the menu is fully defined"

    "/ If I have an explicit preferredExtent ..

    preferredExtent notNil ifTrue:[
	^ preferredExtent
    ].

    menu isNil ifTrue:[
	self getListFromModel
    ].
    self computeLabelSize.
    ^ super preferredExtent.

    "Modified: 19.7.1996 / 20:45:16 / cg"
!

specClass
    self class == PopUpList ifTrue:[^ PopUpListSpec].
    ^ super specClass
! !

!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
    ].

    self sizeFixed:true.
    self label:label printString.

    selectionHolder notNil ifTrue:[
	selectionHolder perform:changeMsg with:value
    ].

    "/
    "/ ST-80 way of doing it
    "/ tell my model - if any
    "/
    self sendChangeMessageWith:value.

    "/
    "/ ST/X action blocks
    "/
    menuAction notNil ifTrue:[
	menuAction value:value.
    ].

    "Modified: 14.2.1997 / 16:47:09 / cg"
! !

!PopUpList class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/PopUpList.st,v 1.32 1997-02-25 14:51:44 cg Exp $'
! !