PopUpMenu.st
changeset 59 450ce95a72a4
parent 38 4b9b70b2cc87
child 63 f4eaf04d1eaf
--- a/PopUpMenu.st	Tue Aug 30 00:54:47 1994 +0200
+++ b/PopUpMenu.st	Mon Oct 10 04:03:47 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -12,7 +12,7 @@
 
 PopUpView subclass:#PopUpMenu
        instanceVariableNames:'menuView lastSelection memorize hideOnLeave
-                              actionLabels actionLines actionValues'
+			      actionLabels actionLines actionValues'
        classVariableNames:''
        poolDictionaries:''
        category:'Views-Menus'
@@ -20,9 +20,9 @@
 
 PopUpMenu comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/PopUpMenu.st,v 1.7 1994-08-07 13:23:09 claus Exp $
+$Header: /cvs/stx/stx/libwidg/PopUpMenu.st,v 1.8 1994-10-10 03:02:35 claus Exp $
 '!
 
 !PopUpMenu class methodsFor:'documentation'!
@@ -30,7 +30,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -43,7 +43,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/PopUpMenu.st,v 1.7 1994-08-07 13:23:09 claus Exp $
+$Header: /cvs/stx/stx/libwidg/PopUpMenu.st,v 1.8 1994-10-10 03:02:35 claus Exp $
 "
 !
 
@@ -59,71 +59,71 @@
 
     Examples:
 
-        |p|
-        p := PopUpMenu
-                labels:#('foo'
-                         'bar'
-                         'baz')
-                selectors:#(
-                            #foo
-                            #bar
-                            #baz)
-                receiver:nil.
-        p showAtPointer
+	|p|
+	p := PopUpMenu
+		labels:#('foo'
+			 'bar'
+			 'baz')
+		selectors:#(
+			    #foo
+			    #bar
+			    #baz)
+		receiver:nil.
+	p showAtPointer
 
 
     sometimes, you want to specify both selectors and some arguments
     to be sent; this is done by:
 
-        |p|
-        p := PopUpMenu
-                labels:#('foo' 'bar' 'baz')
-                selectors:#(#foo: #bar: #foo:)
-                args:#(1 2 3)
-                receiver:nil.
-        p showAtPointer
+	|p|
+	p := PopUpMenu
+		labels:#('foo' 'bar' 'baz')
+		selectors:#(#foo: #bar: #foo:)
+		args:#(1 2 3)
+		receiver:nil.
+	p showAtPointer
 
     or, the same selector but different arguments:
 
-        |p|
-        p := PopUpMenu
-                labels:#('foo' 'bar' 'baz')
-                selectors:#foo:
-                args:#(1 2 3)
-                receiver:nil.
-        p showAtPointer
+	|p|
+	p := PopUpMenu
+		labels:#('foo' 'bar' 'baz')
+		selectors:#foo:
+		args:#(1 2 3)
+		receiver:nil.
+	p showAtPointer
 
     Normally, you do not show the menu explicitely, but install
     it as a middleButtonMenu of some view. (Views button-event handler
     will show it when the button is pressed ...)
 
-        |v m|
+	|v m|
 
-        v := View new.
-        m := PopUpMenu
-                labels:#('lower'
-                         'raise'
-                         '-'
-                         'destroy')
-                selectors:#(#lower #raise nil #destroy)
-                receiver:v.
-        v middleButtonMenu:m.
-        v open
+	v := View new.
+	m := PopUpMenu
+		labels:#('lower'
+			 'raise'
+			 '-'
+			 'destroy')
+		selectors:#(#lower #raise nil #destroy)
+		receiver:v.
+	v middleButtonMenu:m.
+	v open
 
     It is also possible, to add check-mark entries, with an entry string
     starting with the special sequence '\c' (for check-mark). The value
     passed will be the truth-state of the check-mark.
 
-        |m v|
+	|m v|
 
