MenuPanel.st
changeset 5707 1344a1eaf146
parent 5705 c3db8e3414b3
child 5732 e0a1d523567c
--- a/MenuPanel.st	Thu Feb 15 17:21:15 2018 +0100
+++ b/MenuPanel.st	Thu Feb 15 20:07:55 2018 +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
@@ -14,54 +14,54 @@
 "{ NameSpace: Smalltalk }"
 
 View subclass:#MenuPanel
-	instanceVariableNames:'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 closeDelayedMenuBlock
-		preferredWidth application originator centerItems hideOnRelease
-		defaultHideOnRelease buttonInsetX buttonInsetY itemSpace
-		stringOffsetX doAccessCharacterTranslation lastItem hasPerformed
-		focusComesByTab lastDrawnScrollerNextBounds
-		buttonActiveBackgroundColor buttonEnteredBackgroundColor
-		buttonPassiveBackgroundColor sizeFixed extraMargin
-		buttonActiveLevel buttonPassiveLevel buttonEnteredLevel
-		pluggableHelpSpecProvider'
-	classVariableNames:'DefaultBackgroundColor DefaultForegroundColor
-		IconDisabledIndicationOff IconDisabledIndicationOn
-		IconDisabledRadioOff IconDisabledRadioOn IconIndicationOff
-		IconIndicationOn IconRadioOff IconRadioOn Images
-		InitialSelectionQuerySignal LigthenedImages
-		MaxShortCutSearchLevel'
-	poolDictionaries:''
-	category:'Views-Menus'
+        instanceVariableNames:'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 closeDelayedMenuBlock
+                preferredWidth application originator centerItems hideOnRelease
+                defaultHideOnRelease buttonInsetX buttonInsetY itemSpace
+                stringOffsetX doAccessCharacterTranslation lastItem hasPerformed
+                focusComesByTab lastDrawnScrollerNextBounds
+                buttonActiveBackgroundColor buttonEnteredBackgroundColor
+                buttonPassiveBackgroundColor sizeFixed extraMargin
+                buttonActiveLevel buttonPassiveLevel buttonEnteredLevel
+                pluggableHelpSpecProvider'
+        classVariableNames:'DefaultBackgroundColor DefaultForegroundColor
+                IconDisabledIndicationOff IconDisabledIndicationOn
+                IconDisabledRadioOff IconDisabledRadioOn IconIndicationOff
+                IconIndicationOn IconRadioOff IconRadioOn Images
+                InitialSelectionQuerySignal LigthenedImages
+                MaxShortCutSearchLevel'
+        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'!
@@ -69,7 +69,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
@@ -86,8 +86,8 @@
     a menu panel used for both pull-down-menus and pop-up-menus.
 
     Due to some historic leftover, there are two mechanisms for menus:
-	1) the (very) old MenuView (which inherits from SelectionInListView)
-	2) this new MenuPanel.
+        1) the (very) old MenuView (which inherits from SelectionInListView)
+        2) this new MenuPanel.
 
     this will eventually replace most of the MenuView and PopUpMenu stuff.
     (and hopefully be ST-80 compatible...)
@@ -97,15 +97,15 @@
 
 
     Notice:
-	This is going to replace the obsolete MenuView.
+        This is going to replace the obsolete MenuView.
 
     [author:]
-	Claus Atzkern
+        Claus Atzkern
 
     [see also:]
-	Menu
-	MenuItem
-	MenuEditor
+        Menu
+        MenuItem
+        MenuEditor
 
     cg: this code is so ugly - needs a complete rewrite...
 
@@ -292,9 +292,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
 !
@@ -331,8 +331,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.
@@ -342,7 +342,7 @@
 "/ thus we do not overwrite the receiver
 
     aReceiver notNil ifTrue:[
-	mview receiver:aReceiver
+        mview receiver:aReceiver
     ].
   ^ mview
 ! !
@@ -351,7 +351,7 @@
 
 initialize
     InitialSelectionQuerySignal isNil ifTrue:[
-	InitialSelectionQuerySignal := QuerySignal new.
+        InitialSelectionQuerySignal := QuerySignal new.
     ].
 
     "
@@ -656,9 +656,9 @@
 mnemonicIdentifier
     "returns the identifier each mnemonic starts with;
      ex:
-	&File   mnemonic := Cmdf
-	F&ile   mnemonic := Cmdi
-	....."
+        &File   mnemonic := Cmdf
+        F&ile   mnemonic := Cmdi
+        ....."
 
     ^ 'Cmd'
 !
@@ -932,11 +932,11 @@
     |item|
 
     (item := self selection) isNil ifTrue:[
-	self topMenu
-	    openDelayed:nil;
-	    accept:nil.
+        self topMenu
+            openDelayed:nil;
+            accept:nil.
     ] ifFalse:[
-	self acceptItem:item inMenu:self
+        self acceptItem:item inMenu:self
     ]
 
     "Modified: / 29-06-2011 / 16:14:26 / cg"
@@ -1168,22 +1168,22 @@
     topMenu openDelayed:nil.
 
     (anItemOrNil isNil or:[anItemOrNil hideMenuOnActivated]) ifTrue:[
-	topMenu accept:anItemOrNil
+        topMenu accept:anItemOrNil
     ] ifFalse:[
-	anItemOrNil canAccept ifTrue:[
-	    tgState := anItemOrNil toggleIndication.
-
-	    self
-		accept:anItemOrNil
-		index:(aMenu selectionIndex)
-		toggle:tgState
-		receiver:(aMenu receiver).
-
-	    aMenu do:[:el| el updateIndicators].
-	    anItemOrNil hideMenuOnActivated ifFalse:[
-		aMenu invalidate
-	    ].
-	]
+        anItemOrNil canAccept ifTrue:[
+            tgState := anItemOrNil toggleIndication.
+
+            self
+                accept:anItemOrNil
+                index:(aMenu selectionIndex)
+                toggle:tgState
+                receiver:(aMenu receiver).
+
+            aMenu do:[:el| el updateIndicators].
+            anItemOrNil hideMenuOnActivated ifFalse:[
+                aMenu invalidate
+            ].
+        ]
     ]
 
     "Modified: / 29-06-2011 / 14:34:45 / cg"
@@ -1290,8 +1290,8 @@
     "sets collection of group sizes"
 
     aGroupSizes = groupSizes ifFalse:[
-	groupSizes := aGroupSizes copy.
-	self mustRearrange.
+        groupSizes := aGroupSizes copy.
+        self mustRearrange.
     ].
 !
 
@@ -1327,14 +1327,14 @@
     |size|
 
     self disabledRedrawDo:[
-	self removeAll.
-	size := labels size.
-
-	size > 0 ifTrue:[
-	    items := OrderedCollection new:size.
-	    labels do:[:aLabel| items add:(Item in:self label:aLabel) ].
-	    preferredExtent := nil.     "/ flush cached preferredExtent
-	]
+        self removeAll.
+        size := labels size.
+
+        size > 0 ifTrue:[
+            items := OrderedCollection new:size.
+            labels do:[:aLabel| items add:(Item in:self label:aLabel) ].
+            preferredExtent := nil.     "/ flush cached preferredExtent
+        ]
     ].
 !
 
@@ -1378,7 +1378,7 @@
 originator
     originator notNil ifTrue:[^ originator].
     superMenu notNil ifTrue:[
-	^ superMenu originator
+        ^ superMenu originator
     ].
     ^ nil
 !
@@ -1521,11 +1521,11 @@
     "set my enableChannel"
 
     enableChannel notNil ifTrue:[
-	enableChannel removeDependent:self
+        enableChannel removeDependent:self
     ].
 
     (enableChannel := aValueHolder) notNil ifTrue:[
-	enableChannel addDependent:self.
+        enableChannel addDependent:self.
     ].
     self enabled:(enableChannel value).
 !
@@ -1540,11 +1540,11 @@
     "set my menuHolder"
 
     menuHolder notNil ifTrue:[
-	menuHolder removeDependent:self
+        menuHolder removeDependent:self
     ].
 
     (menuHolder := aValueHolder) notNil ifTrue:[
-	menuHolder addDependent:self.
+        menuHolder addDependent:self.
     ].
     self menu:(menuHolder value)
 ! !
@@ -1588,7 +1588,7 @@
     "get the foreground drawing color used to highlight button selection"
 
     ^ styleSheet colorAt:#'button.activeForegroundColor'
-		 default:(self foregroundColor)
+                 default:(self foregroundColor)
 !
 
 buttonEdgeStyle
@@ -1650,7 +1650,7 @@
     |bg|
 
     (bg := self backgroundColor) = DefaultBackgroundColor ifFalse:[
-	^ bg mixed:0.5 with:Color white
+        ^ bg mixed:0.5 with:Color white
     ].
     ^ styleSheet colorAt:#'menuPanel.disabledEtchedFgColor'
 
@@ -1667,7 +1667,7 @@
     "return the background color for entered items"
 
     ^ styleSheet colorAt:#'menu.enteredBackgroundColor'
-		 default:(self backgroundColor)
+                 default:(self backgroundColor)
 !
 
 enteredForegroundColor
@@ -1685,7 +1685,7 @@
     self do:[:anItem| anItem fontChanged ].
 
     (shown and:[superMenu notNil]) ifTrue:[
-	self extent:(self preferredExtent)
+        self extent:(self preferredExtent)
     ].
     self mustRearrange.
 !
@@ -1735,7 +1735,7 @@
 
     currentFont := gc font.
     (aFont notNil and:[aFont ~= currentFont]) ifTrue:[
-	super font:aFont.
+        super font:aFont.
     ].
     ^ currentFont
 !
@@ -1751,7 +1751,7 @@
     "default height"
 
     self hasExplicitExtent ifFalse:[
-	^ self preferredHeight
+        ^ self preferredHeight
     ].
     ^ super height
 !
@@ -1789,15 +1789,15 @@
     |oldLeft|
 
     (shown and:[mustRearrange not and:[sizeFixed not]]) ifFalse:[
-	^ super origin:origin
+        ^ super origin:origin
     ].
     "left partner in horizontal panel toggles visibility"
     oldLeft := self left.
     super origin:origin.
     oldLeft = self left ifFalse:[
-	"/ no change notification... so cannot call #mustRearrange
-	mustRearrange := true.
-	self invalidate.
+        "/ no change notification... so cannot call #mustRearrange
+        mustRearrange := true.
+        self invalidate.
     ].
 !
 
@@ -1983,8 +1983,8 @@
     sizeFixed := aBoolean.
 
     sizeFixed ifFalse:[
-	"/ changed due to menu in horizontal panel
-	superView notNil ifTrue:[ superView addDependent:self ].
+        "/ changed due to menu in horizontal panel
+        superView notNil ifTrue:[ superView addDependent:self ].
     ].
 !
 
@@ -2126,7 +2126,7 @@
 
 itemsDo:aBlock
     items notNil ifTrue:[
-	items do:aBlock
+        items do:aBlock
     ]
 
     "Created: / 09-11-2010 / 10:05:54 / cg"
@@ -2134,7 +2134,7 @@
 
 itemsDoWithIndex:aBlock
     items notNil ifTrue:[
-	items doWithIndex:aBlock
+        items doWithIndex:aBlock
     ]
 
     "Created: / 09-11-2010 / 10:06:02 / cg"
@@ -2181,8 +2181,8 @@
 
 level:anInt
     anInt ~~ level ifTrue:[
-	super level:anInt.
-	self mustRearrange
+        super level:anInt.
+        self mustRearrange
     ]
 
     "Modified: / 15.11.2001 / 17:42:07 / cg"
@@ -2242,7 +2242,7 @@
     verticalLayout notNil ifTrue:[ ^ verticalLayout ].
 
     superMenu notNil ifTrue:[ verticalLayout := true ]
-		    ifFalse:[ verticalLayout := self isPopUpView ].
+                    ifFalse:[ verticalLayout := self isPopUpView ].
     ^ verticalLayout
 !
 
@@ -2339,10 +2339,10 @@
     |submenu|
 
     self itemAt:stringOrNumber do:[:anItem|
-	submenu := anItem currentSubmenu.
-	submenu isNil ifTrue:[
-	    submenu := anItem setupSubmenu
-	].
+        submenu := anItem currentSubmenu.
+        submenu isNil ifTrue:[
+            submenu := anItem setupSubmenu
+        ].
     ].
     ^ submenu
 
@@ -2363,11 +2363,11 @@
     item := self selection.
 
     item notNil ifTrue:[
-	submenu := item currentSubmenu.
-
-	(submenu notNil and:[submenu shown]) ifTrue:[
-	    ^ submenu
-	].
+        submenu := item currentSubmenu.
+
+        (submenu notNil and:[submenu shown]) ifTrue:[
+            ^ submenu
+        ].
     ].
     ^ nil
 ! !
@@ -2419,7 +2419,7 @@
     self rearrangeItemsIfItemVisibilityChanged.
 
     aBoolean ifTrue:[
-	self fixSize.
+        self fixSize.
     ].
 "/    self makeFullyVisible.   -- done in realize
     self openModal:[true]. "realize     "
@@ -2428,7 +2428,7 @@
     "/ return nil - to avoid items triggering twice.
 
     self topMenu hasPerformed ifTrue:[
-	^ nil
+        ^ nil
     ].
 
     ^ self lastValueAccepted
@@ -2566,11 +2566,11 @@
     |item|
 
     (item := self itemAt:stringOrNumber) notNil ifTrue:[
-	items remove:item.
-	items := items asNilIfEmpty.
-	item destroy.
-	preferredExtent := nil.     "/ flush cached preferredExtent
-	self mustRearrange.
+        items remove:item.
+        items := items asNilIfEmpty.
+        item destroy.
+        preferredExtent := nil.     "/ flush cached preferredExtent
+        self mustRearrange.
     ].
     ^ item
 
@@ -2581,13 +2581,13 @@
     "remove all items and submenus"
 
     self disabledRedrawDo:[
-	self selection:nil.
-	groupSizes := nil.
-	items notNil ifTrue:[
-	    items copy do:[:el| el destroy ].
-	].
-	items := nil.
-	preferredExtent := nil.     "/ flush cached preferredExtent
+        self selection:nil.
+        groupSizes := nil.
+        items notNil ifTrue:[
+            items copy do:[:el| el destroy ].
+        ].
+        items := nil.
+        preferredExtent := nil.     "/ flush cached preferredExtent
     ].
 
     "Modified: / 15.11.2001 / 17:02:51 / cg"
@@ -2601,15 +2601,15 @@
     changedObject == enableChannel ifTrue:[^ self enabled:(enableChannel value)].
 
     changedObject == superView ifTrue:[
-	"/ changed due to menu in horizontal panel
-	something == #sizeOfView ifTrue:[
-	    (shown and:[sizeFixed not]) ifTrue:[
-		"/ no change notification... so cannot call #mustRearrange
-		mustRearrange := true.
-		self invalidate.
-	    ].
-	].
-	^ self
+        "/ changed due to menu in horizontal panel
+        something == #sizeOfView ifTrue:[
+            (shown and:[sizeFixed not]) ifTrue:[
+                "/ no change notification... so cannot call #mustRearrange
+                mustRearrange := true.
+                self invalidate.
+            ].
+        ].
+        ^ self
     ].
 
     super update:something with:aParameter from:changedObject
@@ -2642,31 +2642,31 @@
     "setup from a menu"
 
     self disabledRedrawDo:[
-	|menu newItems menuReceiver|
-
-	self removeAll.
-
-	(menu := aMenu) notNil ifTrue:[
-	    (aMenu isCollection) ifTrue:[
-		menu := Menu decodeFromLiteralArray:aMenu.
-	    ] ifFalse:[
-		menuReceiver := menu receiver.
-		menuReceiver notNil ifTrue:[
-		    self receiver:menuReceiver.
-		]
-	    ].
-	    (newItems := menu menuItems) notEmptyOrNil ifTrue:[
-		items := newItems collect:[:ni |
-				|i|
-
-				i:= Item in:self.
-				i menuItem:ni.
-				i.
-			    ].
-	    ].
-	    self groupSizes:(menu groupSizes).
-	    preferredExtent := nil.     "/ flush cached preferredExtent
-	]
+        |menu newItems menuReceiver|
+
+        self removeAll.
+
+        (menu := aMenu) notNil ifTrue:[
+            (aMenu isCollection) ifTrue:[
+                menu := Menu decodeFromLiteralArray:aMenu.
+            ] ifFalse:[
+                menuReceiver := menu receiver.
+                menuReceiver notNil ifTrue:[
+                    self receiver:menuReceiver.
+                ]
+            ].
+            (newItems := menu menuItems) notEmptyOrNil ifTrue:[
+                items := newItems collect:[:ni |
+                                |i|
+
+                                i:= Item in:self.
+                                i menuItem:ni.
+                                i.
+                            ].
+            ].
+            self groupSizes:(menu groupSizes).
+            preferredExtent := nil.     "/ flush cached preferredExtent
+        ]
     ]
 
     "Modified: / 09-11-2010 / 11:52:28 / cg"
