MenuPanel.st
changeset 3144 772766a2e99e
parent 3143 645efaba917a
child 3147 b7c2db746f84
--- a/MenuPanel.st	Wed Nov 08 16:31:47 2006 +0100
+++ b/MenuPanel.st	Wed Nov 08 18:32:55 2006 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-	      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,48 +12,48 @@
 "{ Package: 'stx:libwidg2' }"
 
 View subclass:#MenuPanel
-	instanceVariableNames:'adornment shadowView mapTime mustRearrange superMenu
-		shortKeyInset selection items groupSizes receiver enabled
-		lastActiveMenu enteredItem prevFocusView previousPointerGrab
-		previousKeyboardGrab relativeGrabOrigin hasImplicitGrap
-		scrollActivity rightArrowShadow rightArrow fgColor verticalLayout
-		showSeparatingLines showGroupDivider implicitGrabView
-		lastPointerView openDelayedMenuBlock preferredWidth application
-		originator centerItems hideOnRelease defaultHideOnRelease
-		buttonInsetX buttonInsetY itemSpace activeBackgroundColor
-		stringOffsetX'
-	classVariableNames:'InitialSelectionQuerySignal Images LigthenedImages
-		DefaultForegroundColor DefaultBackgroundColor IconIndicationOn
-		IconIndicationOff IconRadioOn IconRadioOff
-		IconDisabledIndicationOn IconDisabledIndicationOff
-		IconDisabledRadioOn IconDisabledRadioOff'
-	poolDictionaries:''
-	category:'Views-Menus'
+        instanceVariableNames:'adornment shadowView mapTime mustRearrange superMenu
+                shortKeyInset selection items groupSizes receiver enabled
+                lastActiveMenu enteredItem prevFocusView previousPointerGrab
+                previousKeyboardGrab relativeGrabOrigin hasImplicitGrap
+                scrollActivity rightArrowShadow rightArrow fgColor verticalLayout
+                showSeparatingLines showGroupDivider implicitGrabView
+                lastPointerView openDelayedMenuBlock preferredWidth application
+                originator centerItems hideOnRelease defaultHideOnRelease
+                buttonInsetX buttonInsetY itemSpace activeBackgroundColor
+                stringOffsetX'
+        classVariableNames:'InitialSelectionQuerySignal Images LigthenedImages
+                DefaultForegroundColor DefaultBackgroundColor IconIndicationOn
+                IconIndicationOff IconRadioOn IconRadioOff
+                IconDisabledIndicationOn IconDisabledIndicationOff
+                IconDisabledRadioOn IconDisabledRadioOff'
+        poolDictionaries:''
+        category:'Views-Menus'
 !
 
 Object subclass:#Item
-	instanceVariableNames:'menuItem layout menuPanel subMenu displayLabel displayLabelExtent
-		disabledDisplayLabel enableChannel label activeHelpText
-		flyByHelpText isVisible indication choice accessCharacter'
-	classVariableNames:'HorizontalInset VerticalInset HorizontalButtonInset
-		VerticalButtonInset LabelRightOffset VerticalPopUpInset'
-	poolDictionaries:''
-	privateIn:MenuPanel
+        instanceVariableNames:'menuItem layout menuPanel subMenu displayLabel displayLabelExtent
+                disabledDisplayLabel enableChannel label activeHelpText
+                flyByHelpText isVisible indication choice accessCharacter'
+        classVariableNames:'HorizontalInset VerticalInset HorizontalButtonInset
+                VerticalButtonInset LabelRightOffset VerticalPopUpInset'
+        poolDictionaries:''
+        privateIn:MenuPanel
 !
 
 Object subclass:#Adornment
-	instanceVariableNames:'indication accessCharacterPosition shortcutKey argument argument2
-		choice choiceValue'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:MenuPanel::Item
+        instanceVariableNames:'indication accessCharacterPosition shortcutKey argument argument2
+                choice choiceValue'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:MenuPanel::Item
 !
 
 Object subclass:#ScrollActivity
-	instanceVariableNames:'semaLock activeMenu scrollTask direction icons'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:MenuPanel
+        instanceVariableNames:'semaLock activeMenu scrollTask direction icons'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:MenuPanel
 !
 
 !MenuPanel class methodsFor:'documentation'!