-        v := View new.
-        m := PopUpMenu
-                labels:#('\c foo'
-                         '\c bar')
-                selectors:#(#value: #value:)
-                receiver:[:v | Transcript show:'arg: '; showCr:v].
-        v middleButtonMenu:m.
-        v open
+	v := View new.
+	m := PopUpMenu
+		labels:#('\c foo'
+			 '\c bar')
+		selectors:#(#value: #value:)
+		receiver:[:v | Transcript show:'arg: '; showCr:v].
+	v middleButtonMenu:m.
+	v open
 
 
     Finally, you can wrap other views into a popup menu (for example,
@@ -133,32 +133,32 @@
     Currently there is only one class in the system, which can be used
     this way (PatternMenu in the DrawTool demo):
 
-        |v p|
+	|v p|
 
-        v := View new.
-        p := PatternMenu new.
-        p patterns:(Array with:Color red
-                          with:Color green
-                          with:Color blue).
-        v middleButtonMenu:(PopUpMenu forMenu:p).
-        v open
+	v := View new.
+	p := PatternMenu new.
+	p patterns:(Array with:Color red
+			  with:Color green
+			  with:Color blue).
+	v middleButtonMenu:(PopUpMenu forMenu:p).
+	v open
 
     or try:
 
-        |v p|
+	|v p|
 
-        v := View new.
-        p := PatternMenu new.
-        p patterns:(Array with:Color red
-                          with:Color green
-                          with:Color blue).
-        p selectors:#value:.
-        p receiver:[:val | v viewBackground:val. v clear].
-        p args:(Array with:Color red
-                      with:Color green
-                      with:Color blue).
-        v middleButtonMenu:(PopUpMenu forMenu:p).
-        v open
+	v := View new.
+	p := PatternMenu new.
+	p patterns:(Array with:Color red
+			  with:Color green
+			  with:Color blue).
+	p selectors:#value:.
+	p receiver:[:val | v viewBackground:val. v clear].
+	p args:(Array with:Color red
+		      with:Color green
+		      with:Color blue).
+	v middleButtonMenu:(PopUpMenu forMenu:p).
+	v open
 
         
     ST-80 style:
@@ -167,47 +167,47 @@
     also possible, to use Smalltalk-80 style menus (which return some value
     from their startup method):
 
-        |m selection|
+	|m selection|
 
-        m := PopUpMenu
-                labels:#('one' 'two' 'three').
-        selection := m startUp.
-        Transcript show:'the selection was: '; showCr:selection
+	m := PopUpMenu
+		labels:#('one' 'two' 'three').
+	selection := m startUp.
+	Transcript show:'the selection was: '; showCr:selection
 
     startUp will return the entries index, or 0 if there was no selection.
     You can also specify an array of values to be returned instead of the
     index:
 
-        |m selection|
+	|m selection|
 
-        m := PopUpMenu
-                labels:#('one' 'two' 'three')
-                values:#(10 20 30).
-        selection := m startUp.
-        Transcript show:'the value was: '; showCr:selection
+	m := PopUpMenu
+		labels:#('one' 'two' 'three')
+		values:#(10 20 30).
+	selection := m startUp.
+	Transcript show:'the value was: '; showCr:selection
 
     In ST/X style menus, separating lines between entries are created
     by a '-'-string as its label text (and corresponding nil-entries in the
     selectors- and args-arrays).
     In ST-80, you have to pass the indices of the lines in an extra array:
 
-        |m selection|
+	|m selection|
 
-        m := PopUpMenu
-                labels:#('one' 'two' 'three' 'four' 'five')
-                lines:#(2 4).
-        selection := m startUp.
-        Transcript show:'the value was: '; showCr:selection
+	m := PopUpMenu
+		labels:#('one' 'two' 'three' 'four' 'five')
+		lines:#(2 4).
+	selection := m startUp.
+	Transcript show:'the value was: '; showCr:selection
 
     or:
-        |m selection|
+	|m selection|
 
-        m := PopUpMenu
-                labels:#('one' 'two' 'three')
-                lines:#(2)
-                values:#(10 20 30).
-        selection := m startUp.
-        Transcript show:'the value was: '; showCr:selection
+	m := PopUpMenu
+		labels:#('one' 'two' 'three')
+		lines:#(2)
+		values:#(10 20 30).
+	selection := m startUp.
+	Transcript show:'the value was: '; showCr:selection
 
     Use whichever interface you prefer.
 "
@@ -220,7 +220,7 @@
      the popup-menu is to be created) is located."
 
     aView isNil ifTrue:[
-        ^ self on:Display
+	^ self on:Display
     ].
     ^ self on:(aView device)
 !