@@ -2832,20 +2832,20 @@
     |level layout|
 
     isSelected ifTrue:[
-	level := styleSheet at:#'menu.hilightLevel' default:0.
+        level := styleSheet at:#'menu.hilightLevel' default:0.
     ] ifFalse:[
-	anItem == enteredItem ifTrue:[ level := self enteredLevel ]
-			     ifFalse:[ level := 0 ]
+        anItem == enteredItem ifTrue:[ level := self enteredLevel ]
+                             ifFalse:[ level := 0 ]
     ].
 
     level ~~ 0 ifTrue:[
-	layout := anItem layout.
-
-	self drawEdgesForX:(layout left)
-			 y:(layout top)
-		     width:(layout width)
-		    height:(layout height)
-		     level:level
+        layout := anItem layout.
+
+        self drawEdgesForX:(layout left)
+                         y:(layout top)
+                     width:(layout width)
+                    height:(layout height)
+                     level:level
     ].
 !
 
@@ -2907,11 +2907,11 @@
     |layout|
 
     (mustRearrange not and:[shown]) ifTrue:[
-	layout := anItem layout.
-
-	(layout bottom > margin and:[layout top < (height - margin)]) ifTrue:[
-	    self invalidate:(layout "insetBy:-1") repairNow:aBool
-	]
+        layout := anItem layout.
+
+        (layout bottom > margin and:[layout top < (height - margin)]) ifTrue:[
+            self invalidate:(layout "insetBy:-1") repairNow:aBool
+        ]
     ].
 
     "Modified: / 29.2.2000 / 11:28:59 / cg"
@@ -3125,8 +3125,8 @@
     items isNil ifTrue:[^ self].
 
     (items contains:[:item | item canChangeVisibility]) ifTrue:[
-	mustRearrange := true.
-	self rearrangeItems.
+        mustRearrange := true.
+        self rearrangeItems.
     ]
 
     "Modified: / 03-12-2013 / 17:04:05 / cg"
@@ -3326,7 +3326,7 @@
     |menue motionPoint translatedPoint sensor|
 
     self scrollActivity isActive ifTrue:[
-	^ self
+        ^ self
     ].
 
     sensor := self sensor.
@@ -3343,20 +3343,20 @@
     "/ hideOnRelease := true.
 
     (self isPopUpView or:[sensor anyButtonPressed]) ifTrue:[
-	^ self
+        ^ self
     ].
 
     hideOnRelease ifTrue:[
-	sensor anyButtonPressed ifFalse:[^ self]
+        sensor anyButtonPressed ifFalse:[^ self]
     ] ifFalse:[
-	sensor anyButtonPressed ifTrue:[^ self]
+        sensor anyButtonPressed ifTrue:[^ self]
     ].
 
     (selection notNil and:[selection visibleSubmenu isNil]) ifTrue:[
-	"/ selection on grabView without a submenu (Button ...); check whether moving out
-	(self containsPoint:motionPoint) ifFalse:[
-	    ^ self accept:nil
-	]
+        "/ selection on grabView without a submenu (Button ...); check whether moving out
+        (self containsPoint:motionPoint) ifFalse:[
+            ^ self accept:nil
+        ]
     ].
 
     "Modified: / 13.11.2001 / 20:21:49 / cg"
@@ -3408,72 +3408,77 @@
      releaseTime menuMapTime|
 
     hideOnRelease ifFalse:[
-	^ self
+        ^ self
     ].
     topMenu := self topMenu.
     topMenu openDelayed:nil.
 
     self scrollActivity stop ifTrue:[
-	^ self
+        ^ self
     ].
     dstMenu := topMenu activeMenu.
     hideMenuAndPerformAction := dstMenu selection notNil or:[dstMenu isPopUpView not].
 
     hideMenuAndPerformAction ifTrue:[
-	"open topMenu, a popup by click and release button in a short time period"
-	(topMenu == self
-	and:[mapTime notNil
-	and:[dstMenu == self
-	and:[dstMenu isPopUpView]]]) ifTrue:[
-	    hideMenuAndPerformAction := false.
-	].
+        "open topMenu, a popup by click and release button in a short time period"
+        (topMenu == self
+        and:[mapTime notNil
+        and:[dstMenu == self
+        and:[dstMenu isPopUpView]]]) ifTrue:[
+            hideMenuAndPerformAction := false.
+        ].
     ].
     hideMenuAndPerformAction ifFalse:[
-	hideOnRelease ifTrue:[
-	    releaseTime := windowGroup lastEvent timeStamp.
-	    menuMapTime := dstMenu mapTime ? releaseTime.
-
-	    hideMenuAndPerformAction := (releaseTime millisecondDeltaFrom:menuMapTime)
-					> (PopUpMenu maxClickTimeToStayOpen).
-	].
+        hideOnRelease ifTrue:[
+            windowGroup isNil ifTrue:[ "/ race condition?!!
+                hideMenuAndPerformAction := true.
+                self accept:nil.
+                ^ self.
+            ].
+            releaseTime := windowGroup lastEvent timeStamp.
+            menuMapTime := dstMenu mapTime ? releaseTime.
+
+            hideMenuAndPerformAction := (releaseTime millisecondDeltaFrom:menuMapTime)
+                                        > (PopUpMenu maxClickTimeToStayOpen).
+        ].
     ].
     hideMenuAndPerformAction ifTrue:[
-	srcPoint := x@y.
-
-	(     (dstMenu := self detectMenuAtGrabPoint:srcPoint) notNil
-	 and:[(item    := dstMenu selection) notNil]
-	) ifTrue:[
-	    item visibleSubmenu notNil ifTrue:[
-		dstMenu selection:nil.
-		(selection isNil and:[self isPopUpView not]) ifTrue:[
-		    self accept:nil.
-		].
-		^ self
-	    ].
-	    subm := item currentSubmenu.
-
-	    subm notNil ifTrue:[
-		subm shown ifTrue:[^ self].
-		"/ test whether any action is assigned to the menu
-		"/ if not ignorre accept
-		item hasDelayedMenu ifFalse:[^ self].
-		"/ handle action defined for the delayed menu
-	    ].
-	    dstPoint := dstMenu translateGrabPoint:srcPoint.
-
-	    (dstMenu itemAtPoint:dstPoint) == dstMenu selection ifFalse:[
-		item := nil
-	    ].
-	    topMenu acceptItem:item inMenu:dstMenu.
-	    ^ self
-	].
-
-	(selection notNil and:[dstMenu == self]) ifTrue:[
-	    selection visibleSubmenu notNil ifTrue:[
-		^ self
-	    ]
-	].
-	self accept:nil.
+        srcPoint := x@y.
+
+        (     (dstMenu := self detectMenuAtGrabPoint:srcPoint) notNil
+         and:[(item    := dstMenu selection) notNil]
+        ) ifTrue:[
+            item visibleSubmenu notNil ifTrue:[
+                dstMenu selection:nil.
+                (selection isNil and:[self isPopUpView not]) ifTrue:[
+                    self accept:nil.
+                ].
+                ^ self
+            ].
+            subm := item currentSubmenu.
+
+            subm notNil ifTrue:[
+                subm shown ifTrue:[^ self].
+                "/ test whether any action is assigned to the menu
+                "/ if not ignorre accept
+                item hasDelayedMenu ifFalse:[^ self].
+                "/ handle action defined for the delayed menu
+            ].
+            dstPoint := dstMenu translateGrabPoint:srcPoint.
+
+            (dstMenu itemAtPoint:dstPoint) == dstMenu selection ifFalse:[
+                item := nil
+            ].
+            topMenu acceptItem:item inMenu:dstMenu.
+            ^ self
+        ].
+
+        (selection notNil and:[dstMenu == self]) ifTrue:[
+            selection visibleSubmenu notNil ifTrue:[
+                ^ self
+            ]
+        ].
+        self accept:nil.
     ].
 !
 
@@ -3646,26 +3651,26 @@
     self detectGrabMenu handlePointerLeave:state.
 
     (selection isNil or:[self isPopUpView]) ifTrue:[
-	^ self
+        ^ self
     ].
 
     selection visibleSubmenu notNil ifTrue:[^ self].
 
     windowGroup focusView ~~ self ifTrue:[
-	self accept:nil
+        self accept:nil
     ] ifFalse:[
-	selection isButton ifTrue:[
-	    sensor := self sensor.
-
-	    sensor isNil ifTrue:[
-		self accept:nil
-	    ] ifFalse:[
-		"/ I'have the focus; if no button pressed, than keep the selection
-		sensor anyButtonPressed ifTrue:[
-		    self selection:nil
-		]
-	    ].
-	]
+        selection isButton ifTrue:[
+            sensor := self sensor.
+
+            sensor isNil ifTrue:[
+                self accept:nil
+            ] ifFalse:[
+                "/ I'have the focus; if no button pressed, than keep the selection
+                sensor anyButtonPressed ifTrue:[
+                    self selection:nil
+                ]
+            ].
+        ]
     ].
 !
 