@@ -61,7 +61,7 @@
 copyright
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-	      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
@@ -104,7 +104,7 @@
 
 "
     start as PullDownMenu
-										[exBegin]
+                                                                                [exBegin]
     |top subView mview desc s1 s2 s3 img lbs labels|
 
     top := StandardSystemView new.
@@ -145,9 +145,9 @@
     mview subMenuAt:2 put:(MenuPanel labels:labels).
     top extent:(mview preferredExtent).
     top open.
-										[exEnd]
-
-										[exBegin]
+                                                                                [exEnd]
+
+                                                                                [exBegin]
     |top menu view item|
 
     top  := StandardSystemView extent:240@100.
@@ -171,11 +171,11 @@
 
     menu origin:0@0 corner:1.0@30.
     top open.
-										[exEnd]
+                                                                                [exEnd]
 
 
     start as PopUpMenu
-										[exBegin]
+                                                                                [exBegin]
     |subView mview desc s1 s2 s3 img lbs labels|
 
     mview := MenuPanel new.
@@ -203,52 +203,52 @@
 
     mview subMenuAt:2 put:(MenuPanel labels:labels).
     mview startUp
-										[exEnd]
+                                                                                [exEnd]
 
 
     start from menu spec
-										[exBegin]
+                                                                                [exBegin]
     |menu|
 
     menu := MenuPanel menu:
-	#(#Menu #( #(#MenuItem 
-		    #label: 'File' 
-		    #submenu:
-		      #(#Menu #(#(#MenuItem #label: 'quit' #value:#quit )     
-				 (#MenuItem 
-				    #label: 'edit' 
-				    #submenu:
-				      #(#Menu #( #(#MenuItem #label: 'edit'  #value:#edit )     
-						 #(#MenuItem #label: 'close' #value:#close)     
-					       )
-					       nil
-					       nil
-				       )     
-				  )
-				 #(#MenuItem #label: 'help' #value:#help )     
-			       )
-			       nil
-			       nil
-		       )     
-		 ) 
-		#(#MenuItem #label: 'Inspect' #value:#inspectMenu ) 
-		#(#MenuItem #label: 'Bar' 
-			    #submenu:
-			       #(#Menu #( #(#MenuItem #label: 'bar 1' #value:#bar1 )     
-					  #(#MenuItem #label: 'bar 2' #value:#bar2 )     
-					)
-					nil
-					nil
-				)     
-		 ) 
-	      ) 
-	      #( 2 )
-	      nil
-	 ) decodeAsLiteralArray.  
+        #(#Menu #( #(#MenuItem 
+                    #label: 'File' 
+                    #submenu:
+                      #(#Menu #(#(#MenuItem #label: 'quit' #value:#quit )     
+                                 (#MenuItem 
+                                    #label: 'edit' 
+                                    #submenu:
+                                      #(#Menu #( #(#MenuItem #label: 'edit'  #value:#edit )     
+                                                 #(#MenuItem #label: 'close' #value:#close)     
+                                               )
+                                               nil
+                                               nil
+                                       )     
+                                  )
+                                 #(#MenuItem #label: 'help' #value:#help )     
+                               )
+                               nil
+                               nil
+                       )     
+                 ) 
+                #(#MenuItem #label: 'Inspect' #value:#inspectMenu ) 
+                #(#MenuItem #label: 'Bar' 
+                            #submenu:
+                               #(#Menu #( #(#MenuItem #label: 'bar 1' #value:#bar1 )     
+                                          #(#MenuItem #label: 'bar 2' #value:#bar2 )     
+                                        )
+                                        nil
+                                        nil
+                                )     
+                 ) 
+              ) 
+              #( 2 )
+              nil
+         ) decodeAsLiteralArray.  
 
     menu verticalLayout:false.
     Transcript showCR:(menu startUp).
-										[exEnd]
+                                                                                [exEnd]
 
 "
 