@@ -248,19 +248,19 @@
 
     newMenu := self onSameDeviceAs:aView. 
     newMenu menu:(MenuView
-                        labels:labels
-                        selectors:selectors
-                        receiver:anObject
-                        in:newMenu).
+			labels:labels
+			selectors:selectors
+			receiver:anObject
+			in:newMenu).
     ^ newMenu
 !
 
 labels:labels selectors:selectors args:args receiver:anObject
     ^ self labels:labels 
-        selectors:selectors 
-             args:args 
-         receiver:anObject 
-              for:nil
+	selectors:selectors 
+	     args:args 
+	 receiver:anObject 
+	      for:nil
 !
 
 labels:labels selectors:selectors args:args receiver:anObject for:aView
@@ -268,20 +268,20 @@
 
     newMenu := self onSameDeviceAs:aView. 
     newMenu menu:(MenuView
-                    labels:labels
-                    selectors:selectors
-                    args:args
-                    receiver:anObject
-                    in:newMenu).
+		    labels:labels
+		    selectors:selectors
+		    args:args
+		    receiver:anObject
+		    in:newMenu).
     ^ newMenu
 !
 
 labels:labels selector:aSelector args:args receiver:anObject
     ^ self labels:labels 
-         selector:aSelector 
-             args:args 
-         receiver:anObject 
-              for:nil
+	 selector:aSelector 
+	     args:args 
+	 receiver:anObject 
+	      for:nil
 !
 
 labels:labels selectors:selectors receiver:anObject
@@ -293,11 +293,11 @@
 
     newMenu := self onSameDeviceAs:aView. 
     newMenu menu:(MenuView
-                    labels:labels
-                    selector:aSelector
-                    args:args
-                    receiver:anObject
-                    in:newMenu).
+		    labels:labels
+		    selector:aSelector
+		    args:args
+		    receiver:anObject
+		    in:newMenu).
     ^ newMenu
 ! !
 
@@ -331,17 +331,21 @@
 
 initialize
     super initialize.
+
+    "dont need any fancy colors"
+"/    viewBackground := White on:device.
+
     memorize := true.
     hideOnLeave := false.
     style == #iris ifTrue:[
-        borderWidth := 1
+	borderWidth := 1
     ].
     (style == #st80) ifTrue:[
-        viewBackground := White.
-        borderWidth := 1.
-        level := 0.
-        margin := 0.
-        shadowView := nil
+"/        viewBackground := White.
+	borderWidth := 1.
+	level := 0.
+	margin := 0.
+	shadowView := nil
     ].
 !
 
@@ -364,7 +368,7 @@
     newWidth := menuView width + extra.
     newHeight := menuView height + extra.
     ((newWidth ~~ width) or:[newHeight ~~ height]) ifTrue:[
-        self extent:(menuView width + extra) @ (menuView height + extra)
+	self extent:(menuView width + extra) @ (menuView height + extra)
     ].
     super fixSize
 !
@@ -406,6 +410,17 @@
     menuView superMenu:aMenu
 ! !
 
+!PopUpMenu methodsFor:'menuview messages'!
+
+doesNotUnderstand:aMessage
+    "forward all menu-view messages"
+
+    (menuView respondsTo:(aMessage selector)) ifTrue:[
+	^ aMessage sendTo:menuView
+    ].
+    ^ super doesNotUnderstand:aMessage
+! !
+
 !PopUpMenu methodsFor:'accessing'!
 
 viewBackground:aColor
@@ -423,22 +438,6 @@
     hideOnLeave := aBoolean
 !
 
-enable:anEntry
-    "enable a menu entry"
-
-    menuView enable:anEntry
-!
-
-disable:anEntry
-    "disable a menu entry"
-
-    menuView disable:anEntry
-!
-
-receiver:anObject
-    menuView receiver:anObject
-!
-
 font:aFont
     menuView font:aFont
 !