@@ -3956,145 +3961,145 @@
      size  "{ Class:SmallInteger }"
     |
     (size  := items size) == 0 ifTrue:[
-	superMenu notNil ifTrue:[superMenu handleCursorKey:aKey].
-	^ self
+        superMenu notNil ifTrue:[superMenu handleCursorKey:aKey].
+        ^ self
     ].
 
     isVrt := self verticalLayout.
 
     selection isNil ifTrue:[
-	(isVrt and:[aKey == #CursorDown]) ifTrue:[
-	    idx := items findFirst:[:el | el notNil and:[ el canSelect ]].
-	    idx ~~ 0 ifTrue:[
-		self selection:(items at:idx).
-		^ self
-	    ]
-	].
-	(isVrt and:[aKey == #CursorUp]) ifTrue:[
-	    idx := items findLast:[:el | el notNil and:[ el canSelect ]].
-	    idx ~~ 0 ifTrue:[
-		self selection:(items at:idx).
-		^ self
-	    ]
-	]
+        (isVrt and:[aKey == #CursorDown]) ifTrue:[
+            idx := items findFirst:[:el | el notNil and:[ el canSelect ]].
+            idx ~~ 0 ifTrue:[
+                self selection:(items at:idx).
+                ^ self
+            ]
+        ].
+        (isVrt and:[aKey == #CursorUp]) ifTrue:[
+            idx := items findLast:[:el | el notNil and:[ el canSelect ]].
+            idx ~~ 0 ifTrue:[
+                self selection:(items at:idx).
+                ^ self
+            ]
+        ]
     ].
 
     (    (isVrt     and:[aKey == #CursorUp    or:[aKey == #CursorDown]])
      or:[(isVrt not and:[aKey == #CursorRight or:[aKey == #CursorLeft]])]
     ) ifTrue:[
-	selection isNil ifTrue:[
-	    (superMenu notNil and:[superMenu verticalLayout == isVrt]) ifTrue:[
-		^ superMenu handleCursorKey:aKey
-	    ].
-	    idx := 0.
-
-	    isVrt ifTrue:[
-		"/ used because of vertical scrolling
-		idx := items findFirst:[:el| el layout top > 0 ].
-		idx ~~ 0 ifTrue:[idx := idx - 1 ]
-	    ].
-	] ifFalse:[
-	    idx := self indexOf:selection.
-	].
-	next := aKey == #CursorRight or:[aKey == #CursorDown].
-
-	idx0 := idx.
-	size timesRepeat:[
-	    |el|
-
-	    next ifTrue:[idx := idx + 1] ifFalse:[idx := idx - 1].
-
-	    idx > size ifTrue:[
-		idx := 0 "1"
-	    ] ifFalse:[
-		idx < 0 ifTrue:[
-		    idx := size
-		]
-	    ].
-
-	    idx == 0 ifTrue:[
-		self selection:nil.
-		^ self
-	    ] ifFalse:[
-		(el := items at:idx ifAbsent:nil) notNil ifTrue:[
-		    el canSelect ifTrue:[
-			el hasDelayedMenu ifTrue:[
-			    "/ do not open menu
-			    self selection:el openMenu:false
-			] ifFalse:[
-			    "/ open comes from style-sheet
-			    self selection:el.
-			].
-			^ self
-		    ].
-		]
-	    ].
-	    idx == idx0 ifTrue:[
-		^ self
-	    ].
-	].
-	^ self
+        selection isNil ifTrue:[
+            (superMenu notNil and:[superMenu verticalLayout == isVrt]) ifTrue:[
+                ^ superMenu handleCursorKey:aKey
+            ].
+            idx := 0.
+
+            isVrt ifTrue:[
+                "/ used because of vertical scrolling
+                idx := items findFirst:[:el| el layout top > 0 ].
+                idx ~~ 0 ifTrue:[idx := idx - 1 ]
+            ].
+        ] ifFalse:[
+            idx := self indexOf:selection.
+        ].
+        next := aKey == #CursorRight or:[aKey == #CursorDown].
+
+        idx0 := idx.
+        size timesRepeat:[
+            |el|
+
+            next ifTrue:[idx := idx + 1] ifFalse:[idx := idx - 1].
+
+            idx > size ifTrue:[
+                idx := 0 "1"
+            ] ifFalse:[
+                idx < 0 ifTrue:[
+                    idx := size
+                ]
+            ].
+
+            idx == 0 ifTrue:[
+                self selection:nil.
+                ^ self
+            ] ifFalse:[
+                (el := items at:idx ifAbsent:nil) notNil ifTrue:[
+                    el canSelect ifTrue:[
+                        el hasDelayedMenu ifTrue:[
+                            "/ do not open menu
+                            self selection:el openMenu:false
+                        ] ifFalse:[
+                            "/ open comes from style-sheet
+                            self selection:el.
+                        ].
+                        ^ self
+                    ].
+                ]
+            ].
+            idx == idx0 ifTrue:[
+                ^ self
+            ].
+        ].
+        ^ self
     ].
 
     superMenu notNil ifTrue:[
-	p1 := self translateGrabPoint:0.
-	p2 := superMenu translateGrabPoint:0.
+        p1 := self translateGrabPoint:0.
+        p2 := superMenu translateGrabPoint:0.
     ].
 
     isVrt ifTrue:[
-	(superMenu notNil and:[p1 x > p2 x]) ifTrue:[
-	    backKey := #CursorRight
-	] ifFalse:[
-	    backKey := #CursorLeft.
-	]
+        (superMenu notNil and:[p1 x > p2 x]) ifTrue:[
+            backKey := #CursorRight
+        ] ifFalse:[
+            backKey := #CursorLeft.
+        ]
     ] ifFalse:[
-	(superMenu notNil and:[p1 y > p2 y]) ifTrue:[
-	    backKey := #CursorDown
-	] ifFalse:[
-	    backKey := #CursorUp.
-	]
+        (superMenu notNil and:[p1 y > p2 y]) ifTrue:[
+            backKey := #CursorDown
+        ] ifFalse:[
+            backKey := #CursorUp.
+        ]
     ].
 
     aKey == backKey ifTrue:[
-	superMenu isNil ifTrue:[
-	    self accept:nil
-	] ifFalse:[
-	    superMenu verticalLayout ~~ isVrt ifTrue:[
-		superMenu handleCursorKey:aKey
-	    ] ifFalse:[
-		superMenu selection hideSubmenu
-	    ]
-	].
-	^ self
+        superMenu isNil ifTrue:[
+            self accept:nil
+        ] ifFalse:[
+            superMenu verticalLayout ~~ isVrt ifTrue:[
+                superMenu handleCursorKey:aKey
+            ] ifFalse:[
+                superMenu selection hideSubmenu
+            ]
+        ].
+        ^ self
     ].
 
     selection isNil ifTrue:[
-	superMenu isNil ifTrue:[^ self accept:nil].
-
-	superMenu verticalLayout ~~ isVrt ifTrue:[
-	    superMenu handleCursorKey:aKey
-	] ifFalse:[
-	    (item := items findFirst:[:el| el canSelect]) notNil ifTrue:[
-		self selectionIndex:item
-	    ]
-	].
-	^ self
+        superMenu isNil ifTrue:[^ self accept:nil].
+
+        superMenu verticalLayout ~~ isVrt ifTrue:[
+            superMenu handleCursorKey:aKey
+        ] ifFalse:[
+            (item := items findFirst:[:el| el canSelect]) notNil ifTrue:[
+                self selectionIndex:item
+            ]
+        ].
+        ^ self
     ].
 
     selection hasSubmenu ifTrue:[
-	(menu := selection visibleSubmenu) isNil ifTrue:[
-	    selection toggleSubmenuVisibility
-	] ifFalse:[
-	    menu selectionIndex:1
-	]
+        (menu := selection visibleSubmenu) isNil ifTrue:[
+            selection toggleSubmenuVisibility
+        ] ifFalse:[
+            menu selectionIndex:1
+        ]
     ] ifFalse:[
-	superMenu notNil ifTrue:[
-	    superMenu verticalLayout ~~ isVrt ifTrue:[
-		superMenu handleCursorKey:aKey
-	    ]
-	] ifFalse:[
-	    self accept:nil
-	]
+        superMenu notNil ifTrue:[
+            superMenu verticalLayout ~~ isVrt ifTrue:[
+                superMenu handleCursorKey:aKey
+            ]
+        ] ifFalse:[
+            self accept:nil
+        ]
     ].
 !
 
@@ -4150,52 +4155,52 @@
     |sensor subm item|
 
     (item := selection) isNil ifTrue:[
-	superMenu notNil ifTrue:[
-	    item := superMenu selection.
-
-	    item value notNil ifTrue:[
-		"/ is a delayed menu
-		self accept:item
-	    ] ifFalse:[
-		item toggleSubmenuVisibility
-	    ]
-	] ifFalse:[
-	    self accept
-	].
-	^ self
+        superMenu notNil ifTrue:[
+            item := superMenu selection.
+
+            item value notNil ifTrue:[
+                "/ is a delayed menu
+                self accept:item
+            ] ifFalse:[
+                item toggleSubmenuVisibility
+            ]
+        ] ifFalse:[
+            self accept
+        ].
+        ^ self
     ].
     selection hasSubmenu ifTrue:[
-	selection hasDelayedMenu ifFalse:[
-	    selection toggleSubmenuVisibility.
-	  ^ self
-	].
-	subm := selection currentSubmenu.
-
-	(subm notNil and:[subm shown]) ifTrue:[
-	    selection toggleSubmenuVisibility.
-	  ^ self
-	].
-	self openDelayed:nil
+        selection hasDelayedMenu ifFalse:[
+            selection toggleSubmenuVisibility.
+          ^ self
+        ].
+        subm := selection currentSubmenu.
+
+        (subm notNil and:[subm shown]) ifTrue:[
+            selection toggleSubmenuVisibility.
+          ^ self
+        ].
+        self openDelayed:nil
     ].
     self accept.
 
     " test for toggle "
     item isToggle ifTrue:[
-	self selection:item.
+        self selection:item.
     ] ifFalse:[
-	(selection notNil and:[selection triggerOnDown]) ifFalse:[
-	    ^ self
-	]
+        (selection notNil and:[selection triggerOnDown]) ifFalse:[
+            ^ self
+        ]
     ].
 
     (sensor := self sensor) isNil ifTrue:[
-	^ self
+        ^ self
     ].
 
     [
-	sensor flushKeyboardFor:nil.
-	Delay waitForSeconds:0.1.
-	sensor hasKeyPressEventFor:nil.
+        sensor flushKeyboardFor:nil.
+        Delay waitForSeconds:0.1.
+        sensor hasKeyPressEventFor:nil.
     ] whileTrue.
 !
 
@@ -4209,32 +4214,32 @@
      and:[anItemOrNil canSelect
      and:[selection isNil
      and:[self isPopUpView not]]]) ifTrue:[
-	anItemOrNil isButton ifTrue:[
-	    (    self buttonEnteredBackgroundColor ~= self buttonPassiveBackgroundColor
-	     or:[self buttonEnteredLevel ~= self buttonPassiveLevel]
-	    ) ifTrue:[
-		newItem := anItemOrNil
-	    ]
-	] ifFalse:[
-	    (self enteredLevel ~~ 0
-	      or:[self enteredBackgroundColor ~= self backgroundColor]
-	    ) ifTrue:[
-		newItem := anItemOrNil
-	    ]
-	]
+        anItemOrNil isButton ifTrue:[
+            (    self buttonEnteredBackgroundColor ~= self buttonPassiveBackgroundColor
+             or:[self buttonEnteredLevel ~= self buttonPassiveLevel]
+            ) ifTrue:[
+                newItem := anItemOrNil
+            ]
+        ] ifFalse:[
+            (self enteredLevel ~~ 0
+              or:[self enteredBackgroundColor ~= self backgroundColor]
+            ) ifTrue:[
+                newItem := anItemOrNil
+            ]
+        ]
     ].
 
     newItem ~~ enteredItem ifTrue:[
-	oldItem     := enteredItem.
-	enteredItem := newItem.
-
-	oldItem notNil ifTrue:[
-	    self invalidateItem:oldItem repairNow:(enteredItem isNil).
-	].
-
-	enteredItem notNil ifTrue:[
-	    self invalidateItem:enteredItem repairNow:true.
-	].
+        oldItem     := enteredItem.
+        enteredItem := newItem.
+
+        oldItem notNil ifTrue:[
+            self invalidateItem:oldItem repairNow:(enteredItem isNil).
+        ].
+
+        enteredItem notNil ifTrue:[
+            self invalidateItem:enteredItem repairNow:true.
+        ].
     ].
 !
 
@@ -4256,7 +4261,7 @@
 
     winGrp := self windowGroup.
     winGrp notNil ifTrue:[
-	masterGroup := winGrp previousGroup.
+        masterGroup := winGrp previousGroup.
     ].
     winGrpForBusyCursor := masterGroup ? winGrp.
 
@@ -4270,9 +4275,9 @@
     (item showBusyCursorWhilePerforming
     and:[winGrpForBusyCursor notNil])
     ifTrue:[
-	winGrpForBusyCursor withWaitCursorDo:acceptAction
+        winGrpForBusyCursor withWaitCursorDo:acceptAction
     ] ifFalse:[
-	acceptAction value
+        acceptAction value
     ].
 
     "Modified: / 29-06-2011 / 16:32:36 / cg"
@@ -4286,8 +4291,8 @@
     |selectableItem|
 
     (super canTab and:[self isPopUpView not]) ifTrue:[
-	selectableItem := self firstItemSelectable.
-	^ selectableItem notNil
+        selectableItem := self firstItemSelectable.
+        ^ selectableItem notNil
     ].
     ^ false
 !
@@ -4296,10 +4301,10 @@
     "returns true if focus comes by tab and should be drawn"
 
     focusComesByTab == true ifTrue:[
-	(shown and:[self hasFocus]) ifTrue:[
-	    ^ true
-	].
-	focusComesByTab := false.
+        (shown and:[self hasFocus]) ifTrue:[
+            ^ true
+        ].
+        focusComesByTab := false.
     ].
     ^ false
 
@@ -4312,16 +4317,16 @@
     |selectableItem|
 
     (self supportsFocusOnTab and:[self isPopUpView not]) ifTrue:[
-	focusComesByTab := aBoolean.
-
-	self hasSelection ifTrue:[
-	    ^ self
-	].
-
-	aBoolean ifTrue:[
-	    selectableItem := self firstItemSelectable.
-	].
-	self selection:selectableItem openMenu:false.
+        focusComesByTab := aBoolean.
+
+        self hasSelection ifTrue:[
+            ^ self
+        ].
+
+        aBoolean ifTrue:[
+            selectableItem := self firstItemSelectable.
+        ].
+        self selection:selectableItem openMenu:false.
     ].
 
     "Modified: / 29-06-2011 / 16:23:19 / cg"
@@ -4331,8 +4336,8 @@
     "notification from the windowGroup that I got/lost the keyboard focus."
 
     self isPopUpView ifTrue:[
-	"/ not visible for popup menus
-	^ super hasKeyboardFocus:aBoolean
+        "/ not visible for popup menus
+        ^ super hasKeyboardFocus:aBoolean
     ].
 
 "/    (aBoolean not and:[hasImplicitGrap ~~ true]) ifTrue:[
@@ -4371,9 +4376,9 @@
     "/ for now, the menuPanelTakesFocusOnClick returns true, otherwise,
     "/ we cannot control menus with the keyboard.
     self isPopUpView ifTrue:[
-	^ false
+        ^ false
     ] ifFalse:[
-	^ UserPreferences current menuPanelTakesFocusOnClick.
+        ^ UserPreferences current menuPanelTakesFocusOnClick.
     ]
 ! !
 
@@ -4398,20 +4403,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.
@@ -4571,9 +4576,9 @@
 
     dstMenu := self detectMenuAtGrabPoint:srcPoint.
     dstMenu notNil ifTrue:[
-	dstPoint := dstMenu translateGrabPoint:srcPoint.
-	item := dstMenu itemAtPoint:dstPoint.
-	aBlock value:dstMenu value:item.
+        dstPoint := dstMenu translateGrabPoint:srcPoint.
+        item := dstMenu itemAtPoint:dstPoint.
+        aBlock value:dstMenu value:item.
     ]
 ! !
 
@@ -4797,23 +4802,23 @@
     |bgColor|
 
     self isPopUpView ifTrue:[
-	bgColor := styleSheet colorAt:'menu.backgroundColor'.
-	bgColor notNil ifTrue:[ self viewBackground:bgColor ].
-
-	"Because of #saveUnder of ShadowView the order of realize is significant:
-	 shadowView must be realized before self"
-	self hiddenOnRealize:true.
-	super realize.
-	self resize.
-	self makeFullyVisible.
+        bgColor := styleSheet colorAt:'menu.backgroundColor'.
+        bgColor notNil ifTrue:[ self viewBackground:bgColor ].
+
+        "Because of #saveUnder of ShadowView the order of realize is significant:
+         shadowView must be realized before self"
+        self hiddenOnRealize:true.
+        super realize.
+        self resize.
+        self makeFullyVisible.
 "/        self mustRearrange.
-	shadowView notNil ifTrue:[
-	    shadowView realize.
-	].
-	self raise.
-	self map.
+        shadowView notNil ifTrue:[
+            shadowView realize.
+        ].
+        self raise.
+        self map.
     ] ifFalse:[
-	super realize.
+        super realize.
     ].
     self allSubViewsDo:[:aView| aView realize ].
     "/ hideOnRelease := defaultHideOnRelease.
@@ -4836,7 +4841,7 @@
     self mustRearrange.      "/ care for changed font sizes etc.
 
     self do:[:anItem |
-	anItem reinitStyle
+        anItem reinitStyle
     ].
 
     "Created: / 10.9.1998 / 21:37:05 / cg"
@@ -4851,7 +4856,7 @@
 
     "hide all submenus opened within the menu"
     self itemsDo:[:eachItem|
-	eachItem visibleSubmenu notNil ifTrue:[ eachItem hideSubmenu ].
+        eachItem visibleSubmenu notNil ifTrue:[ eachItem hideSubmenu ].
     ].
 
     self removeDependencies.
@@ -4907,56 +4912,56 @@
     lKey := uKey asLowercase.
 
     accessCharacterMatchQuery :=
-	[:el|
-	    |k|
-
-	    k := el accessCharacter.
-	    k == uKey or:[k == lKey]
-	].
+        [:el|
+            |k|
+
+            k := el accessCharacter.
+            k == uKey or:[k == lKey]
+        ].
     maxShortCutSearchLevel := self class maxShortCutSearchLevel.
 
     selection notNil ifTrue:[
-	"first lookup the current grapMenu before starting in the topMenu
-	"
-	menu := self detectGrabMenu.
-
-	[ menu ~~ self ] whileTrue:[
-	    index := menu selectionIndex.
-	    list  := menu
-			selectItemIndicesFor:accessCharacterMatchQuery
-			maxDepth:maxShortCutSearchLevel from:(index + 1) to:99999
-			ignoreSubmenuBlock:[:anItem| anItem ignoreMnemonicKeys ].
-
-	    list size ~~ 0 ifTrue:[
-		"/ has item which responds to the mnemonic
-		menu processCollectedShortcutIndices:list.
-		^ self
-	    ].
-	    menu := menu superMenu.
-	].
-	index := self selectionIndex.
-	list  := self
-		    selectItemIndicesFor:accessCharacterMatchQuery
-		    maxDepth:maxShortCutSearchLevel from:(1 + index) to:99999
-		    ignoreSubmenuBlock:[:anItem| anItem ignoreMnemonicKeys ].
+        "first lookup the current grapMenu before starting in the topMenu
+        "
+        menu := self detectGrabMenu.
+
+        [ menu ~~ self ] whileTrue:[
+            index := menu selectionIndex.
+            list  := menu
+                        selectItemIndicesFor:accessCharacterMatchQuery
+                        maxDepth:maxShortCutSearchLevel from:(index + 1) to:99999
+                        ignoreSubmenuBlock:[:anItem| anItem ignoreMnemonicKeys ].
+
+            list size ~~ 0 ifTrue:[
+                "/ has item which responds to the mnemonic
+                menu processCollectedShortcutIndices:list.
+                ^ self
+            ].
+            menu := menu superMenu.
+        ].
+        index := self selectionIndex.
+        list  := self
+                    selectItemIndicesFor:accessCharacterMatchQuery
+                    maxDepth:maxShortCutSearchLevel from:(1 + index) to:99999
+                    ignoreSubmenuBlock:[:anItem| anItem ignoreMnemonicKeys ].
 
     ] ifFalse:[
-	index := 99999.
-	list  := nil.
+        index := 99999.
+        list  := nil.
     ].
 
     list isNil ifTrue:[
-	list := self
-		    selectItemIndicesFor:accessCharacterMatchQuery
-		    maxDepth:maxShortCutSearchLevel from:1 to:index
-		    ignoreSubmenuBlock:[:anItem| anItem ignoreMnemonicKeys ].
-
-
-	list isNil ifTrue:[
-	    "/ must clear existing selection
-	    self selection:nil.
-	    ^ nil
-	]
+        list := self
+                    selectItemIndicesFor:accessCharacterMatchQuery
+                    maxDepth:maxShortCutSearchLevel from:1 to:index
+                    ignoreSubmenuBlock:[:anItem| anItem ignoreMnemonicKeys ].
+
+
+        list isNil ifTrue:[
+            "/ must clear existing selection
+            self selection:nil.
+            ^ nil
+        ]
     ].
 
     "/ has item which responds to the mnemonic
@@ -5107,34 +5112,34 @@
     stop  := aStop  min:(items size).
 
     start to:stop do:[:i|
-	|item menu result|
-
-	item := items at:i.
-	(item enabled and:[item isVisible]) ifTrue:[
-	    (aOneArgBlock value:item) ifTrue:[
-		^ OrderedCollection with:i
-	    ].
-
-	    maxDepth > 1 ifTrue:[
-		(item hasSubmenu and:[item hasDelayedMenu not]) ifTrue:[
-		    (ignoreSubmenueBlock isNil or:[(ignoreSubmenueBlock value:item) not]) ifTrue:[
-			menu := item setupSubmenu.
-
-			(menu notNil and:[menu isEnabled]) ifTrue:[
-			    result := menu
-					selectItemIndicesFor:aOneArgBlock
-					maxDepth:(maxDepth - 1) from:1 to:99999
-					ignoreSubmenuBlock:ignoreSubmenueBlock.
-
-			    result notNil ifTrue:[
-				result addFirst:i.
-				^ result
-			    ].
-			].
-		    ].
-		].
-	    ].
-	].
+        |item menu result|
+
+        item := items at:i.
+        (item enabled and:[item isVisible]) ifTrue:[
+            (aOneArgBlock value:item) ifTrue:[
+                ^ OrderedCollection with:i
+            ].
+
+            maxDepth > 1 ifTrue:[
+                (item hasSubmenu and:[item hasDelayedMenu not]) ifTrue:[
+                    (ignoreSubmenueBlock isNil or:[(ignoreSubmenueBlock value:item) not]) ifTrue:[
+                        menu := item setupSubmenu.
+
+                        (menu notNil and:[menu isEnabled]) ifTrue:[
+                            result := menu
+                                        selectItemIndicesFor:aOneArgBlock
+                                        maxDepth:(maxDepth - 1) from:1 to:99999
+                                        ignoreSubmenuBlock:ignoreSubmenueBlock.
+
+                            result notNil ifTrue:[
+                                result addFirst:i.
+                                ^ result
+                            ].
+                        ].
+                    ].
+                ].
+            ].
+        ].
     ].
     ^ nil
 
@@ -5163,7 +5168,7 @@
     menu := self.
 
     [(smenu := menu superMenu) notNil] whileTrue:[
-	menu := smenu
+        menu := smenu
     ].
     ^ menu
 ! !
@@ -5192,8 +5197,8 @@
     application notNil ifTrue:[^ application ].
 
     superMenu notNil ifTrue:[
-	application := superMenu application.
-	^ application
+        application := superMenu application.
+        ^ application
     ].
     application := super application.
     ^ application
@@ -5203,9 +5208,9 @@
     "returns the item for which aBlock returns true."
 
     items notNil ifTrue:[
-	items keysAndValuesDo:[:anIndex :anItem|
-	    (aBlock value:anItem) ifTrue:[^ anItem].
-	].
+        items keysAndValuesDo:[:anIndex :anItem|
+            (aBlock value:anItem) ifTrue:[^ anItem].
+        ].
     ].
     ^ nil
 !
@@ -5223,28 +5228,28 @@
     lKey := aKey asLowercase.
 
     items keysAndValuesDo:[:anIndex :anItem|
-	|char label|
-
-	(     anIndex ~~ cIdx
-	 and:[anItem canSelect
-	 and:[(label := anItem textLabel) notNil
-	 and:[label size ~~ 0]]]
-	) ifTrue:[
-	    (char := anItem accessCharacter) notNil ifTrue:[
-		(char == uKey or:[char == lKey]) ifTrue:[
-		    ^ anItem
-		]
-	    ] ifFalse:[
-		char := label at:1.
-
-		(char == uKey or:[char == lKey]) ifTrue:[
-		    anIndex > cIdx ifTrue:[
-			^ anItem
-		    ].
-		    item isNil ifTrue:[item := anItem]
-		]
-	    ]
-	]
+        |char label|
+
+        (     anIndex ~~ cIdx
+         and:[anItem canSelect
+         and:[(label := anItem textLabel) notNil
+         and:[label size ~~ 0]]]
+        ) ifTrue:[
+            (char := anItem accessCharacter) notNil ifTrue:[
+                (char == uKey or:[char == lKey]) ifTrue:[
+                    ^ anItem
+                ]
+            ] ifFalse:[
+                char := label at:1.
+
+                (char == uKey or:[char == lKey]) ifTrue:[
+                    anIndex > cIdx ifTrue:[
+                        ^ anItem
+                    ].
+                    item isNil ifTrue:[item := anItem]
+                ]
+            ]
+        ]
     ].
     ^ item
 !
@@ -5261,13 +5266,13 @@
     "on each item perform selector with an argument derived from aList"
 
     aList isCollection ifTrue:[
-	items size >= aList size ifTrue:[
-	    aList keysAndValuesDo:[:anIndex :anArg|
-		(items at:anIndex) perform:aSelector with:anArg
-	    ]
-	]
+        items size >= aList size ifTrue:[
+            aList keysAndValuesDo:[:anIndex :anArg|
+                (items at:anIndex) perform:aSelector with:anArg
+            ]
+        ]
     ] ifFalse:[
-	self do:[:anItem| anItem perform:aSelector with:aList ]
+        self do:[:anItem| anItem perform:aSelector with:aList ]
     ]
 !
 
@@ -5293,9 +5298,9 @@
     superMenu := aSuperMenu.
 
     superMenu notNil ifTrue:[
-	styleSheet       := superMenu styleSheet.
-	rightArrow       := superMenu rightArrow.
-	rightArrowShadow := superMenu rightArrowShadow.
+        styleSheet       := superMenu styleSheet.
+        rightArrow       := superMenu rightArrow.
+        rightArrowShadow := superMenu rightArrowShadow.
     ].
 ! !
 
@@ -5321,8 +5326,8 @@
     "submenu becomes the active menu"
 
     mapTime isNil ifTrue:[
-	"/ set the mapTime if not yet done
-	mapTime := Timestamp now.
+        "/ set the mapTime if not yet done
+        mapTime := Timestamp now.
     ].
     self topMenu activeMenu:self.
 
@@ -5342,7 +5347,7 @@
 "/    ].
 "/
     top activeMenu == self ifTrue:[
-	top activeMenu:nil
+        top activeMenu:nil
     ]
 
     "Created: / 27.2.1998 / 17:41:17 / cg"
@@ -5399,19 +5404,19 @@
     isVert := self verticalLayout.
 
     superView notNil ifTrue:[
-	((first := items first layout) isNil
-	 or:[(last  := items last layout) isNil]
-	) ifTrue:[
-	    ^ false
-	].
-	isVert ifTrue:[
-	    ^ first top < 0 or:[last bottom > height]
-	].
-	^ first left < 0 or:[last right > width]
+        ((first := items first layout) isNil
+         or:[(last  := items last layout) isNil]
+        ) ifTrue:[
+            ^ false
+        ].
+        isVert ifTrue:[
+            ^ first top < 0 or:[last bottom > height]
+        ].
+        ^ first left < 0 or:[last right > width]
     ].
     maxExtent := self maxExtent.
     isVert ifTrue:[
-	^ (height >= maxExtent y)
+        ^ (height >= maxExtent y)
     ].
     ^ (width >= maxExtent x)
 !
@@ -5493,7 +5498,7 @@
      and:[self hasScrollers
      and:[(layout := anItem layout) notNil]]
     ) ifFalse:[
-	^ self
+        ^ self
     ].
     index      := self indexOfItem:anItem.
     boundsPREV := self scrollerBoundsAt:#PREV.
@@ -5502,59 +5507,59 @@
     isVertical := self verticalLayout.
 
     isVertical ifTrue:[
-	boundsMin := boundsPREV bottom.
-	boundsMax := boundsNEXT top.
-	layoutMin := layout top.
-	layoutMax := layout bottom.
-	windowSz  := height.
+        boundsMin := boundsPREV bottom.
+        boundsMax := boundsNEXT top.
+        layoutMin := layout top.
+        layoutMax := layout bottom.
+        windowSz  := height.
     ] ifFalse:[
-	boundsMin := boundsPREV right.
-	boundsMax := boundsNEXT left.
-	layoutMin := layout left.
-	layoutMax := layout right.
-	windowSz  := width.
+        boundsMin := boundsPREV right.
+        boundsMax := boundsNEXT left.
+        layoutMin := layout left.
+        layoutMax := layout right.
+        windowSz  := width.
     ].
 
 
     layoutMin < boundsMin ifTrue:[
-	layoutMin >= 0 ifTrue:[
-	    ^ self
-	].
-	"/ test whether is first visible item
-	index := items findLast:[:el| el isVisible] startingAt:(index - 1).
-
-	index == 0 ifTrue:[ scr0 := margin ]
-		  ifFalse:[ scr0 := boundsMin ].
-
-	delta := layoutMin negated + scr0.
+        layoutMin >= 0 ifTrue:[
+            ^ self
+        ].
+        "/ test whether is first visible item
+        index := items findLast:[:el| el isVisible] startingAt:(index - 1).
+
+        index == 0 ifTrue:[ scr0 := margin ]
+                  ifFalse:[ scr0 := boundsMin ].
+
+        delta := layoutMin negated + scr0.
     ] ifFalse:[
-	layoutMax > boundsMax ifFalse:[
-	    ^ self
-	].
-	"/ test whether is last visible item
-	index  := items findFirst:[:el| el isVisible ] startingAt:(index + 1).
-
-	index == 0 ifTrue:[ scr0 := windowSz - margin ]
-		  ifFalse:[ scr0 := boundsMax ].
-
-	delta := scr0 - layoutMax.
+        layoutMax > boundsMax ifFalse:[
+            ^ self
+        ].
+        "/ test whether is last visible item
+        index  := items findFirst:[:el| el isVisible ] startingAt:(index + 1).
+
+        index == 0 ifTrue:[ scr0 := windowSz - margin ]
+                  ifFalse:[ scr0 := boundsMax ].
+
+        delta := scr0 - layoutMax.
     ].
     delta == 0 ifTrue:[ ^ self ].
 
     doScroll := false.
 
     shown ifTrue:[
-	delta abs < (windowSz / 2) ifTrue:[
-	    doScroll := true.
-	    self repairDamage
-	]
+        delta abs < (windowSz / 2) ifTrue:[
+            doScroll := true.
+            self repairDamage
+        ]
     ].
     isVertical ifTrue:[ dltOrg := 0@delta ] ifFalse:[dltOrg := delta@0].
     items do:[:el| el moveBy:dltOrg ].
 
     doScroll ifFalse:[
-	self invalidate.
-	^ self
+        self invalidate.
+        ^ self
     ].
 
     windowSz  := windowSz - margin - margin.
@@ -5564,37 +5569,37 @@
     scrSz := boundsMax - scr1.
 
     delta < 0 ifTrue:[
-	isVertical ifTrue:[
-	    self copyFrom:self x:margin y:scr1 toX:margin y:scr0
-			   width:windowSz height:scrSz async:false.
-
-	    scr1 := scr0 + scrSz.
-	    inv2 := (margin @ scr1) extent:(windowSz @ (height - scr1 - margin)).
-	    "/ self invalidateX:margin y:scr1 width:windowSz height:(height - scr1 - margin).
-	] ifFalse:[
-	    self copyFrom:self x:scr1 y:margin toX:scr0 y:margin
-			   width:scrSz height:windowSz async:false.
-
-	    scr1 := scr0 + scrSz.
-	    inv2 := (scr1 @ margin) extent:((width - scr1 - margin) @ windowSz).
-	    "/ self invalidateX:scr1 y:margin width:(width - scr1 - margin) height:windowSz.
-	].
-	inv1 := boundsPREV.
+        isVertical ifTrue:[
+            self copyFrom:self x:margin y:scr1 toX:margin y:scr0
+                           width:windowSz height:scrSz async:false.
+
+            scr1 := scr0 + scrSz.
+            inv2 := (margin @ scr1) extent:(windowSz @ (height - scr1 - margin)).
+            "/ self invalidateX:margin y:scr1 width:windowSz height:(height - scr1 - margin).
+        ] ifFalse:[
+            self copyFrom:self x:scr1 y:margin toX:scr0 y:margin
+                           width:scrSz height:windowSz async:false.
+
+            scr1 := scr0 + scrSz.
+            inv2 := (scr1 @ margin) extent:((width - scr1 - margin) @ windowSz).
+            "/ self invalidateX:scr1 y:margin width:(width - scr1 - margin) height:windowSz.
+        ].
+        inv1 := boundsPREV.
     ] ifFalse:[
-	isVertical ifTrue:[
-	    self copyFrom:self x:margin y:scr0 toX:margin y:scr1
-			   width:windowSz height:scrSz async:false.
-
-	    inv2 := (margin @ margin) extent:(windowSz @ (scr1 - margin)).
-	    "/ self invalidateX:margin y:margin width:windowSz height:scr1 - margin.
-	] ifFalse:[
-	    self copyFrom:self x:scr0 y:margin toX:scr1 y:margin
-			   width:scrSz height:windowSz async:false.
-
-	    inv2 := (margin @ margin) extent:(scr1 - margin) @ windowSz.
-	    "/ self invalidateX:margin y:margin width:scr1 - margin height:windowSz.
-	].
-	inv1 := boundsNEXT.
+        isVertical ifTrue:[
+            self copyFrom:self x:margin y:scr0 toX:margin y:scr1
+                           width:windowSz height:scrSz async:false.
+
+            inv2 := (margin @ margin) extent:(windowSz @ (scr1 - margin)).
+            "/ self invalidateX:margin y:margin width:windowSz height:scr1 - margin.
+        ] ifFalse:[
+            self copyFrom:self x:scr0 y:margin toX:scr1 y:margin
+                           width:scrSz height:windowSz async:false.
+
+            inv2 := (margin @ margin) extent:(scr1 - margin) @ windowSz.
+            "/ self invalidateX:margin y:margin width:scr1 - margin height:windowSz.
+        ].
+        inv1 := boundsNEXT.
     ].
     self invalidate:inv1.
     self invalidate:inv2.
@@ -5665,10 +5670,10 @@
      for a menu and all contained submenus"
 
     superMenu notNil ifTrue:[
-	^ superMenu scrollActivity
+        ^ superMenu scrollActivity
     ].
     scrollActivity isNil ifTrue:[
-	scrollActivity := ScrollActivity new.
+        scrollActivity := ScrollActivity new.
     ].
     ^ scrollActivity
 !
@@ -5784,9 +5789,9 @@
     |subMenu|
 
     selection notNil ifTrue:[
-	(subMenu := selection visibleSubmenu) notNil ifTrue:[
-	    ^ subMenu detectGrabMenu
-	]
+        (subMenu := selection visibleSubmenu) notNil ifTrue:[
+            ^ subMenu detectGrabMenu
+        ]
     ].
     ^ self
 !
@@ -5799,11 +5804,11 @@
     dstPoint := self translateGrabPoint:aGrabPoint.
 
     ((dstPoint x between:0 and:width) and:[dstPoint y between:0 and:height]) ifTrue:[
-	firstMenu := self.
+        firstMenu := self.
     ].
 
     (selection isNil or:[(dstMenu := selection visibleSubmenu) isNil]) ifTrue:[
-	^ firstMenu
+        ^ firstMenu
     ].
     dstMenu := dstMenu detectMenuAtGrabPoint:aGrabPoint.
     ^ dstMenu ? firstMenu
@@ -5816,7 +5821,7 @@
     |idx|
 
     stringOrNumberOrPoint isPoint ifTrue:[
-	^ self itemAtPoint:stringOrNumberOrPoint
+        ^ self itemAtPoint:stringOrNumberOrPoint
     ].
     idx := self indexOf:stringOrNumberOrPoint.
     (idx > 0 and:[idx <= items size]) ifTrue:[ ^ items at:idx ].
@@ -5829,9 +5834,9 @@
     |x y|
 
     items notNil ifTrue:[
-	x := aPoint x.
-	y := aPoint y.
-	^ items detect:[:el| el containsPointX:x y:y] ifNone:nil
+        x := aPoint x.
+        y := aPoint y.
+        ^ items detect:[:el| el containsPointX:x y:y] ifNone:nil
     ].
     ^ nil
 !
@@ -5842,16 +5847,16 @@
     |grabPoint superMenu|
 
     (self containsPoint:aPoint) ifTrue:[
-	^ self
+        ^ self
     ].
 
     grabPoint := aPoint - (self translateGrabPoint:0).
     superMenu := self.
 
     [ (superMenu := superMenu superMenu) notNil ] whileTrue:[
-	(superMenu containsPoint:(superMenu translateGrabPoint:grabPoint)) ifTrue:[
-	    ^ superMenu
-	]
+        (superMenu containsPoint:(superMenu translateGrabPoint:grabPoint)) ifTrue:[
+            ^ superMenu
+        ]
     ].
     ^ nil
 
@@ -5863,8 +5868,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
     ].
 !
 
@@ -5962,23 +5967,23 @@
     |b|
 
     superMenu notNil ifTrue:[
-	superMenu openDelayed:anItemOrNil afterSeconds:seconds.
-	^ self
+        superMenu openDelayed:anItemOrNil afterSeconds:seconds.
+        ^ self
     ].
     (b := openDelayedMenuBlock notNil) ifTrue:[
-	openDelayedMenuBlock := nil.
-	Processor removeTimedBlock:b.
+        openDelayedMenuBlock := nil.
+        Processor removeTimedBlock:b.
     ].
     (anItemOrNil notNil and:[anItemOrNil hasSubmenu]) ifFalse:[
-	openDelayedMenuBlock := nil.
-	^ self
+        openDelayedMenuBlock := nil.
+        ^ self
     ].
 
     openDelayedMenuBlock :=
-	[
-	    openDelayedMenuBlock := nil.
-	    anItemOrNil openDelayedSubmenu
-	].
+        [
+            openDelayedMenuBlock := nil.
+            anItemOrNil openDelayedSubmenu
+        ].
 
     Processor addTimedBlock:openDelayedMenuBlock afterSeconds:seconds.
 
@@ -5994,12 +5999,12 @@
     "/ self openDelayed:nil.
 
     (b := closeDelayedMenuBlock notNil) ifTrue:[
-	closeDelayedMenuBlock := nil.
-	Processor removeTimedBlock:b.
+        closeDelayedMenuBlock := nil.
+        Processor removeTimedBlock:b.
     ].
     (b := openDelayedMenuBlock notNil) ifTrue:[
-	openDelayedMenuBlock := nil.
-	Processor removeTimedBlock:b.
+        openDelayedMenuBlock := nil.
+        Processor removeTimedBlock:b.
     ].
 
     delayedOpenSeconds := self delayInSecondsBeforeOpeningSubmenu.
@@ -6010,24 +6015,24 @@
 
     "/ redraw current selection cleared
     oldSelect notNil ifTrue:[
-	|oldSubmenu|
-
-	oldSubmenu := oldSelect visibleSubmenu.
-	oldSubmenu notNil ifTrue:[
-	    "/ if the new item has a submenu, any current submenu will be closed, when that
-	    "/ one eventuall opens. However, if it is a simple item,
-	    "/ it would remain open. So schedule a delayed close action for it.
-	    closeDelayedMenuBlock :=
-		[
-		    "/ but only if we have not reentered the item with the submenu we want to close
-		    selection ~~ oldSelect ifTrue:[
-			(oldSelect hasSubmenu
-			and:[ oldSelect visibleSubmenu notNil ]) ifTrue:[
-			    oldSelect hideSubmenu.
-			].
-		    ].
-		].
-	    Processor addTimedBlock:closeDelayedMenuBlock afterSeconds:delayedOpenSeconds.
+        |oldSubmenu|
+
+        oldSubmenu := oldSelect visibleSubmenu.
+        oldSubmenu notNil ifTrue:[
+            "/ if the new item has a submenu, any current submenu will be closed, when that
+            "/ one eventuall opens. However, if it is a simple item,
+            "/ it would remain open. So schedule a delayed close action for it.
+            closeDelayedMenuBlock :=
+                [
+                    "/ but only if we have not reentered the item with the submenu we want to close
+                    selection ~~ oldSelect ifTrue:[
+                        (oldSelect hasSubmenu
+                        and:[ oldSelect visibleSubmenu notNil ]) ifTrue:[
+                            oldSelect hideSubmenu.
+                        ].
+                    ].
+                ].
+            Processor addTimedBlock:closeDelayedMenuBlock afterSeconds:delayedOpenSeconds.
 "/ mhmh - seems to not only not needed, but actually hurting (leftover menus)
 "/            Processor addTimedBlock:[
 "/                selection ~~ anItemOrNil ifTrue:[
@@ -6043,34 +6048,34 @@
 "/                    ].
 "/                ].
 "/            ] afterSeconds:delayedOpenSeconds.
-	].
-	oldSelect invalidate.
+        ].
+        oldSelect invalidate.
     ].
 
     anItemOrNil notNil ifTrue:[
-	self makeItemVisible:anItemOrNil.
-	anItemOrNil canSelect ifTrue:[
-	    selection := anItemOrNil
-	].
+        self makeItemVisible:anItemOrNil.
+        anItemOrNil canSelect ifTrue:[
+            selection := anItemOrNil
+        ].
     ].
     selection isNil ifTrue:[^ self].
 
     ActiveHelp isActive ifTrue:[
-	helpListener := ActiveHelp currentHelpListener.
-	helpListener initiateHelpFor:self at:nil now:true.
+        helpListener := ActiveHelp currentHelpListener.
+        helpListener initiateHelpFor:self at:nil now:true.
     ].
 
     shown ifTrue:[
-	"/ self rearrangeItems.
-	selection invalidate.
-	selection hasSubmenu ifTrue:[
-	    "/ cg: disabled: prevents delayed menu when moving over a separator item
-	    false "(oldSelect isNil or:[oldSelect visibleSubmenu isNil])" ifTrue:[
-		self openDelayed:selection afterSeconds:0.
-	    ] ifFalse:[
-		self openDelayed:selection afterSeconds:delayedOpenSeconds.
-	    ]
-	].
+        "/ self rearrangeItems.
+        selection invalidate.
+        selection hasSubmenu ifTrue:[
+            "/ cg: disabled: prevents delayed menu when moving over a separator item
+            false "(oldSelect isNil or:[oldSelect visibleSubmenu isNil])" ifTrue:[
+                self openDelayed:selection afterSeconds:0.
+            ] ifFalse:[
+                self openDelayed:selection afterSeconds:delayedOpenSeconds.
+            ]
+        ].
     ].
 
     "Modified: / 29-08-2013 / 09:44:06 / cg"
@@ -6091,29 +6096,29 @@
     selection == anItemOrNil ifTrue:[^ self].
 
     (anItemOrNil isNil or:[anItemOrNil hasSubmenu not]) ifTrue:[
-	self selection:anItemOrNil openMenu:false.
-	^ self
+        self selection:anItemOrNil openMenu:false.
+        ^ self
     ].
 
     openMenu     := self isPopUpView not.
     openOnSelect := styleSheet at:#'menu.openOnSelect' default:false.
 
     openMenu ifFalse:[
-	openMenu := openOnSelect.
+        openMenu := openOnSelect.
     ].
     self selection:anItemOrNil openMenu:openMenu.
 
     openOnSelect ifFalse:[
-	"/ select first item in submenu
-
-	submenu := anItemOrNil currentSubmenu.
-
-	submenu notNil ifTrue:[
-	    item := submenu itemAt:1.
-	    (item notNil and:[item hasSubmenu not]) ifTrue:[
-		submenu selection:item openMenu:false
-	    ]
-	].
+        "/ select first item in submenu
+
+        submenu := anItemOrNil currentSubmenu.
+
+        submenu notNil ifTrue:[
+            item := submenu itemAt:1.
+            (item notNil and:[item hasSubmenu not]) ifTrue:[
+                submenu selection:item openMenu:false
+            ]
+        ].
     ].
 !
 
@@ -6123,7 +6128,7 @@
     |helpListener oldSelect|
 
     anItemOrNil == selection ifTrue:[
-	^ self
+        ^ self
     ].
     self openDelayed:nil.
 
@@ -6131,19 +6136,19 @@
     selection := nil.
 
     anItemOrNil notNil ifTrue:[
-	self makeItemVisible:anItemOrNil.
-	anItemOrNil canSelect ifTrue:[
-	    selection := anItemOrNil
-	] ifFalse:[
-	    oldSelect isNil ifTrue:[^ self].
-	].
+        self makeItemVisible:anItemOrNil.
+        anItemOrNil canSelect ifTrue:[
+            selection := anItemOrNil
+        ] ifFalse:[
+            oldSelect isNil ifTrue:[^ self].
+        ].
     ].
     oldSelect notNil ifTrue:[
-	"/ clear current selection
-	oldSelect isSelected:false.
+        "/ clear current selection
+        oldSelect isSelected:false.
     ].
     selection isNil ifTrue:[
-	^ self
+        ^ self
     ].
 
 "/    selection == enteredItem ifTrue:[
@@ -6152,18 +6157,18 @@
 "/        self pointerEntersItem:nil
 "/    ].
     ActiveHelp isActive ifTrue:[
-	helpListener := ActiveHelp currentHelpListener.
-	helpListener initiateHelpFor:self at:nil now:true.
+        helpListener := ActiveHelp currentHelpListener.
+        helpListener initiateHelpFor:self at:nil now:true.
     ].
     shown ifTrue:[
-	"/ self rearrangeItems.
-
-	openMenu ifFalse:[
-	    selection invalidate.
-	]
+        "/ self rearrangeItems.
+
+        openMenu ifFalse:[
+            selection invalidate.
+        ]
     ].
     openMenu ifTrue:[
-	selection isSelected:true.
+        selection isSelected:true.
     ].
 !
 
@@ -6173,7 +6178,7 @@
     |item|
 
     (item := self selection) notNil ifTrue:[
-	^ self findFirst:[:el| el == item ]
+        ^ self findFirst:[:el| el == item ]
     ].
     ^ 0
 !
@@ -6190,18 +6195,18 @@
     "translate the grab point into self"
 
     superMenu isNil ifTrue:[
-	"I am the grabView"
-	aGrabPoint isNumber ifTrue:[^ aGrabPoint @ aGrabPoint].
-	^ aGrabPoint
+        "I am the grabView"
+        aGrabPoint isNumber ifTrue:[^ aGrabPoint @ aGrabPoint].
+        ^ aGrabPoint
     ].
 
     relativeGrabOrigin isNil ifTrue:[
-	relativeGrabOrigin := self topMenu translatePoint:0 to:self.
-	relativeGrabOrigin isNil ifTrue:[
-	    "I am the grabView"
-	    aGrabPoint isNumber ifTrue:[^ aGrabPoint @ aGrabPoint].
-	    ^ aGrabPoint
-	].
+        relativeGrabOrigin := self topMenu translatePoint:0 to:self.
+        relativeGrabOrigin isNil ifTrue:[
+            "I am the grabView"
+            aGrabPoint isNumber ifTrue:[^ aGrabPoint @ aGrabPoint].
+            ^ aGrabPoint
+        ].
     ].
     ^ relativeGrabOrigin + aGrabPoint
 !
@@ -6212,7 +6217,7 @@
     |grapPoint|
 
     aMenu == self ifTrue:[
-	^ aPoint
+        ^ aPoint
     ].
     grapPoint := aPoint - (self translateGrabPoint:0).
 
@@ -6325,13 +6330,13 @@
     |arg|
 
     indication notNil ifTrue:[
-	arg := self indicationValue not.
-	self indicationValue:arg.
+        arg := self indicationValue not.
+        self indicationValue:arg.
     ] ifFalse:[
-	(choice notNil and:[choice isValueModel])ifTrue:[
-	    choice value:(menuItem choiceValue).
-	    ^ true
-	].
+        (choice notNil and:[choice isValueModel])ifTrue:[
+            choice value:(menuItem choiceValue).
+            ^ true
+        ].
     ].
     ^ arg
 ! !
@@ -6380,12 +6385,12 @@
     |myFont prevFont w h|
 
     displayLabelExtent notNil ifTrue:[
-	^ displayLabelExtent
+        ^ displayLabelExtent
     ].
 
     displayLabel isNil ifTrue:[
-	displayLabelExtent := 0@0.
-	^ displayLabelExtent
+        displayLabelExtent := 0@0.
+        ^ displayLabelExtent
     ].
 
     myFont := self font.
@@ -6395,33 +6400,33 @@
     prevFont := menuPanel setFont:myFont.
 
     displayLabel isString ifTrue:[
-	w := displayLabel widthOn:menuPanel.
-	h := displayLabel heightOn:menuPanel.
+        w := displayLabel widthOn:menuPanel.
+        h := displayLabel heightOn:menuPanel.
 "/        w := myFont widthOf:displayLabel.
 "/        h := myFont heightOf:displayLabel.
     ] ifFalse:[
-	displayLabel isArray ifTrue:[
-	    w := h := 0.
-
-	    displayLabel do:[:aSubLabel|
-		aSubLabel notNil ifTrue:[
-		    w := w max:(aSubLabel widthOn:menuPanel).
-		    h := h + 1 + (aSubLabel heightOn:menuPanel).
-		] ifFalse:[
-		    h := h + (self spaceBetweenEmptyLines)
-		]
-	    ]
-	] ifFalse:[
-	    w := displayLabel widthOn:menuPanel.
-	    h := displayLabel heightOn:menuPanel.
-	].
+        displayLabel isArray ifTrue:[
+            w := h := 0.
+
+            displayLabel do:[:aSubLabel|
+                aSubLabel notNil ifTrue:[
+                    w := w max:(aSubLabel widthOn:menuPanel).
+                    h := h + 1 + (aSubLabel heightOn:menuPanel).
+                ] ifFalse:[
+                    h := h + (self spaceBetweenEmptyLines)
+                ]
+            ]
+        ] ifFalse:[
+            w := displayLabel widthOn:menuPanel.
+            h := displayLabel heightOn:menuPanel.
+        ].
     ].
 
     menuPanel setFont:prevFont.     "/ restore previous font
 
     "/ care for italic fonts - give a few more pixels at the end
     myFont italic ifTrue:[
-	w := w + 2.
+        w := w + 2.
     ].
     displayLabelExtent := w@h.
     ^ displayLabelExtent
@@ -6439,8 +6444,8 @@
     font := menuItem font.
 
     font notNil ifTrue:[
-	font := font onDevice:(menuPanel device).
-	menuItem font:font.
+        font := font onDevice:(menuPanel device).
+        menuItem font:font.
     ].
     ^ font
 !
@@ -6513,57 +6518,57 @@
     displayLabel       := label value ? ''.
 
     displayLabel isString ifTrue:[
-	"CHECK FOR SEPARATOR"
-
-	(menuItem isButton not and:[indication isNil and:[choice isNil]]) ifTrue:[
-	    size := displayLabel size.
-
-	    size == 0 ifTrue:[
-		displayLabel := nil.            "blank separator"
-		^ self
-	    ].
-
-	    size == 1 ifTrue:[
-		char := displayLabel first.
-
-		(char == $- or:[char == $=]) ifTrue:[
-		    label := displayLabel.      "line separator"
-		    displayLabel := nil.
-		    ^ self
-		]
-	    ]
-	]
+        "CHECK FOR SEPARATOR"
+
+        (menuItem isButton not and:[indication isNil and:[choice isNil]]) ifTrue:[
+            size := displayLabel size.
+
+            size == 0 ifTrue:[
+                displayLabel := nil.            "blank separator"
+                ^ self
+            ].
+
+            size == 1 ifTrue:[
+                char := displayLabel first.
+
+                (char == $- or:[char == $=]) ifTrue:[
+                    label := displayLabel.      "line separator"
+                    displayLabel := nil.
+                    ^ self
+                ]
+            ]
+        ]
     ] ifFalse:[
-	displayLabel isCollection ifTrue:[
-	    displayLabel := displayLabel asArray.
-	]
+        displayLabel isCollection ifTrue:[
+            displayLabel := displayLabel asArray.
+        ]
     ].
     menuPanel notNil ifTrue:[
-	menuPanel doAccessCharacterTranslation ifTrue:[
-	    displayLabel notNil ifTrue:[
-		displayLabel isArray ifTrue:[
-		    displayLabel keysAndValuesDo:[:i :el|
-			el notNil ifTrue:[
-			    displayLabel at:i put:(self updateAccessCharacterFor:el).
-			].
-		    ].
-		] ifFalse:[
-		    displayLabel isImageOrForm ifFalse:[
-			displayLabel := self updateAccessCharacterFor:displayLabel.
-		    ].
-		].
-	    ].
-	].
-
-	menuPanel shown ifTrue:[
-	    self fetchImages.
-
-	    oldExtent = self displayLabelExtent ifTrue:[
-		self invalidate
-	    ] ifFalse:[
-		menuPanel mustRearrange
-	    ]
-	].
+        menuPanel doAccessCharacterTranslation ifTrue:[
+            displayLabel notNil ifTrue:[
+                displayLabel isArray ifTrue:[
+                    displayLabel keysAndValuesDo:[:i :el|
+                        el notNil ifTrue:[
+                            displayLabel at:i put:(self updateAccessCharacterFor:el).
+                        ].
+                    ].
+                ] ifFalse:[
+                    displayLabel isImageOrForm ifFalse:[
+                        displayLabel := self updateAccessCharacterFor:displayLabel.
+                    ].
+                ].
+            ].
+        ].
+
+        menuPanel shown ifTrue:[
+            self fetchImages.
+
+            oldExtent = self displayLabelExtent ifTrue:[
+                self invalidate
+            ] ifFalse:[
+                menuPanel mustRearrange
+            ]
+        ].
     ].
 
     "Modified: / 06-10-2011 / 16:36:53 / cg"
@@ -6608,8 +6613,8 @@
      no submenu exists evaluate the action assigned to the item (accept)."
 
     menuItem shortcutKey ~= aKey ifTrue:[
-	menuItem shortcutKey:aKey.
-	self invalidate.
+        menuItem shortcutKey:aKey.
+        self invalidate.
     ].
 !
 
@@ -6651,59 +6656,59 @@
     |widget|
 
     subMenu notNil ifTrue:[
-	subMenu ~~ aSubMenu ifTrue:[
-	    subMenu destroy.
-	    subMenu := nil.
-	].
+        subMenu ~~ aSubMenu ifTrue:[
+            subMenu destroy.
+            subMenu := nil.
+        ].
     ].
 
     aSubMenu isNil ifTrue:[
-	subMenu notNil ifTrue:[
-	    subMenu destroy.
-	    subMenu := nil.
-	].
-	^ self
+        subMenu notNil ifTrue:[
+            subMenu destroy.
+            subMenu := nil.
+        ].
+        ^ self
     ].
 
     (aSubMenu isKindOf:Menu) ifTrue:[
-	subMenu := MenuPanel new.
-
-	menuPanel notNil ifTrue:[
-	    subMenu receiver:menuPanel receiver.
-	].
-	subMenu superMenu:menuPanel.
-
-	menuItem horizontalLayout == true ifTrue:[
-	    subMenu verticalLayout:false
-	].
-	subMenu menu:aSubMenu.
+        subMenu := MenuPanel new.
+
+        menuPanel notNil ifTrue:[
+            subMenu receiver:menuPanel receiver.
+        ].
+        subMenu superMenu:menuPanel.
+
+        menuItem horizontalLayout == true ifTrue:[
+            subMenu verticalLayout:false
+        ].
+        subMenu menu:aSubMenu.
     ] ifFalse:[
-	aSubMenu isView ifFalse:[
-	    (aSubMenu isKindOf:ApplicationModel) ifFalse:[
-		"/ ... mhhhh ....
-		^ menuItem submenuChannel:aSubMenu
-	    ].
-	    widget := SimpleView new.
-	    widget client:aSubMenu.
-	] ifTrue:[
-	    widget := aSubMenu.
-	    subMenu perform:#superMenu: with:menuPanel ifNotUnderstood:[].
-	].
-
-	(widget isKindOf:MenuPanel) ifTrue:[
-	    subMenu := widget.
-
-	    menuItem horizontalLayout == true ifTrue:[
-		subMenu verticalLayout:false
-	    ].
-	] ifFalse:[
-	    subMenu := MenuPanel new.
-	    subMenu receiver:menuPanel receiver.
-	    subMenu addSubView:widget.
-	    subMenu extent:(widget preferredExtent).
-	    widget origin:0.0@0.0 corner:1.0@1.0.
-	].
-	subMenu superMenu:menuPanel.
+        aSubMenu isView ifFalse:[
+            (aSubMenu isKindOf:ApplicationModel) ifFalse:[
+                "/ ... mhhhh ....
+                ^ menuItem submenuChannel:aSubMenu
+            ].
+            widget := SimpleView new.
+            widget client:aSubMenu.
+        ] ifTrue:[
+            widget := aSubMenu.
+            subMenu perform:#superMenu: with:menuPanel ifNotUnderstood:[].
+        ].
+
+        (widget isKindOf:MenuPanel) ifTrue:[
+            subMenu := widget.
+
+            menuItem horizontalLayout == true ifTrue:[
+                subMenu verticalLayout:false
+            ].
+        ] ifFalse:[
+            subMenu := MenuPanel new.
+            subMenu receiver:menuPanel receiver.
+            subMenu addSubView:widget.
+            subMenu extent:(widget preferredExtent).
+            widget origin:0.0@0.0 corner:1.0@1.0.
+        ].
+        subMenu superMenu:menuPanel.
     ].
 !
 
@@ -6722,15 +6727,15 @@
     |txt|
 
     displayLabel notNil ifTrue:[
-	displayLabel isArray ifFalse:[
-	    ^ displayLabel perform:#string ifNotUnderstood:nil
-	].
-
-	displayLabel do:[:el|
-	    (txt := el perform:#string ifNotUnderstood:nil) notNil ifTrue:[
-		^ txt
-	    ]
-	].
+        displayLabel isArray ifFalse:[
+            ^ displayLabel perform:#string ifNotUnderstood:nil
+        ].
+
+        displayLabel do:[:el|
+            (txt := el perform:#string ifNotUnderstood:nil) notNil ifTrue:[
+                ^ txt
+            ]
+        ].
     ].
     ^ nil
 !
@@ -6739,7 +6744,7 @@
     "return true if triggering the action if pressed"
 
     menuItem triggerOnDown ifTrue:[
-	self hasSubmenu ifFalse:[^ true].
+        self hasSubmenu ifFalse:[^ true].
     ].
     ^ false
 !
@@ -6787,17 +6792,17 @@
     choice == something ifTrue:[^ self].
 
     choice isValueModel ifTrue:[
-	choice removeDependent:self
+        choice removeDependent:self
     ].
 
     choice := something.
     choice notNil ifTrue:[
-	choice isSymbol ifTrue:[
-	    choice := (self aspectAt:choice) ? choice.
-	].
-	choice isValueModel ifTrue:[
-	    choice addDependent:self
-	]
+        choice isSymbol ifTrue:[
+            choice := (self aspectAt:choice) ? choice.
+        ].
+        choice isValueModel ifTrue:[
+            choice addDependent:self
+        ]
     ].
 !
 
@@ -6811,8 +6816,8 @@
     "implements a radio group; the value writen to the choice if selected"
 
     menuItem choiceValue ~= something ifTrue:[
-	menuItem choiceValue:something.
-	choice notNil ifTrue:[ self invalidate ].
+        menuItem choiceValue:something.
+        choice notNil ifTrue:[ self invalidate ].
     ].
 !
 
@@ -6894,7 +6899,7 @@
     and:[ app notNil
     and:[ app askFor:#isUIPainter]])
     ifTrue:[
-	^ self "/ suppressed
+        ^ self "/ suppressed
     ].
     aMessage infoPrint.
 "/    app notNil ifTrue:[
@@ -6915,16 +6920,16 @@
     indication == aValueHolder ifTrue:[^ self].
 
     indication isValueModel ifTrue:[
-	indication removeDependent:self
+        indication removeDependent:self
     ].
 
     (indication := aValueHolder) notNil ifTrue:[
-	indication isValueModel ifTrue:[
-	    indication addDependent:self
-	] ifFalse:[
-	    "/ to force an update of the value
-	    self indicationValue
-	]
+        indication isValueModel ifTrue:[
+            indication addDependent:self
+        ] ifFalse:[
+            "/ to force an update of the value
+            self indicationValue
+        ]
     ].
 !
 
@@ -6987,12 +6992,12 @@
     isButton := menuItem isButton.
 
     isButton ifTrue:[
-	s := menuPanel maxAbsoluteButtonLevel ? 0.
-	x := s + HorizontalButtonInset.
-	y := s + VerticalButtonInset.
+        s := menuPanel maxAbsoluteButtonLevel ? 0.
+        x := s + HorizontalButtonInset.
+        y := s + VerticalButtonInset.
     ] ifFalse:[
-	x  := HorizontalInset.
-	y  := (menuPanel isPopUpView ifTrue:[VerticalPopUpInset] ifFalse:[VerticalInset]) ? 2.
+        x  := HorizontalInset.
+        y  := (menuPanel isPopUpView ifTrue:[VerticalPopUpInset] ifFalse:[VerticalInset]) ? 2.
     ].
     x := x * 2.
     y := y * 2.
@@ -7000,43 +7005,43 @@
     isVertical := menuPanel verticalLayout.
 
     self isSeparator ifTrue:[
-	s := self class separatorSize.
-	label = '' ifTrue:[
-	    s := self class halfSeparatorSize.
-	].
-
-	"width of doubleSeparator is 5 !!!!"
-	isVertical ifFalse:[
-	    x := x max:s.
-	    y := y + 5.
-	] ifTrue:[
-	    y := y max:s.
-	    x := x + 5.
-	].
+        s := self class separatorSize.
+        label = '' ifTrue:[
+            s := self class halfSeparatorSize.
+        ].
+
+        "width of doubleSeparator is 5 !!!!"
+        isVertical ifFalse:[
+            x := x max:s.
+            y := y + 5.
+        ] ifTrue:[
+            y := y max:s.
+            x := x + 5.
+        ].
     ] ifFalse:[
-	labelExtent := self displayLabelExtent.
-
-	x := x + labelExtent x.
-	y := y + labelExtent y.
-	x := x + (menuPanel stringOffsetXfor:self).
-
-	isButton ifFalse:[
-	    menuPanel showSeparatingLines ifTrue:[
-		"width of separator is 2 plus right offset 1 := 3"
-		isVertical ifFalse:[x := x + 3] ifTrue:[y := y + 3].
-	    ].
-	].
-	wIcon := 0.
-	self hasMenuIndicator ifTrue:[
-	    icon := MenuPanel menuIndicator.
-	    wIcon := MenuPanel menuIndicatorOffset + icon width.
-	] ifFalse:[
-	    self hasDelayedMenuIndicator ifTrue:[
-		icon := MenuPanel delayedMenuIndicator.
-		wIcon := MenuPanel delayedMenuIndicatorOffset + icon width.
-	    ]
-	].
-	x := x + wIcon.
+        labelExtent := self displayLabelExtent.
+
+        x := x + labelExtent x.
+        y := y + labelExtent y.
+        x := x + (menuPanel stringOffsetXfor:self).
+
+        isButton ifFalse:[
+            menuPanel showSeparatingLines ifTrue:[
+                "width of separator is 2 plus right offset 1 := 3"
+                isVertical ifFalse:[x := x + 3] ifTrue:[y := y + 3].
+            ].
+        ].
+        wIcon := 0.
+        self hasMenuIndicator ifTrue:[
+            icon := MenuPanel menuIndicator.
+            wIcon := MenuPanel menuIndicatorOffset + icon width.
+        ] ifFalse:[
+            self hasDelayedMenuIndicator ifTrue:[
+                icon := MenuPanel delayedMenuIndicator.
+                wIcon := MenuPanel delayedMenuIndicatorOffset + icon width.
+            ]
+        ].
+        x := x + wIcon.
     ].
     ^ x@y
 
@@ -7249,8 +7254,8 @@
     "set/clear the item to look like a Button"
 
     menuItem isButton ~~ aBool ifTrue:[
-	menuItem isButton:aBool.
-	self invalidate.
+        menuItem isButton:aBool.
+        self invalidate.
     ]
 !
 
@@ -7304,22 +7309,22 @@
     aSubmenu removeDependencies.
 
     aSubmenu realized ifFalse:[
-	id := aSubmenu id.
-	id notNil ifTrue:[ menuPanel device unmapWindow:id ]
+        id := aSubmenu id.
+        id notNil ifTrue:[ menuPanel device unmapWindow:id ]
     ] ifTrue:[
-	aSubmenu hide
+        aSubmenu hide
     ].
 
     aSubmenu windowGroup:nil.
     (wg := menuPanel windowGroup) notNil ifTrue:[
-	wg removeView:aSubmenu.
+        wg removeView:aSubmenu.
     ].
 
     "/ release menu if derived from channel
     (subMenu == aSubmenu and:[menuItem submenuChannel notNil]) ifTrue:[
-	menuItem keepLinkedMenu ifFalse:[
-	    subMenu := nil
-	]
+        menuItem keepLinkedMenu ifFalse:[
+            subMenu := nil
+        ]
     ].
 !
 
@@ -7482,13 +7487,13 @@
     "toggle the visibility of the submenu"
 
     subMenu notNil ifTrue:[
-	subMenu shown ifTrue:[^ self hideSubmenu]
+        subMenu shown ifTrue:[^ self hideSubmenu]
     ] ifFalse:[
-	self setupSubmenu.
-	subMenu isNil ifTrue:[
-	    "/ cannot open a submenu
-	    ^ self
-	]
+        self setupSubmenu.
+        subMenu isNil ifTrue:[
+            "/ cannot open a submenu
+            ^ self
+        ]
     ].
     self openSubmenu.
 
@@ -7499,7 +7504,7 @@
     "returns the current visible submenu or nil"
 
     subMenu notNil ifTrue:[
-	subMenu shown ifTrue:[^ subMenu].
+        subMenu shown ifTrue:[^ subMenu].
     ].
     ^ nil
 ! !
@@ -7553,11 +7558,11 @@
     "called whenever the font changed"
 
     displayLabel notNil ifTrue:[
-	displayLabelExtent := nil.
-
-	subMenu notNil ifTrue:[
-	    subMenu font:(menuPanel font).
-	].
+        displayLabelExtent := nil.
+
+        subMenu notNil ifTrue:[
+            subMenu font:(menuPanel font).
+        ].
     ].
 !
 
@@ -7568,46 +7573,46 @@
     (menuPanel isNil or:[layout isNil]) ifTrue:[^ self].        "/ not yet realized or computed
 
     self isSeparator ifFalse:[
-	"/ NOT A SEPARATOR
-
-	menuPanel shown ifTrue:[
-	    changedObject == enableChannel ifTrue:[
-		(enableChannel value == false and:[self isSelected]) ifTrue:[
-		    ^ menuPanel selection:nil.
-		].
-		^ self invalidate
-	    ].
-
-	    (changedObject == indication or:[changedObject == choice]) ifTrue:[
-		menuItem isButton ifTrue:[
-		    self invalidate
-		] ifFalse:[
-		    "/ invalidate the interactor only
-		    "/ take any interactor; interactors has the same extent
-		    form := menuPanel iconIndicationOff.
-
-		    rect := Rectangle left:(layout left + HorizontalInset)
-				       top:(layout top)
-				     width:(form width)
-				    height:(layout height).
-
-		    menuPanel invalidate:rect repairNow:false
-		].
-		^ self
-	    ].
-	    self invalidate.
-	].
+        "/ NOT A SEPARATOR
+
+        menuPanel shown ifTrue:[
+            changedObject == enableChannel ifTrue:[
+                (enableChannel value == false and:[self isSelected]) ifTrue:[
+                    ^ menuPanel selection:nil.
+                ].
+                ^ self invalidate
+            ].
+
+            (changedObject == indication or:[changedObject == choice]) ifTrue:[
+                menuItem isButton ifTrue:[
+                    self invalidate
+                ] ifFalse:[
+                    "/ invalidate the interactor only
+                    "/ take any interactor; interactors has the same extent
+                    form := menuPanel iconIndicationOff.
+
+                    rect := Rectangle left:(layout left + HorizontalInset)
+                                       top:(layout top)
+                                     width:(form width)
+                                    height:(layout height).
+
+                    menuPanel invalidate:rect repairNow:false
+                ].
+                ^ self
+            ].
+            self invalidate.
+        ].
     ].
 
     changedObject == isVisible ifTrue:[
-	menuPanel mustRearrange.
-	"/ actually: the following is wrong, because we have to delay the rearrangement
-	"/ until the next redraw event comes. Otherwise, we might compute new layouts
-	"/ too early if more items change their visibility.
-	"/ redraw will call rearrangeItems, if the mustRearrange is set.
-
-	"/ menuPanel rearrangeItems.
-	^ self.
+        menuPanel mustRearrange.
+        "/ actually: the following is wrong, because we have to delay the rearrangement
+        "/ until the next redraw event comes. Otherwise, we might compute new layouts
+        "/ too early if more items change their visibility.
+        "/ redraw will call rearrangeItems, if the mustRearrange is set.
+
+        "/ menuPanel rearrangeItems.
+        ^ self.
     ].
 
     super update:something with:aParameter from:changedObject
@@ -7619,14 +7624,14 @@
     "update indicators "
 
     indication notNil ifTrue:[
-	(indication isSymbol
-	or:[menuItem hideMenuOnActivated not])
-	ifTrue:[
-	    "indication is a selector;
-	     otherwise no need to redraw, because
-	     a change notification is raised from the model !!!!"
-	    self update:nil with:nil from:indication
-	]
+        (indication isSymbol
+        or:[menuItem hideMenuOnActivated not])
+        ifTrue:[
+            "indication is a selector;
+             otherwise no need to redraw, because
+             a change notification is raised from the model !!!!"
+            self update:nil with:nil from:indication
+        ]
     ]
 ! !
 
@@ -7648,25 +7653,25 @@
     |lbl|
 
     menuPanel disabledRedrawDo:[
-	menuItem := aMenuItem.
-	menuItem isNil ifTrue:[ menuItem := MenuItem new].
-
-	label := displayLabel := activeHelpText := nil.
-
-	self    enabled:(menuItem enabled).
-	self indication:(menuItem indication).
-	self     choice:(menuItem choice).
-	self  isVisible:(menuItem isVisible ? true).
+        menuItem := aMenuItem.
+        menuItem isNil ifTrue:[ menuItem := MenuItem new].
+
+        label := displayLabel := activeHelpText := nil.
+
+        self    enabled:(menuItem enabled).
+        self indication:(menuItem indication).
+        self     choice:(menuItem choice).
+        self  isVisible:(menuItem isVisible ? true).
 
 "/ we should call the resourceRetriever here instead of labelImage
 "/ but ... ??
 
-	(lbl := menuItem labelImage value) isNil ifTrue:[
-	    lbl := menuItem rawLabel. "/ avoid translating &'s twice
-	].
-
-	self submenu:(menuItem submenu).
-	self label:lbl.
+        (lbl := menuItem labelImage value) isNil ifTrue:[
+            lbl := menuItem rawLabel. "/ avoid translating &'s twice
+        ].
+
+        self submenu:(menuItem submenu).
+        self label:lbl.
     ]
 
     "Modified: / 22.8.1998 / 15:34:16 / cg"
@@ -7703,16 +7708,16 @@
 
     isOn := (choice value = menuItem choiceValue).
     self enabled ifFalse:[
-	^ isOn ifTrue:[menuPanel iconRadioGroupDisabledOn]
-	       ifFalse:[menuPanel iconRadioGroupDisabledOff]
+        ^ isOn ifTrue:[menuPanel iconRadioGroupDisabledOn]
+               ifFalse:[menuPanel iconRadioGroupDisabledOff]
     ].
     self isSelected ifTrue:[
-	^ isOn == true
-	    ifTrue:[menuPanel iconRadioGroupEnteredOn]
-	    ifFalse:[menuPanel iconRadioGroupEnteredOff]
+        ^ isOn == true
+            ifTrue:[menuPanel iconRadioGroupEnteredOn]
+            ifFalse:[menuPanel iconRadioGroupEnteredOff]
     ].
     ^ isOn ifTrue:[menuPanel iconRadioGroupOn]
-	   ifFalse:[menuPanel iconRadioGroupOff]
+           ifFalse:[menuPanel iconRadioGroupOff]
 !
 
 draw
@@ -7727,17 +7732,17 @@
 
     self isVisible ifFalse:[^ self].
     layout isNil ifTrue:[
-	"/ cg: why does this happen - it does!!
-	^ self
+        "/ cg: why does this happen - it does!!
+        ^ self
     ].
 
     self isSeparator ifTrue:[
-	self drawSeparator.
-	^ self
+        self drawSeparator.
+        ^ self
     ].
     menuItem isButton ifTrue:[
-	self drawButton.
-	^ self
+        self drawButton.
+        ^ self
     ].
 
     "/ DRAW A LABELED ENTRY; no button, no separator
@@ -7745,40 +7750,40 @@
     isSelected := self isSelected.
     bgColor    := menuPanel backgroundColor.
     paint      := isSelected
-		    ifTrue:[self activeBackgroundColor]
-		    ifFalse:[
-			(self isEnabled and:[ self isEntered ]) ifTrue:[
-			    menuPanel enteredBackgroundColor
-			] ifFalse:[
-			    bgColor
-			]].
+                    ifTrue:[self activeBackgroundColor]
+                    ifFalse:[
+                        (self isEnabled and:[ self isEntered ]) ifTrue:[
+                            menuPanel enteredBackgroundColor
+                        ] ifFalse:[
+                            bgColor
+                        ]].
 
     (ownBgCol := self backgroundColorFromLabel) notNil ifTrue:[
-	paint := ownBgCol
+        paint := ownBgCol
     ].
 
     paint ~= bgColor ifTrue:[
-	menuPanel paint:paint.
-	menuPanel fillRectangle:layout.
+        menuPanel paint:paint.
+        menuPanel fillRectangle:layout.
     ].
 
     menuPanel showSeparatingLines ifTrue:[
-	self drawSeparatingLines
+        self drawSeparatingLines
     ].
 
     self drawLabel.
 
     (ownBgCol notNil and:[isSelected]) ifTrue:[
-	ownBgCol brightness > 0.5 ifTrue:[menuPanel paint: menuPanel selectionFrameDarkColor]
-				 ifFalse:[menuPanel paint: menuPanel selectionFrameBrightColor].
-
-	x := layout left.
-	y := layout top.
-	w := layout width.
-	h := layout height.
-
-	menuPanel displayRectangleX:(x + 1) y:(y + 1) width:(w - 2) height:(h - 2).
-	menuPanel displayRectangleX:(x + 2) y:(y + 2) width:(w - 4) height:(h - 4).
+        ownBgCol brightness > 0.5 ifTrue:[menuPanel paint: menuPanel selectionFrameDarkColor]
+                                 ifFalse:[menuPanel paint: menuPanel selectionFrameBrightColor].
+
+        x := layout left.
+        y := layout top.
+        w := layout width.
+        h := layout height.
+
+        menuPanel displayRectangleX:(x + 1) y:(y + 1) width:(w - 2) height:(h - 2).
+        menuPanel displayRectangleX:(x + 2) y:(y + 2) width:(w - 4) height:(h - 4).
     ].
     menuPanel drawLabelEdgeFor:self selected:isSelected.
 !
@@ -7977,46 +7982,46 @@
 
     icon := self menuIndicatorIcon.
     icon isNil ifTrue:[
-	^ self
+        ^ self
     ].
 
     x := layout right  - icon width.
     verticalPosition := menuPanel menuIndicatorVerticalPosition.
     verticalPosition == #center ifTrue:[
-	y := (layout height - icon height) // 2 + layout top.
+        y := (layout height - icon height) // 2 + layout top.
     ] ifFalse:[
-	verticalPosition == #top ifTrue:[
-	    y := layout top + 2.
-	] ifFalse:[
-	    y := layout bottom - icon height - 2.
-	]
+        verticalPosition == #top ifTrue:[
+            y := layout top + 2.
+        ] ifFalse:[
+            y := layout bottom - icon height - 2.
+        ]
     ].
 
     bAbsLevel := 0.
     menuItem isButton ifTrue:[
-	self isSelected ifTrue:[
-	    x := x + 1.
-	    y := y + 1.
-	].
-	bAbsLevel := menuPanel maxAbsoluteButtonLevel.
-	x := x - bAbsLevel.
-	y := y - bAbsLevel.
+        self isSelected ifTrue:[
+            x := x + 1.
+            y := y + 1.
+        ].
+        bAbsLevel := menuPanel maxAbsoluteButtonLevel.
+        x := x - bAbsLevel.
+        y := y - bAbsLevel.
     ].
     x := x - 1 "- HorizontalInset".
 
     (self isEnabled "and:[self delayedMenuIsEnabled]") ifFalse:[
-	icon := menuPanel lightenedImageOnDevice:icon
+        icon := menuPanel lightenedImageOnDevice:icon
     ].
     icon displayOn:menuPanel x:x y:y.
 
     (menuPanel drawMenuIndicatorSeparatorLine
-	and:[ self isEntered
-	and:[ menuPanel buttonEnteredLevel ~~ 0] ])
+        and:[ self isEntered
+        and:[ menuPanel buttonEnteredLevel ~~ 0] ])
     ifTrue:[
-	menuPanel paint:menuPanel buttonShadowColor.
-	menuPanel displayLineFromX:x-2 y:layout top+bAbsLevel+1 toX:x-2 y:layout bottom-bAbsLevel-2.
-	menuPanel paint:menuPanel buttonLightColor.
-	menuPanel displayLineFromX:x-1 y:layout top+bAbsLevel+1 toX:x-1 y:layout bottom-bAbsLevel-2.
+        menuPanel paint:menuPanel buttonShadowColor.
+        menuPanel displayLineFromX:x-2 y:layout top+bAbsLevel+1 toX:x-2 y:layout bottom-bAbsLevel-2.
+        menuPanel paint:menuPanel buttonLightColor.
+        menuPanel displayLineFromX:x-1 y:layout top+bAbsLevel+1 toX:x-1 y:layout bottom-bAbsLevel-2.
     ].
 !
 
@@ -8197,9 +8202,9 @@
 
     isOn := self indicationValue.
     self enabled ifFalse:[
-	^ isOn == true
-	    ifTrue:[menuPanel iconIndicationDisabledOn]
-	    ifFalse:[menuPanel iconIndicationDisabledOff]
+        ^ isOn == true
+            ifTrue:[menuPanel iconIndicationDisabledOn]
+            ifFalse:[menuPanel iconIndicationDisabledOff]
     ].
 "/    self isSelected ifTrue:[
 "/        ^ isOn == true
@@ -8208,8 +8213,8 @@
 "/    ].
 
     ^ isOn == true
-	ifTrue:[menuPanel iconIndicationOn]
-	ifFalse:[menuPanel iconIndicationOff]
+        ifTrue:[menuPanel iconIndicationOn]
+        ifFalse:[menuPanel iconIndicationOff]
 !
 
 invalidate
@@ -8217,7 +8222,7 @@
     layout isNil ifTrue:[^ self].
 
     (displayLabel notNil and:[menuPanel notNil]) ifTrue:[
-	menuPanel invalidateItem:self repairNow:false
+        menuPanel invalidateItem:self repairNow:false
     ]
 !
 
@@ -8225,10 +8230,10 @@
     "return a menu indicator icon used if the item has a menu or delayed menu."
 
     self hasDelayedMenuIndicator ifTrue:[
-	^ MenuPanel delayedMenuIndicator.
+        ^ MenuPanel delayedMenuIndicator.
     ].
     self hasMenuIndicator ifTrue:[
-	^ MenuPanel menuIndicator.
+        ^ MenuPanel menuIndicator.
     ].
     ^ nil
 ! !
@@ -8250,8 +8255,8 @@
     menuPanel := aPanel.
 
     menuItem isNil ifTrue:[
-	self breakPoint:#ca.
-	menuItem := MenuItem new
+        self breakPoint:#ca.
+        menuItem := MenuItem new
     ].
 !
 
@@ -8262,7 +8267,7 @@
 reinitStyle
 
     subMenu notNil ifTrue:[
-	subMenu reinitStyle
+        subMenu reinitStyle
     ].
 
     "Created: / 17.8.2000 / 17:57:07 / cg"
@@ -8391,8 +8396,8 @@
 
 printOn:aGCOrStream
     aGCOrStream
-	nextPutAll:self class name;
-	nextPut:$(.
+        nextPutAll:self class name;
+        nextPut:$(.
     label displayOn:aGCOrStream.
     aGCOrStream nextPut:$).
 ! !
@@ -8403,7 +8408,7 @@
     "returns the active background color derived from menuPanel"
 
     menuItem isButton ifTrue:[
-	^ menuPanel buttonActiveBackgroundColor
+        ^ menuPanel buttonActiveBackgroundColor
     ].
     ^ menuPanel activeBackgroundColor
 !
@@ -8412,7 +8417,7 @@
     "returns the active foreground color derived from menuPanel"
 
     menuItem isButton ifTrue:[
-	^ menuPanel buttonActiveForegroundColor
+        ^ menuPanel buttonActiveForegroundColor
     ].
     ^menuPanel activeForegroundColor
 !
@@ -8421,7 +8426,7 @@
     "returns the background color derived from menuPanel"
 
     menuItem isButton ifTrue:[
-	^ menuPanel buttonPassiveBackgroundColor
+        ^ menuPanel buttonPassiveBackgroundColor
     ].
     ^ menuPanel backgroundColor
 !
@@ -8438,15 +8443,15 @@
     run := run first.
 
     run size == 0 ifTrue:[
-	(run value isColor and:[run key == #backgroundColor]) ifTrue:[
-	    ^ run value
-	]
+        (run value isColor and:[run key == #backgroundColor]) ifTrue:[
+            ^ run value
+        ]
     ] ifFalse:[
-	run do:[:r|
-	    (r value isColor and:[r key == #backgroundColor]) ifTrue:[
-		^ r value
-	    ]
-	]
+        run do:[:r|
+            (r value isColor and:[r key == #backgroundColor]) ifTrue:[
+                ^ r value
+            ]
+        ]
     ].
   ^ nil
 !
@@ -8479,42 +8484,42 @@
     numArgs := sel numArgs.
 
     numArgs == 0 ifTrue:[
-	gotMenu := false.
-	MessageNotUnderstood handle:[:ex |
-	    |selector|
-
-	    ((selector := ex selector) == sel
-	    or:[selector == #aspectFor:]) ifFalse:[
-		ex reject
-	    ].
-	] do:[
-	    subm := aRecv aspectFor:sel.
-	    gotMenu := true.
-	].
-	"/ used to be subm notNil; however, this is a bad test,
-	"/ as it does not allow for the app to return nil for no-menu.
-	gotMenu ifTrue:[^ subm].
+        gotMenu := false.
+        MessageNotUnderstood handle:[:ex |
+            |selector|
+
+            ((selector := ex selector) == sel
+            or:[selector == #aspectFor:]) ifFalse:[
+                ex reject
+            ].
+        ] do:[
+            subm := aRecv aspectFor:sel.
+            gotMenu := true.
+        ].
+        "/ used to be subm notNil; however, this is a bad test,
+        "/ as it does not allow for the app to return nil for no-menu.
+        gotMenu ifTrue:[^ subm].
     ].
 
     (Array with:(aRecv) with:(aRecv class))
     do:[:aPossibleReceiver |
-	MessageNotUnderstood handle:[:ex|
-	    ex message selector == sel ifFalse:[ ex reject ]
-	] do:[
-	    numArgs == 0 ifTrue:[
-		subm := aPossibleReceiver perform:sel
-	    ] ifFalse:[
-		numArgs == 1 ifTrue:[
-		    subm := aPossibleReceiver perform:sel with:(menuItem argument ? menuPanel)
-		] ifFalse:[
-		    subm := aPossibleReceiver perform:sel with:(menuItem argument) with:menuPanel
-		]
-	    ]
-	].
-	subm notNil ifTrue:[^ subm].
-	Smalltalk isSmalltalkDevelopmentSystem ifTrue:[
-	    "/ ('MenuPanel [info]: no submenu for "%1" from %2' bindWith:sel with:aPossibleReceiver) infoPrintCR.
-	]
+        MessageNotUnderstood handle:[:ex|
+            ex message selector == sel ifFalse:[ ex reject ]
+        ] do:[
+            numArgs == 0 ifTrue:[
+                subm := aPossibleReceiver perform:sel
+            ] ifFalse:[
+                numArgs == 1 ifTrue:[
+                    subm := aPossibleReceiver perform:sel with:(menuItem argument ? menuPanel)
+                ] ifFalse:[
+                    subm := aPossibleReceiver perform:sel with:(menuItem argument) with:menuPanel
+                ]
+            ]
+        ].
+        subm notNil ifTrue:[^ subm].
+        Smalltalk isSmalltalkDevelopmentSystem ifTrue:[
+            "/ ('MenuPanel [info]: no submenu for "%1" from %2' bindWith:sel with:aPossibleReceiver) infoPrintCR.
+        ]
     ].
 
     ^ subm
@@ -8530,35 +8535,35 @@
     indication isNil ifTrue:[^ nil].       "no indication specified"
 
     indication isSymbol ifFalse:[
-	^ indication value == true          "block or model"
+        ^ indication value == true          "block or model"
     ].
 
     numArgs := indication numArgs.
     numArgs == 2 ifTrue:[
-	recv := menuPanel receiver ? menuPanel application.
-	(recv notNil and:[recv isValueModel not]) ifTrue:[
-	    sel := indication copyFrom:1 to:(indication indexOf:$:).
-	    sel := sel asSymbol.
-
-	    MessageNotUnderstood handle:[:ex|
-		ex selector ~~ sel ifTrue:[
-		    ex reject.
-		].
-	    ] do:[
-		sel := recv perform:sel with:(menuItem argument).
-	    ]
-	].
+        recv := menuPanel receiver ? menuPanel application.
+        (recv notNil and:[recv isValueModel not]) ifTrue:[
+            sel := indication copyFrom:1 to:(indication indexOf:$:).
+            sel := sel asSymbol.
+
+            MessageNotUnderstood handle:[:ex|
+                ex selector ~~ sel ifTrue:[
+                    ex reject.
+                ].
+            ] do:[
+                sel := recv perform:sel with:(menuItem argument).
+            ]
+        ].
     ] ifFalse:[
-	numArgs == 0 ifTrue:[
-	    sel := indication
-	] ifFalse:[
-	    sel := (indication copyButLast:1) asSymbol.
-	].
-	sel := self aspectAt:sel.
-	sel isValueModel ifTrue:[
-	    indication := sel.
-	    indication addDependent:self.
-	].
+        numArgs == 0 ifTrue:[
+            sel := indication
+        ] ifFalse:[
+            sel := (indication copyButLast:1) asSymbol.
+        ].
+        sel := self aspectAt:sel.
+        sel isValueModel ifTrue:[
+            indication := sel.
+            indication addDependent:self.
+        ].
     ].
     ^ sel value == true
 !
@@ -8571,36 +8576,36 @@
     indication isNil ifTrue:[^ self].                                   "no indication specified"
 
     indication isSymbol ifFalse:[
-	indication perform:#value: with:aValue ifNotUnderstood:nil.     "block or model"
-	^ self
+        indication perform:#value: with:aValue ifNotUnderstood:nil.     "block or model"
+        ^ self
     ].
 
     (numArgs := indication numArgs) == 0 ifTrue:[                       "no arguments to selector; cannot set"
-	^ self
+        ^ self
     ].
 
     recv := menuPanel receiver.
     recv isValueModel ifTrue:[^ self].
 
     recv isNil ifTrue:[
-	recv := menuPanel application.
-	recv isNil ifTrue:[^ self].
+        recv := menuPanel application.
+        recv isNil ifTrue:[^ self].
     ].
 
     MessageNotUnderstood handle:[:ex|
-	(ex selector ~~ indication) ifTrue:[
-	    ex reject
-	].
-	self ifNotInUIBuilderInfoPrintCR:
-	    ('MenuPanel::Item [info]: application (%1) does not respond to: %2'
-	     bindWith:recv classNameWithArticle
-	     with:indication).
+        (ex selector ~~ indication) ifTrue:[
+            ex reject
+        ].
+        self ifNotInUIBuilderInfoPrintCR:
+            ('MenuPanel::Item [info]: application (%1) does not respond to: %2'
+             bindWith:recv classNameWithArticle
+             with:indication).
     ] do:[
-	numArgs == 1 ifTrue:[
-	    recv perform:indication with:aValue
-	] ifFalse:[
-	    recv perform:indication with:(menuItem argument ? self) with:aValue
-	]
+        numArgs == 1 ifTrue:[
+            recv perform:indication with:aValue
+        ] ifFalse:[
+            recv perform:indication with:(menuItem argument ? self) with:aValue
+        ]
     ].
 
     "Modified (format): / 02-08-2013 / 16:42:20 / cg"
@@ -8620,17 +8625,17 @@
     |c lbl|
 
     self isSeparator ifFalse:[
-	^ nil
+        ^ nil
     ].
 
     (lbl := label value) isNil ifTrue:[
-	^ #singleLine
+        ^ #singleLine
     ].
 
     lbl size == 1 ifTrue:[
-	c := lbl first.
-	c == $- ifTrue:[^ #singleLine].
-	c == $= ifTrue:[^ #doubleLine].
+        c := lbl first.
+        c == $- ifTrue:[^ #singleLine].
+        c == $= ifTrue:[^ #doubleLine].
     ].
     ^ #blankLine
 !
@@ -8643,66 +8648,66 @@
     channel isNil ifTrue:[ ^ subMenu ].
 
     subMenu notNil ifTrue:[
-	menuItem keepLinkedMenu ifTrue:[ ^ subMenu ].
+        menuItem keepLinkedMenu ifTrue:[ ^ subMenu ].
     ].
 
     channel isSymbol ifFalse:[
-	submenuHolder := channel
+        submenuHolder := channel
     ] ifTrue:[
-	"/ submenu is specified by a selector in submenuChannel.
-	"/ who gets me the menu:
-	"/ 1) submenuProvider (if not nil)
-	"/ 2) menuPanel application
-	"/ 3) menuPanel receiver
-	"/ 4) menuPanel application master-chain
-	"/ 5) menuPanel receiver master-chain
-
-	(submenuProvider := menuItem submenuProvider) notNil ifTrue:[
-	    submenuHolder := self findSubMenuIn:submenuProvider.
-	    whoProvidedMenu := submenuProvider.
-	].
-	submenuHolder isNil ifTrue:[
-	    appl := menuPanel application.
-	    (appl notNil and:[appl ~~ submenuProvider]) ifTrue:[
-		submenuHolder := self findSubMenuIn:appl.
-		whoProvidedMenu := appl.
-	    ].
-	    submenuHolder isNil ifTrue:[
-		recv := menuPanel receiver.
-		(recv notNil and:[recv ~~ appl and:[recv ~~ submenuProvider]]) ifTrue:[
-		    submenuHolder := self findSubMenuIn:recv.
-		    whoProvidedMenu := recv.
-		].
-		(submenuHolder isNil and:[appl notNil]) ifTrue:[
-		    t := appl.
-		    [ submenuHolder isNil
-		       and:[ (master := t perform:#masterApplication ifNotUnderstood:nil) notNil ]
-		    ] whileTrue:[
-		       ( master ~~ appl
-			and:[ master ~~ recv
-			and:[ master ~~ submenuProvider ]] ) ifTrue:[
-			    submenuHolder := self findSubMenuIn:master.
-			].
-			t := master.
-			whoProvidedMenu := master.
-		    ]
-		].
-		(submenuHolder isNil and:[recv notNil]) ifTrue:[
-		    t := recv.
-		    [ submenuHolder isNil
-		       and:[ (master := t perform:#masterApplication ifNotUnderstood:nil) notNil ]
-		    ] whileTrue:[
-		       ( master ~~ appl
-			and:[ master ~~ recv
-			and:[ master ~~ submenuProvider ]] ) ifTrue:[
-			    submenuHolder := self findSubMenuIn:master.
-			].
-			t := master.
-			whoProvidedMenu := master.
-		    ]
-		].
-	    ].
-	].
+        "/ submenu is specified by a selector in submenuChannel.
+        "/ who gets me the menu:
+        "/ 1) submenuProvider (if not nil)
+        "/ 2) menuPanel application
+        "/ 3) menuPanel receiver
+        "/ 4) menuPanel application master-chain
+        "/ 5) menuPanel receiver master-chain
+
+        (submenuProvider := menuItem submenuProvider) notNil ifTrue:[
+            submenuHolder := self findSubMenuIn:submenuProvider.
+            whoProvidedMenu := submenuProvider.
+        ].
+        submenuHolder isNil ifTrue:[
+            appl := menuPanel application.
+            (appl notNil and:[appl ~~ submenuProvider]) ifTrue:[
+                submenuHolder := self findSubMenuIn:appl.
+                whoProvidedMenu := appl.
+            ].
+            submenuHolder isNil ifTrue:[
+                recv := menuPanel receiver.
+                (recv notNil and:[recv ~~ appl and:[recv ~~ submenuProvider]]) ifTrue:[
+                    submenuHolder := self findSubMenuIn:recv.
+                    whoProvidedMenu := recv.
+                ].
+                (submenuHolder isNil and:[appl notNil]) ifTrue:[
+                    t := appl.
+                    [ submenuHolder isNil
+                       and:[ (master := t perform:#masterApplication ifNotUnderstood:nil) notNil ]
+                    ] whileTrue:[
+                       ( master ~~ appl
+                        and:[ master ~~ recv
+                        and:[ master ~~ submenuProvider ]] ) ifTrue:[
+                            submenuHolder := self findSubMenuIn:master.
+                        ].
+                        t := master.
+                        whoProvidedMenu := master.
+                    ]
+                ].
+                (submenuHolder isNil and:[recv notNil]) ifTrue:[
+                    t := recv.
+                    [ submenuHolder isNil
+                       and:[ (master := t perform:#masterApplication ifNotUnderstood:nil) notNil ]
+                    ] whileTrue:[
+                       ( master ~~ appl
+                        and:[ master ~~ recv
+                        and:[ master ~~ submenuProvider ]] ) ifTrue:[
+                            submenuHolder := self findSubMenuIn:master.
+                        ].
+                        t := master.
+                        whoProvidedMenu := master.
+                    ]
+                ].
+            ].
+        ].
 "/        submenuHolder isNil ifTrue:[
 "/            self halt:'did not find any menu'
 "/        ].
@@ -8732,14 +8737,14 @@
     ].
 
     (newSubmenu := submenuHolder value) isArray ifTrue:[
-	submenuEncoding := newSubmenu.
-	newSubmenu := Menu decodeFromLiteralArray:submenuEncoding.
-	"/ cg: linked menus also may contain translations ...
-	newSubmenu notNil ifTrue:[
-	    whoProvidedMenu "appl" notNil ifTrue:[
-		newSubmenu findGuiResourcesIn:whoProvidedMenu "appl".
-	    ]
-	].
+        submenuEncoding := newSubmenu.
+        newSubmenu := Menu decodeFromLiteralArray:submenuEncoding.
+        "/ cg: linked menus also may contain translations ...
+        newSubmenu notNil ifTrue:[
+            whoProvidedMenu "appl" notNil ifTrue:[
+                newSubmenu findGuiResourcesIn:whoProvidedMenu "appl".
+            ]
+        ].
     ].
     "/ appl notNil ifTrue:[submenu application:appl].
     self submenu:newSubmenu.
@@ -8749,7 +8754,7 @@
 !
 
 spaceBetweenEmptyLines
-	^ 3
+        ^ 3
 ! !
 
 !MenuPanel::Item methodsFor:'queries'!
@@ -8772,9 +8777,9 @@
     self isSeparator ifTrue:[^ false].
 
     (self isVisible and:[self enabled]) ifTrue:[
-	(choice isNil or:[choice value ~= menuItem choiceValue]) ifTrue:[
-	    ^ true
-	].
+        (choice isNil or:[choice value ~= menuItem choiceValue]) ifTrue:[
+            ^ true
+        ].
     ].
     ^ false
 !
@@ -8783,7 +8788,7 @@
     "returns true if aPoint is contained in my layout"
 
     (self isVisible and:[layout notNil]) ifTrue:[
-	^ layout containsPoint:aPoint
+        ^ layout containsPoint:aPoint
     ].
     ^ false
 
@@ -8794,7 +8799,7 @@
     "returns true if point is contained in my layout"
 
     (self isVisible and:[layout notNil]) ifTrue:[
-	^ layout containsPointX:x y:y
+        ^ layout containsPointX:x y:y
     ].
     ^ false
 !
@@ -8803,12 +8808,12 @@
     "returns true if a delayed menu exists"
 
     self hasSubmenu ifFalse:[
-	^ false
+        ^ false
     ].
     menuItem itemValue notNil ifTrue:[ ^ true ].
 
     (indication isNil and:[choice isNil]) ifTrue:[
-	^ false
+        ^ false
     ].
     ^ true
 !
@@ -8818,7 +8823,7 @@
      and is in the topMenuPanel (because submenuIndicator is already drawn in popUpViews)"
 
     menuPanel isPopUpView ifFalse:[
-	^ self hasDelayedMenu
+        ^ self hasDelayedMenu
     ].
     ^ false
 !
@@ -8834,7 +8839,7 @@
      and is in the topMenuPanel (because submenuIndicator is already drawn in popUpViews)"
 
     menuPanel isPopUpView ifFalse:[
-	^ self hasSubmenu and:[menuItem isButton]
+        ^ self hasSubmenu and:[menuItem isButton]
     ].
     ^ false
 !
@@ -8890,29 +8895,29 @@
     |oldState newState|
 
     isVisible isNil ifTrue:[
-	oldState := true
+        oldState := true
     ] ifFalse:[
-	oldState := isVisible value.
-	isVisible isValueModel ifTrue:[
-	    isVisible removeDependent:self
-	]
+        oldState := isVisible value.
+        isVisible isValueModel ifTrue:[
+            isVisible removeDependent:self
+        ]
     ].
     isVisible := something.
 
     isVisible isNil ifTrue:[
-	newState := true
+        newState := true
     ] ifFalse:[
-	isVisible isValueModel ifTrue:[
-	    isVisible addDependent:self
-	] ifFalse:[
-	    isVisible isSymbol ifTrue:[^ self]
-	].
-	menuPanel shown ifFalse:[^ self].
-	newState := isVisible value.
+        isVisible isValueModel ifTrue:[
+            isVisible addDependent:self
+        ] ifFalse:[
+            isVisible isSymbol ifTrue:[^ self]
+        ].
+        menuPanel shown ifFalse:[^ self].
+        newState := isVisible value.
     ].
 
     newState ~~ oldState ifTrue:[
-	menuPanel mustRearrange
+        menuPanel mustRearrange
     ]
 
     "Modified: / 5.10.1998 / 12:12:04 / cg"
@@ -8924,13 +8929,13 @@
     |icon xSep|
 
     (self isVisible and:[layout notNil]) ifTrue:[
-	(layout containsPoint:aPoint) ifTrue:[
-	    icon := self menuIndicatorIcon.
-	    icon notNil ifTrue:[
-		xSep := layout right - icon width.
-		^ aPoint x >= xSep
-	    ]
-	]
+        (layout containsPoint:aPoint) ifTrue:[
+            icon := self menuIndicatorIcon.
+            icon notNil ifTrue:[
+                xSep := layout right - icon width.
+                ^ aPoint x >= xSep
+            ]
+        ]
     ].
     ^ false
 !
@@ -8948,13 +8953,13 @@
     shortcutKey := menuItem shortcutKey.
 
     shortcutKey isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
     shortcutKey isCharacter ifTrue:[
-	shortcutKey == Character space ifFalse:[
-	    ^ 'Space'
-	].
-	^ shortcutKey asString
+        shortcutKey == Character space ifFalse:[
+            ^ 'Space'
+        ].
+        ^ shortcutKey asString
     ].
     ^ menuPanel device shortKeyStringFor:shortcutKey.
 
@@ -9313,22 +9318,22 @@
     |task resp|
 
     activeMenu isNil ifTrue:[
-	^ false
+        ^ false
     ].
 
     semaLock critical:[
-	resp := activeMenu notNil.
-
-	(task := scrollTask) notNil ifTrue:[
-	    scrollTask := nil.
-
-	    Error handle:[:ex|
-	    ] do:[
-		task terminateWithAllSubprocessesInGroup.
-		task waitUntilTerminated.
-	    ].
-	].
-	activeMenu := direction := nil.
+        resp := activeMenu notNil.
+
+        (task := scrollTask) notNil ifTrue:[
+            scrollTask := nil.
+
+            Error handle:[:ex|
+            ] do:[
+                task terminateWithAllSubprocessesInGroup.
+                task waitUntilTerminated.
+            ].
+        ].
+        activeMenu := direction := nil.
     ].
     ^ resp
 ! !