@@ -264,9 +264,9 @@
     |menu|
 
     aSpec notNil ifTrue:[
-	menu := Menu new.
-	menu receiver:aReceiver.
-	menu fromLiteralArrayEncoding:aSpec.
+        menu := Menu new.
+        menu receiver:aReceiver.
+        menu fromLiteralArrayEncoding:aSpec.
     ].
   ^ self menu:menu receiver:aReceiver
 !
@@ -303,8 +303,8 @@
     mview := self new.
 
     (aMenu notNil and:[aMenu receiver isNil]) ifTrue:[
-	"/ no receiver specified in the menu; thus set the receiver immediately
-	mview receiver:aReceiver
+        "/ no receiver specified in the menu; thus set the receiver immediately
+        mview receiver:aReceiver
     ].
 
     mview menu:aMenu.
@@ -314,7 +314,7 @@
 "/ thus we do not overwrite the receiver
 
     aReceiver notNil ifTrue:[
-	mview receiver:aReceiver
+        mview receiver:aReceiver
     ].
   ^ mview
 ! !
@@ -852,8 +852,10 @@
         masterGroup notNil ifTrue:[masterGroup processExposeEvents].
     ].
 
-    acceptAction := [   self accept:item index:itemIdx toggle:tgState receiver:recv.
-
+    acceptAction := [   
+                        |winGrp|
+
+                        self accept:item index:itemIdx toggle:tgState receiver:recv.
                         focusView notNil ifTrue:[
                             (winGrp := self windowGroup) notNil ifTrue:[
                                 self windowGroup focusView:focusView.
@@ -866,14 +868,16 @@
     and:[(winGrp := (masterGroup ? (self windowGroup))) notNil]])
     ifTrue:[
         winGrp withWaitCursorDo:acceptAction
-    ] ifFalse:[acceptAction value].
+    ] ifFalse:[
+        acceptAction value
+    ].
 
     self isPopUpView ifTrue:[
         self menuAdornmentAt:#item put:item.
     ].
     ^ item.
 
-    "Modified: / 15.11.2001 / 17:05:40 / cg"
+    "Modified: / 08-11-2006 / 17:14:06 / cg"
 !
 
 accept:anItem index:anIndex toggle:aState receiver:aReceiver
@@ -1863,8 +1867,8 @@
 
 level:anInt
     anInt ~~ level ifTrue:[
-	super level:anInt.
-	self mustRearrange
+        super level:anInt.
+        self mustRearrange
     ]
 
     "Modified: / 15.11.2001 / 17:42:07 / cg"
@@ -3579,12 +3583,12 @@
     relativeGrabOrigin := nil.
 
     superMenu notNil ifTrue:[
-	superMenu doGrab
+        superMenu doGrab
     ] ifFalse:[
-	hasImplicitGrap ~~ true ifTrue:[
-	    self grabMouseAndKeyboard.
-	    hasImplicitGrap := true
-	]
+        hasImplicitGrap ~~ true ifTrue:[
+            self grabMouseAndKeyboard.
+            hasImplicitGrap := true
+        ]
     ]
 !
 
@@ -3594,20 +3598,20 @@
     self clearImplicitGrab.
 
     superMenu notNil ifTrue:[
-	forceDo ifTrue:[
-	    superMenu doUngrab:true
-	].
-	^ self
+        forceDo ifTrue:[
+            superMenu doUngrab:true
+        ].
+        ^ self
     ].
 
     hasImplicitGrap ~~ true ifTrue:[
-	^ self
+        ^ self
     ].
 
     forceDo ifFalse:[
-	(selection notNil or:[prevFocusView == self]) ifTrue:[
-	    ^ self
-	].
+        (selection notNil or:[prevFocusView == self]) ifTrue:[
+            ^ self
+        ].
     ].
     self ungrabMouseAndKeyboard.
     self selection:nil.
@@ -4094,22 +4098,22 @@
     |menu item|
 
     indices size == 0 ifTrue:[
-	^ self
+        ^ self
     ].
     menu := self.
 
     [menu selectionIndex == indices first] whileTrue:[
-	(    (item := menu selection) isNil             "/ shouldn't happen
-	 or:[(menu := item submenu) isNil]              "/ no more indices; done
-	) ifTrue:[
-	    ^ true
-	].
-	indices removeFirst.
-
-	indices isEmpty ifTrue:[
-	   menu selection:nil.
-	 ^ self
-	]
+        (    (item := menu selection) isNil             "/ shouldn't happen
+         or:[(menu := item submenu) isNil]              "/ no more indices; done
+        ) ifTrue:[
+            ^ true
+        ].
+        indices removeFirst.
+
+        indices isEmpty ifTrue:[
+           menu selection:nil.
+         ^ self
+        ]
     ].
     menu openMenusFromItemIndices:indices.
 !
@@ -4810,8 +4814,8 @@
 container:aView
     super container:aView.
     aView notNil ifTrue:[
-	"/ I am no longer a popUpView
-	self updateLevelAndBorder
+        "/ I am no longer a popUpView
+        self updateLevelAndBorder
     ].
 !
 
@@ -5689,7 +5693,7 @@
     and:[ menuPanel application notNil
     and:[ menuPanel application askFor:#isUIPainter]])
     ifTrue:[
-	^ self "/ suppressed
+        ^ self "/ suppressed
     ].
     aMessage infoPrintCR
 !
@@ -6881,7 +6885,7 @@
 reinitStyle
 
     subMenu notNil ifTrue:[
-	subMenu reinitStyle
+        subMenu reinitStyle
     ].
 
     "Created: / 17.8.2000 / 17:57:07 / cg"
@@ -7572,8 +7576,8 @@
     <resource: #image>
 
     ^Icon
-	constantNamed:#'MenuPanel::Scrolling class icon'
-	ifAbsentPut:[(Depth1Image new) width: 11; height: 11; photometric:(#palette); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?>@@@@@@ @C@@N@@<@C8@O<@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((Depth1Image new) width: 11; height: 11; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@_<@? A<@C @D@@@@@@@@@@@a') ; yourself); yourself]
+        constantNamed:#'MenuPanel::Scrolling class icon'
+        ifAbsentPut:[(Depth1Image new) width: 11; height: 11; photometric:(#palette); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?>@@@@@@ @C@@N@@<@C8@O<@@@@@@@@a') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((Depth1Image new) width: 11; height: 11; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@_<@? A<@C @D@@@@@@@@@@@a') ; yourself); yourself]
 ! !
 
 !MenuPanel::ScrollActivity class methodsFor:'instance creation'!
@@ -7603,23 +7607,23 @@
     device := aMenu device.
 
     aDirection == #PREV ifTrue:[
-	aMenu verticalLayout ifTrue:[index := 3]    "/ 3 - 1 * 90  180
-			    ifFalse:[index := 2]    "/ 2 - 1 * 90  90   
+        aMenu verticalLayout ifTrue:[index := 3]    "/ 3 - 1 * 90  180
+                            ifFalse:[index := 2]    "/ 2 - 1 * 90  90   
     ] ifFalse:[
-	aMenu verticalLayout ifTrue:[index := 1]    "/ 1 - 1 * 90  0
-			    ifFalse:[index := 4]    "/ 4 - 1 * 90  270
+        aMenu verticalLayout ifTrue:[index := 1]    "/ 1 - 1 * 90  0
+                            ifFalse:[index := 4]    "/ 4 - 1 * 90  270
     ].
 
     icon := icons at:index.
 
     (icon isNil or:[icon device ~~ device]) ifTrue:[
-	icon := self class icon.
-	index > 1 ifTrue:[ icon := icon rotated:(index - 1 * 90) ]
-		 ifFalse:[ icon := icon copy ].
-
-	icon := icon onDevice:device.
-	icon clearMaskedPixels.
-	icons at:index put:icon
+        icon := self class icon.
+        index > 1 ifTrue:[ icon := icon rotated:(index - 1 * 90) ]
+                 ifFalse:[ icon := icon copy ].
+
+        icon := icon onDevice:device.
+        icon clearMaskedPixels.
+        icons at:index put:icon
     ].
     ^ icon
 ! !
@@ -7725,7 +7729,7 @@
 !MenuPanel class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/MenuPanel.st,v 1.438 2006-11-08 15:31:47 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/MenuPanel.st,v 1.439 2006-11-08 17:32:55 cg Exp $'
 ! !
 
 MenuPanel initialize!