@@ -447,7 +446,7 @@
     "return the list of labels"
 
     actionLabels notNil ifTrue:[
-        ^ actionLabels asText
+	^ actionLabels asText
     ].
     ^ menuView list
 !
@@ -464,42 +463,6 @@
     menuView remove:indexOrName
 !
 
-addLabel:aLabel selector:aSelector
-    "add a new menu entry to the end"
-
-    menuView addLabel:aLabel selector:aSelector
-!
-
-addLabel:aLabel selector:aSelector arg:anArg
-    "add a new menu entry to the end"
-
-    menuView addLabel:aLabel selector:aSelector arg:anArg
-!
-
-addLabel:aLabel selector:aSelector after:indexOrName
-    "add a new menu entry somewhere"
-
-    menuView addLabel:aLabel selector:aSelector after:indexOrName
-!
-
-labelAt:index put:aString
-    "change a menu entry"
-
-    menuView labelAt:index put:aString
-!
-
-selectorAt:index put:aSymbol
-    "change a selector entry"
-
-    menuView selectorAt:index put:aSymbol
-!
-
-subMenuAt:indexOrName
-    "return a submenu - or nil if there is none"
-
-    ^ menuView subMenuAt:indexOrName
-!
-
 subMenuAt:indexOrName put:aMenu
     "define a submenu to be shown for entry indexOrName"
 
@@ -513,35 +476,23 @@
     "|v m|
      v := View new.
      m := PopUpMenu labels:#('1' '2' '3')
-                 selectors:#(one two nil)
-                  receiver:v
-                       for:nil.
+		 selectors:#(one two nil)
+		  receiver:v
+		       for:nil.
      m subMenuAt:3 put:(PopUpMenu
-                             labels:#('a' 'b' 'c')
-                          selectors:#(a b c)
-                           receiver:v
-                                for:nil).
+			     labels:#('a' 'b' 'c')
+			  selectors:#(a b c)
+			   receiver:v
+				for:nil).
      v middleButtonMenu:m.
      v realize"
 !
 
-checkToggleAt:index
-    "return a checkToggles state"
-
-    ^ menuView checkToggleAt:index
-!
-
-checkToggleAt:index put:aBoolean
-    "set/clear a checkToggle"
-
-    ^ menuView checkToggleAt:index put:aBoolean
-!
-
 numberOfItems
     "return the number of items in the menu"
 
     actionLabels notNil ifTrue:[
-        ^ actionLabels asText size
+	^ actionLabels asText size
     ].
     ^ menuView list size
 !
@@ -576,29 +527,29 @@
     offs := 1.
     dstOffs := 1.
     1 to:lineArray size do:[:lineIndex |
-        linePos := lineArray at:lineIndex.
-        [offs <= linePos] whileTrue:[
-            convertedLabels at:dstOffs put:(labelArray at:offs).
-            argArray at:dstOffs put:offs.
-            offs := offs + 1.
-            dstOffs := dstOffs + 1
-        ].
-        convertedLabels at:dstOffs put:'-'.
-        argArray at:dstOffs put:nil.
-        dstOffs := dstOffs + 1
+	linePos := lineArray at:lineIndex.
+	[offs <= linePos] whileTrue:[
+	    convertedLabels at:dstOffs put:(labelArray at:offs).
+	    argArray at:dstOffs put:offs.
+	    offs := offs + 1.
+	    dstOffs := dstOffs + 1
+	].
+	convertedLabels at:dstOffs put:'-'.
+	argArray at:dstOffs put:nil.
+	dstOffs := dstOffs + 1
     ].
     [offs <= labelArray size] whileTrue:[
-        convertedLabels at:dstOffs put:(labelArray at:offs).
-        argArray at:dstOffs put:offs.
-        offs := offs + 1.
-        dstOffs := dstOffs + 1
+	convertedLabels at:dstOffs put:(labelArray at:offs).
+	argArray at:dstOffs put:offs.
+	offs := offs + 1.
+	dstOffs := dstOffs + 1
     ].
     self menu:(MenuView
-                        labels:convertedLabels
-                      selector:nil
-                          args:argArray
-                      receiver:nil 
-                            in:self)
+			labels:convertedLabels
+		      selector:nil
+			  args:argArray
+		      receiver:nil 
+			    in:self)
 ! !
 
 !PopUpMenu methodsFor:'activation'!
