ComboListView.st
changeset 679 bd0e422aab67
parent 598 288e67e06da4
child 682 861e446e3b24
equal deleted inserted replaced
678:9afa8810a8be 679:bd0e422aab67
     1 "
     1 "
     2  COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
     2  COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
     3               All Rights Reserved
     3 	      All Rights Reserved
     4 
     4 
     5  This software is furnished under a license and may be used
     5  This software is furnished under a license and may be used
     6  only in accordance with the terms of that license and with the
     6  only in accordance with the terms of that license and with the
     7  inclusion of the above copyright notice.   This software may not
     7  inclusion of the above copyright notice.   This software may not
     8  be provided or otherwise made available to, or used by, any
     8  be provided or otherwise made available to, or used by, any
    22 !ComboListView class methodsFor:'documentation'!
    22 !ComboListView class methodsFor:'documentation'!
    23 
    23 
    24 copyright
    24 copyright
    25 "
    25 "
    26  COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
    26  COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
    27               All Rights Reserved
    27 	      All Rights Reserved
    28 
    28 
    29  This software is furnished under a license and may be used
    29  This software is furnished under a license and may be used
    30  only in accordance with the terms of that license and with the
    30  only in accordance with the terms of that license and with the
    31  inclusion of the above copyright notice.   This software may not
    31  inclusion of the above copyright notice.   This software may not
    32  be provided or otherwise made available to, or used by, any
    32  be provided or otherwise made available to, or used by, any
    52     items in the popped menu; 
    52     items in the popped menu; 
    53     otherwise, if listMessage is nonNil, the model is assumed to also provide the
    53     otherwise, if listMessage is nonNil, the model is assumed to also provide the
    54     list as displayed in the popped menu.
    54     list as displayed in the popped menu.
    55 
    55 
    56     [author:]
    56     [author:]
    57         Claus Gittinger
    57 	Claus Gittinger
    58 
    58 
    59     [see also:]
    59     [see also:]
    60         ComboView
    60 	ComboView
    61         PopUpList SelectionInListView
    61 	PopUpList SelectionInListView
    62         ComboBoxView
    62 	ComboBoxView
    63         PullDownMenu Label EntryField
    63 	PullDownMenu Label EntryField
    64 "
    64 "
    65 !
    65 !
    66 
    66 
    67 examples
    67 examples
    68 "
    68 "
    69   non-MVC use; 
    69   non-MVC use; 
    70     set the list explicitely:
    70     set the list explicitely:
    71                                                         [exBegin]
    71 							[exBegin]
    72      |top comboBox|
    72      |top comboBox|
    73 
    73 
    74      top := StandardSystemView new.
    74      top := StandardSystemView new.
    75      top extent:(300 @ 200).
    75      top extent:(300 @ 200).
    76 
    76 
    78      comboBox origin:(0.0 @ 0.0) corner:(1.0 @ 0.0).
    78      comboBox origin:(0.0 @ 0.0) corner:(1.0 @ 0.0).
    79      comboBox bottomInset:(comboBox preferredExtent y negated).
    79      comboBox bottomInset:(comboBox preferredExtent y negated).
    80 
    80 
    81      comboBox list:#('hello' 'world' 'this' 'is' 'st/x').
    81      comboBox list:#('hello' 'world' 'this' 'is' 'st/x').
    82      top open.
    82      top open.
    83                                                                 [exEnd]
    83 								[exEnd]
    84 
    84 
    85 
    85 
    86 
    86 
    87     with callBack:
    87     with callBack:
    88                                                                 [exBegin]
    88 								[exBegin]
    89      |top b|
    89      |top b|
    90 
    90 
    91      top := StandardSystemView new.
    91      top := StandardSystemView new.
    92      top extent:(300 @ 200).
    92      top extent:(300 @ 200).
    93 
    93 
    96      b bottomInset:(b preferredExtent y negated).
    96      b bottomInset:(b preferredExtent y negated).
    97 
    97 
    98      b list:#('hello' 'world' 'this' 'is' 'st/x').
    98      b list:#('hello' 'world' 'this' 'is' 'st/x').
    99      b action:[:selected | Transcript showCR:selected].
    99      b action:[:selected | Transcript showCR:selected].
   100      top open.
   100      top open.
   101                                                                 [exEnd]
   101 								[exEnd]
   102 
   102 
   103 
   103 
   104 
   104 
   105     with values different from the label strings:
   105     with values different from the label strings:
   106                                                                         [exBegin]
   106 									[exBegin]
   107      |p|
   107      |p|
   108      p := ComboListView label:'dummy'.
   108      p := ComboListView label:'dummy'.
   109      p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
   109      p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
   110      p selection:'apples'.
   110      p selection:'apples'.
   111      p values:#(10 20 30 40 nil 50).
   111      p values:#(10 20 30 40 nil 50).
   112      p action:[:what | Transcript show:'you selected: '; showCR:what].
   112      p action:[:what | Transcript show:'you selected: '; showCR:what].
   113      p open
   113      p open
   114                                                                         [exEnd]
   114 									[exEnd]
   115 
   115 
   116 
   116 
   117     with separating lines:
   117     with separating lines:
   118                                                                 [exBegin]
   118 								[exBegin]
   119      |p|
   119      |p|
   120      p := ComboListView label:'fruit'.
   120      p := ComboListView label:'fruit'.
   121      p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
   121      p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
   122      p selection:'apples'.
   122      p selection:'apples'.
   123      p open
   123      p open
   124                                                                 [exEnd]
   124 								[exEnd]
   125 
   125 
   126 
   126 
   127 
   127 
   128 
   128 
   129     sometimes, you may like the index instead of the value:
   129     sometimes, you may like the index instead of the value:
   130     (notice, that the separating line counts, so you have to take care ...)
   130     (notice, that the separating line counts, so you have to take care ...)
   131                                                                 [exBegin]
   131 								[exBegin]
   132      |p|
   132      |p|
   133      p := ComboListView label:'dummy'.
   133      p := ComboListView label:'dummy'.
   134      p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
   134      p list:#('apples' 'bananas' 'grape' 'lemon' '-' 'margaritas').
   135      p selection:'apples'.
   135      p selection:'apples'.
   136      p action:[:what | Transcript show:'you selected: '; showCR:what].
   136      p action:[:what | Transcript show:'you selected: '; showCR:what].
   137      p useIndex:true.
   137      p useIndex:true.
   138      p open
   138      p open
   139                                                                 [exEnd]
   139 								[exEnd]
   140 
   140 
   141 
   141 
   142 
   142 
   143     since the list is actually represented by a menuView,
   143     since the list is actually represented by a menuView,
   144     which itself is inheriting from listView, which itself can display
   144     which itself is inheriting from listView, which itself can display
   145     things different from strings, arbitrary lists can be constructed:
   145     things different from strings, arbitrary lists can be constructed:
   146     (see ListEntry, LabelAndIcon and Text classes)
   146     (see ListEntry, LabelAndIcon and Text classes)
   147                                                                         [exBegin]
   147 									[exBegin]
   148      |p l|
   148      |p l|
   149      p := ComboListView label:'dummy'.
   149      p := ComboListView label:'dummy'.
   150 
   150 
   151      l := OrderedCollection new.
   151      l := OrderedCollection new.
   152      l add:(Text string:'apples' color:Color red).
   152      l add:(Text string:'apples' color:Color red).
   161      l add:(Text string:'c++' color:Color blue).
   161      l add:(Text string:'c++' color:Color blue).
   162      l add:(Text string:'eiffel' color:Color blue).
   162      l add:(Text string:'eiffel' color:Color blue).
   163      l add:(Text string:'java' color:Color blue).
   163      l add:(Text string:'java' color:Color blue).
   164      p list:l.
   164      p list:l.
   165      p values:#(apples bananas grape lemon 
   165      p values:#(apples bananas grape lemon 
   166                 nil 
   166 		nil 
   167                 'mhmh - so good' 'makes headache'
   167 		'mhmh - so good' 'makes headache'
   168                 nil
   168 		nil
   169                 'great' 'another headache' 'not bad' 'neat').
   169 		'great' 'another headache' 'not bad' 'neat').
   170      p selection:'apples'.
   170      p selection:'apples'.
   171      p action:[:what | Transcript show:'you selected: '; showCR:what].
   171      p action:[:what | Transcript show:'you selected: '; showCR:what].
   172      p open
   172      p open
   173                                                                         [exEnd]
   173 									[exEnd]
   174 
   174 
   175     with values different from the label strings:
   175     with values different from the label strings:
   176                                                                         [exBegin]
   176 									[exBegin]
   177      |p|
   177      |p|
   178 
   178 
   179      p := PopUpList label:'language selection'.
   179      p := PopUpList label:'language selection'.
   180      p list:( #(
   180      p list:( #(
   181                 'usa'
   181 		'usa'
   182                 'uk'
   182 		'uk'
   183                 'france'
   183 		'france'
   184                 'germany'       
   184 		'germany'       
   185                 'italy'
   185 		'italy'
   186                ) collect:[:country |
   186 	       ) collect:[:country |
   187                             LabelAndIcon 
   187 			    LabelAndIcon 
   188                                 icon:(Image fromFile:'bitmaps/xpmBitmaps/countries/' , country , '.xpm')
   188 				icon:(Image fromFile:'bitmaps/xpmBitmaps/countries/' , country , '.xpm')
   189                                 string:country
   189 				string:country
   190                          ]
   190 			 ]
   191             ).
   191 	    ).
   192      p values:#(us england france germany italy).
   192      p values:#(us england france germany italy).
   193 
   193 
   194      p action:[:what | Transcript show:'you selected: '; showCR:what].
   194      p action:[:what | Transcript show:'you selected: '; showCR:what].
   195      p open
   195      p open
   196                                                                         [exEnd]
   196 									[exEnd]
   197 
   197 
   198 
   198 
   199   with a model (see in the inspector, how the index-holders value changes)
   199   with a model (see in the inspector, how the index-holders value changes)
   200   the defaults are setup to allow a SelectionInList directly as model:
   200   the defaults are setup to allow a SelectionInList directly as model:
   201                                                                         [exBegin]
   201 									[exBegin]
   202      |p model|
   202      |p model|
   203 
   203 
   204      model := SelectionInList with:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
   204      model := SelectionInList with:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
   205 
   205 
   206      p := ComboListView label:'healthy fruit'.
   206      p := ComboListView label:'healthy fruit'.
   207      p model:model.
   207      p model:model.
   208      p open.
   208      p open.
   209      model inspect
   209      model inspect
   210                                                                         [exEnd]
   210 									[exEnd]
   211 
   211 
   212   model provides selection; list is explicit:
   212   model provides selection; list is explicit:
   213                                                                 [exBegin]
   213 								[exBegin]
   214      |model top b|
   214      |model top b|
   215 
   215 
   216      model := 'foo' asValue.
   216      model := 'foo' asValue.
   217 
   217 
   218      top := StandardSystemView new.
   218      top := StandardSystemView new.
   225      b list:#('hello' 'world' 'this' 'is' 'st/x').
   225      b list:#('hello' 'world' 'this' 'is' 'st/x').
   226      b model:model.
   226      b model:model.
   227 
   227 
   228      top openModal.
   228      top openModal.
   229      Transcript showCR:('comboBox''s value: ' , model value).
   229      Transcript showCR:('comboBox''s value: ' , model value).
   230                                                                 [exEnd]
   230 								[exEnd]
   231 
   231 
   232 
   232 
   233     a comboListView and a SelectionInListView on the same model:
   233     a comboListView and a SelectionInListView on the same model:
   234                                                                         [exBegin]
   234 									[exBegin]
   235      |p slv model|
   235      |p slv model|
   236 
   236 
   237      model := SelectionInList with:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
   237      model := SelectionInList with:#('apples' 'bananas' 'grape' 'lemon' 'margaritas').
   238      model selection:'apples'.
   238      model selection:'apples'.
   239 
   239 
   240      p := ComboListView on:model.
   240      p := ComboListView on:model.
   241      p open.
   241      p open.
   242 
   242 
   243      slv := SelectionInListView on:model.
   243      slv := SelectionInListView on:model.
   244      slv open.
   244      slv open.
   245                                                                         [exEnd]
   245 									[exEnd]
   246 
   246 
   247 
   247 
   248     two comboListViews on the same model, different aspects:
   248     two comboListViews on the same model, different aspects:
   249                                                                         [exBegin]
   249 									[exBegin]
   250      |top panel p model|
   250      |top panel p model|
   251 
   251 
   252      model := Plug new.
   252      model := Plug new.
   253      model respondTo:#eat: with:[:val | Transcript showCR:'eat: ' , val].
   253      model respondTo:#eat: with:[:val | Transcript showCR:'eat: ' , val].
   254      model respondTo:#drink: with:[:val | Transcript showCR:'drink: ' , val].
   254      model respondTo:#drink: with:[:val | Transcript showCR:'drink: ' , val].
   267      p := ComboListView label:'drinks'.
   267      p := ComboListView label:'drinks'.
   268      p model:model; listMessage:#drinks; aspect:nil; change:#drink:.
   268      p model:model; listMessage:#drinks; aspect:nil; change:#drink:.
   269      panel add:p.
   269      panel add:p.
   270 
   270 
   271      top open
   271      top open
   272                                                                         [exEnd]
   272 									[exEnd]
   273 
   273 
   274 
   274 
   275 
   275 
   276 
   276 
   277     with separate list- and indexHolders:
   277     with separate list- and indexHolders:
   278                                                                         [exBegin]
   278 									[exBegin]
   279      |p selectionHolder listHolder|
   279      |p selectionHolder listHolder|
   280 
   280 
   281      listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
   281      listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
   282      selectionHolder := 'apples' asValue.
   282      selectionHolder := 'apples' asValue.
   283 
   283 
   284      p := ComboListView label:'healthy fruit'.
   284      p := ComboListView label:'healthy fruit'.
   285      p listHolder:listHolder.
   285      p listHolder:listHolder.
   286      p model:selectionHolder.
   286      p model:selectionHolder.
   287      p open.
   287      p open.
   288      selectionHolder inspect
   288      selectionHolder inspect
   289                                                                         [exEnd]
   289 									[exEnd]
   290 
   290 
   291     using different values:
   291     using different values:
   292                                                                         [exBegin]
   292 									[exBegin]
   293      |p selectionHolder listHolder values|
   293      |p selectionHolder listHolder values|
   294 
   294 
   295      listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
   295      listHolder := #('apples' 'bananas' 'grape' 'lemon' 'margaritas') asValue.
   296      values := #(apples bananas grape lemon alcohol).
   296      values := #(apples bananas grape lemon alcohol).
   297 
   297 
   301      p listHolder:listHolder.
   301      p listHolder:listHolder.
   302      p model:selectionHolder.
   302      p model:selectionHolder.
   303      p values:values.
   303      p values:values.
   304      p open.
   304      p open.
   305      selectionHolder inspect
   305      selectionHolder inspect
   306                                                                         [exEnd]
   306 									[exEnd]
   307 
   307 
   308 
   308 
   309   in a dialog:
   309   in a dialog:
   310                                                                 [exBegin]
   310 								[exBegin]
   311      |model1 model2 dialog b|
   311      |model1 model2 dialog b|
   312 
   312 
   313      model1 := 'foo' asValue.
   313      model1 := 'foo' asValue.
   314      model2 := 'bar' asValue.
   314      model2 := 'bar' asValue.
   315 
   315 
   329 
   329 
   330      dialog open.
   330      dialog open.
   331 
   331 
   332      Transcript showCR:('1st comboBox''s value: ' , model1 value).
   332      Transcript showCR:('1st comboBox''s value: ' , model1 value).
   333      Transcript showCR:('2nd comboBox''s value: ' , model2 value).
   333      Transcript showCR:('2nd comboBox''s value: ' , model2 value).
   334                                                                 [exEnd]
   334 								[exEnd]
   335 "
   335 "
   336 ! !
   336 ! !
   337 
   337 
   338 !ComboListView class methodsFor:'defaults'!
   338 !ComboListView class methodsFor:'defaults'!
   339 
   339 
   361 useIndex:aBoolean
   361 useIndex:aBoolean
   362     "specify, if the selected components value or its index in the
   362     "specify, if the selected components value or its index in the
   363      list should be sent to the model. The default is its value."
   363      list should be sent to the model. The default is its value."
   364 
   364 
   365     useIndex := aBoolean.
   365     useIndex := aBoolean.
       
   366     "/ change the aspetMessage - but only if it has not yet been
       
   367     "/ changed explicitly
       
   368     useIndex ifTrue:[
       
   369 	aspectMsg == #selection ifTrue:[
       
   370 	    aspectMsg := #selectionIndex
       
   371 	] 
       
   372     ] ifFalse:[
       
   373 	aspectMsg == #selectionIndex ifTrue:[
       
   374 	    aspectMsg := #selection
       
   375 	]
       
   376     ].
   366 
   377 
   367     "Created: 26.7.1996 / 17:44:18 / cg"
   378     "Created: 26.7.1996 / 17:44:18 / cg"
       
   379     "Modified: / 24.1.1998 / 19:06:41 / cg"
   368 !
   380 !
   369 
   381 
   370 values:aCollection
   382 values:aCollection
   371     "specify, which values are to be stuffed into the model or
   383     "specify, which values are to be stuffed into the model or
   372      passed via the actionBlock."
   384      passed via the actionBlock."
   394      or directly"
   406      or directly"
   395 
   407 
   396     |m|
   408     |m|
   397 
   409 
   398     (m := field model) notNil ifTrue:[
   410     (m := field model) notNil ifTrue:[
   399         ^ m value
   411 	^ m value
   400     ] ifFalse:[
   412     ] ifFalse:[
   401         ^ field label
   413 	^ field label
   402     ]
   414     ]
   403 !
   415 !
   404 
   416 
   405 contents:something
   417 contents:something
   406     "set the current value - either in the fields model
   418     "set the current value - either in the fields model
   407      or directly"
   419      or directly"
   408 
   420 
   409     |m|
   421     |m|
   410 
   422 
   411     (m := field model) notNil ifTrue:[
   423     (m := field model) notNil ifTrue:[
   412         m value:something
   424 	m value:something
   413     ] ifFalse:[
   425     ] ifFalse:[
   414         field label:something
   426 	field label:something
   415     ]
   427     ]
   416 
   428 
   417     "Created: 15.7.1996 / 13:16:49 / cg"
   429     "Created: 15.7.1996 / 13:16:49 / cg"
   418     "Modified: 5.1.1997 / 00:05:04 / cg"
   430     "Modified: 5.1.1997 / 00:05:04 / cg"
   419 !
   431 !
   458 
   470 
   459 getValueFromModel
   471 getValueFromModel
   460     |selection idx aspect|
   472     |selection idx aspect|
   461 
   473 
   462     (model notNil and:[aspectMsg notNil]) ifTrue:[
   474     (model notNil and:[aspectMsg notNil]) ifTrue:[
   463         "/ kludge - try #value if aspect is the default and
   475 	"/ kludge - try #value if aspect is the default and
   464         "/ not understood by the model
   476 	"/ not understood by the model
   465         "/ this allows a valueHolder to be used, even
   477 	"/ this allows a valueHolder to be used, even
   466         "/ if the aspectMessage was not setup correctly.
   478 	"/ if the aspectMessage was not setup correctly.
   467 
   479 
   468         aspect := aspectMsg.
   480 	aspect := aspectMsg.
   469         aspect == self class defaultAspectMessage ifTrue:[
   481 	aspect == self class defaultAspectMessage ifTrue:[
   470             (model respondsTo:aspect) ifFalse:[
   482 	    (model respondsTo:aspect) ifFalse:[
   471                 aspect := #value
   483 		aspect := #value
   472             ]
   484 	    ]
   473         ].
   485 	].
   474 
   486 
   475         selection := model perform:aspect.
   487 	selection := model perform:aspect.
   476         selection notNil ifTrue:[
   488 	selection notNil ifTrue:[
   477             values notNil ifTrue:[
   489 	    values notNil ifTrue:[
   478                 idx := values indexOf:selection
   490 		idx := values indexOf:selection
   479             ] ifFalse:[
   491 	    ] ifFalse:[
   480                 useIndex ifTrue:[
   492 		useIndex ifTrue:[
   481                     idx := selection
   493 		    idx := selection
   482                 ] ifFalse:[
   494 		] ifFalse:[
   483                     self contents:selection.
   495 		    self contents:selection.
   484                     ^ self.
   496 		    ^ self.
   485                 ]
   497 		]
   486             ].
   498 	    ].
   487 
   499 
   488             self contents:(list at:idx ifAbsent:nil)
   500 	    self contents:(list at:idx ifAbsent:nil)
   489         ]
   501 	]
   490     ].
   502     ].
   491 
   503 
   492     "Created: 15.7.1996 / 12:28:53 / cg"
   504     "Created: 15.7.1996 / 12:28:53 / cg"
   493     "Modified: 28.2.1997 / 13:41:02 / cg"
   505     "Modified: 28.2.1997 / 13:41:02 / cg"
   494 ! !
   506 ! !
   497 
   509 
   498 specClass
   510 specClass
   499     "XXX no longer needed (inherited default works here)"
   511     "XXX no longer needed (inherited default works here)"
   500 
   512 
   501     self class == ComboListView ifTrue:[
   513     self class == ComboListView ifTrue:[
   502         ^ ComboListSpec
   514 	^ ComboListSpec
   503     ].
   515     ].
   504     ^ super specClass
   516     ^ super specClass
   505 
   517 
   506     "Modified: / 31.10.1997 / 19:49:34 / cg"
   518     "Modified: / 31.10.1997 / 19:49:34 / cg"
   507 ! !
   519 ! !
   512     "sent from the popped menu, when an item was selected"
   524     "sent from the popped menu, when an item was selected"
   513 
   525 
   514     |label value chg|
   526     |label value chg|
   515 
   527 
   516     values isNil ifTrue:[
   528     values isNil ifTrue:[
   517         value := anIndex.
   529 	value := anIndex.
   518         useIndex ifFalse:[
   530 	useIndex ifFalse:[
   519             value := list at:anIndex.
   531 	    value := list at:anIndex.
   520         ]
   532 	]
   521     ] ifFalse:[
   533     ] ifFalse:[
   522         value := values at:anIndex
   534 	value := values at:anIndex
   523     ].
   535     ].
   524 
   536 
   525     label := list at:anIndex.
   537     label := list at:anIndex.
   526 
   538 
   527     field label:label.
   539     field label:label.
   529     "
   541     "
   530      ST-80 style model notification ...
   542      ST-80 style model notification ...
   531      this updates the model (typically, a ValueHolder)
   543      this updates the model (typically, a ValueHolder)
   532     "
   544     "
   533     (model notNil and:[changeMsg notNil]) ifTrue:[
   545     (model notNil and:[changeMsg notNil]) ifTrue:[
   534         "/ kludge - try #value: if changeMsg is the default and
   546 	"/ kludge - try #value: if changeMsg is the default and
   535         "/ not understood by the model
   547 	"/ not understood by the model
   536         "/ this allows a valueHolder to be used, even
   548 	"/ this allows a valueHolder to be used, even
   537         "/ if the aspectMessage was not setup correctly.
   549 	"/ if the aspectMessage was not setup correctly.
   538 
   550 
   539         chg := changeMsg.
   551 	chg := changeMsg.
   540         chg == self class defaultChangeMessage ifTrue:[
   552 	chg == self class defaultChangeMessage ifTrue:[
   541             (model respondsTo:chg) ifFalse:[
   553 	    (model respondsTo:chg) ifFalse:[
   542                 chg := #value:
   554 		chg := #value:
   543             ]
   555 	    ]
   544         ].
   556 	].
   545 
   557 
   546         self sendChangeMessage:chg with:value
   558 	self sendChangeMessage:chg with:value
   547     ].
   559     ].
   548     pullDownButton turnOff.
   560     pullDownButton turnOff.
   549 
   561 
   550     "
   562     "
   551      ST/X style actionBlock evaluation ...
   563      ST/X style actionBlock evaluation ...
   552     "
   564     "
   553     action notNil ifTrue:[
   565     action notNil ifTrue:[
   554         action value:value
   566 	action value:value
   555     ].
   567     ].
   556 
   568 
   557     "Created: 27.2.1997 / 15:18:44 / cg"
   569     "Created: 27.2.1997 / 15:18:44 / cg"
   558     "Modified: 28.2.1997 / 13:50:17 / cg"
   570     "Modified: 28.2.1997 / 13:50:17 / cg"
   559 ! !
   571 ! !
   560 
   572 
   561 !ComboListView class methodsFor:'documentation'!
   573 !ComboListView class methodsFor:'documentation'!
   562 
   574 
   563 version
   575 version
   564     ^ '$Header: /cvs/stx/stx/libwidg2/ComboListView.st,v 1.25 1997-11-02 17:26:31 cg Exp $'
   576     ^ '$Header: /cvs/stx/stx/libwidg2/ComboListView.st,v 1.26 1998-01-25 14:14:42 cg Exp $'
   565 ! !
   577 ! !