@@ -607,7 +558,7 @@
     "realize the menu at aPoint"
 
     aBoolean ifTrue:[
-        self fixSize.
+	self fixSize.
     ].
     self origin:aPoint.
     self makeFullyVisible.
@@ -638,8 +589,8 @@
 
     menuView hideSubmenu.
     windowGroup notNil ifTrue:[
-        windowGroup removeView:self.
-        windowGroup := nil.
+	windowGroup removeView:self.
+	windowGroup := nil.
     ].
     self unrealize.
 !
@@ -661,22 +612,22 @@
      This is the ST-80 way of launching a menu."
 
     menuView action:[:selected |
-        |actionIndex value|
+	|actionIndex value|
 
-        menuView args isNil ifTrue:[
-            menuView selectors isNil ifTrue:[
-                ^ 0
-            ].
-            ^ menuView receiver perform:(menuView selectors at:selected)
-        ].
-        actionIndex := menuView args at:selected.
-        actionIndex isNil ifTrue:[^ 0].
-        actionValues isNil ifTrue:[^ actionIndex].
-        value := actionValues at:actionIndex.
-        (value isKindOf:PopUpMenu) ifTrue:[
-            ^ value startUp
-        ].
-        ^ value
+	menuView args isNil ifTrue:[
+	    menuView selectors isNil ifTrue:[
+		^ 0
+	    ].
+	    ^ menuView receiver perform:(menuView selectors at:selected)
+	].
+	actionIndex := menuView args at:selected.
+	actionIndex isNil ifTrue:[^ 0].
+	actionValues isNil ifTrue:[^ actionIndex].
+	value := actionValues at:actionIndex.
+	(value isKindOf:PopUpMenu) ifTrue:[
+	    ^ value startUp
+	].
+	^ value
     ].
     self showAtPointer.
     ^ 0
@@ -684,7 +635,7 @@
     "
      Transcript showCr:(PopUpMenu labels:#('foo' 'bar' 'baz')) startUp
      Transcript showCr:(PopUpMenu labels:#('foo' 'bar' 'baz')
-                                  values:#(foo bar baz)) startUp
+				  values:#(foo bar baz)) startUp
     "
 ! !
 
@@ -694,26 +645,26 @@
     |p|
 
     ((x >= 0) and:[x < width]) ifTrue:[
-        ((y >= 0) and:[y < height]) ifTrue:[
-            menuView buttonMotion:button x:x y:y.
-            ^ self
-        ]
+	((y >= 0) and:[y < height]) ifTrue:[
+	    menuView buttonMotion:button x:x y:y.
+	    ^ self
+	]
     ].
 
     "outside of myself"
     menuView superMenu notNil ifTrue:[
-        p := device translatePoint:(x @ y)
-                              from:drawableId
-                                to:(menuView superMenu id).
-        menuView superMenu buttonMotion:button x:p x y:p y
+	p := device translatePoint:(x @ y)
+			      from:drawableId
+				to:(menuView superMenu id).
+	menuView superMenu buttonMotion:button x:p x y:p y
     ].
 
     menuView subMenuShown isNil ifTrue:[
-        menuView pointerLeave:button.
+	menuView pointerLeave:button.
     ].
 
     hideOnLeave ifTrue:[
-        self hide
+	self hide
     ].
 
 "/    menuView superMenu notNil ifTrue:[
@@ -743,7 +694,7 @@
     menuView buttonRelease:button x:x y:y.
 "
     menuView superMenu notNil ifTrue:[
-        menuView superMenu submenuTriggered 
+	menuView superMenu submenuTriggered 
     ].
     menuView buttonRelease:button x:x y:y.
 ! !