grabing and recomputation of items
authorca
Sun, 13 Feb 2000 12:42:17 +0100
changeset 1699 d7b522c4b332
parent 1698 8d29156bab20
child 1700 e2cda6e56205
grabing and recomputation of items
MenuPanel.st
--- a/MenuPanel.st	Sat Feb 12 16:37:01 2000 +0100
+++ b/MenuPanel.st	Sun Feb 13 12:42:17 2000 +0100
@@ -19,9 +19,9 @@
 		itemSpace fitFirstPanel rightArrow rightArrowShadow
 		selectionFrameBrightColor selectionFrameDarkColor
 		buttonLightColor buttonShadowColor buttonHalfLightColor
-		buttonHalfShadowColor lastButtonSelected enteredItem
-		buttonEnteredBgColor prevFocusView previousPointerGrab
-		previousKeyboardGrab'
+		buttonHalfShadowColor enteredItem buttonEnteredBgColor
+		prevFocusView previousPointerGrab previousKeyboardGrab
+		relativeGrabOrigin hasImplicitGrap'
 	classVariableNames:'InitialSelectionQuerySignal DefaultAdornment
 		DefaultGroupDividerSize DefaultHilightLevel DefaultLevel
 		DefaultItemSpace DefaultButtonItemSpace DefaultForegroundColor
@@ -321,78 +321,81 @@
 
 updateStyleCache
 
-    |menuStyle style|
-
-"/    MenuView updateStyleCache.        
-"/
-"/    menuStyle := MenuView styleSheet.
-"/    menuStyle isNil ifTrue:[
-"/        "make sure that style sheet is present"
-"/        MenuView updateStyleCache.        
-"/        menuStyle := MenuView styleSheet.
-"/    ].
-
-    menuStyle := StyleSheet.
-    style := menuStyle name.
-
-"/    DefaultForegroundColor := menuStyle colorAt:'pullDownMenu.foregroundColor'.
-"/    DefaultForegroundColor isNil ifTrue:[
-        DefaultForegroundColor := menuStyle colorAt:#'menu.foregroundColor'
-                                            default:Color black.
-"/    ].
-
-    DefaultLevel := menuStyle at:#'pullDownMenu.level' default:0.
-
-    DefaultBackgroundColor := DefaultViewBackgroundColor.
-"/        DefaultBackgroundColor := menuStyle colorAt:'pullDownMenu.backgroundColor'.
-"/        DefaultBackgroundColor isNil ifTrue:[
-    DefaultBackgroundColor := menuStyle colorAt:#'menu.backgroundColor' default:DefaultBackgroundColor.
-
-    menuStyle is3D ifTrue:[
-        DefaultHilightForegroundColor := DefaultForegroundColor.
-    ] ifFalse:[
-        DefaultHilightForegroundColor := DefaultBackgroundColor.
-    ].
-"/        DefaultHilightForegroundColor := menuStyle colorAt:'pullDownMenu.hilightForegroundColor'.
-"/        DefaultHilightForegroundColor isNil ifTrue:[
-    DefaultHilightForegroundColor := menuStyle colorAt:#'menu.hilightForegroundColor' default:DefaultHilightForegroundColor.
+    <resource: #style (#'menu.foregroundColor' #'menu.backgroundColor'
+                       #'menu.hilightForegroundColor' #'menu.disabledForegroundColor'
+                       #'menu.hilightBackgroundColor' #'menu.buttonEnteredBackgroundColor'
+                       #'menu.hilightLevel' #'menu.groupDividerSize'
+                       #'menu.itemSpace' #'menu.buttonItemSpace'
+                       #'menu.fitFirstPanel' #'menu.buttonActiveLevel'
+                       #'menu.buttonPassiveLevel' #'menu.buttonEnteredLevel'
+                       #'menu.selectionFollowsMouse' #'menu.enteredLevel'
+                       #'viewBackground'
+                       #'pullDownMenu.level' #'pullDownMenu.hilightLevel'
+                       #'button.disabledForegroundColor' #'button.enteredBackgroundColor'
+                       #'button.activeBackgroundColor' #'button.backgroundColor'
+                       #'button.lightColor' #'button.shadowColor'
+                       #'button.halfLightColor' #'button.halfShadowColor'
+                       #'button.passiveLevel' #'button.activeLevel'
+                       #'button.edgeStyle')>
+
+
+    |style styleSheet|
+
+    styleSheet := StyleSheet.
+    style      := styleSheet name.
+
+    DefaultForegroundColor := styleSheet colorAt:#'menu.foregroundColor'
+                                         default:Color black.
+
+    DefaultBackgroundColor := styleSheet colorAt:#'menu.backgroundColor'
+                                         default:DefaultViewBackgroundColor.
+
+    DefaultHilightForegroundColor := styleSheet colorAt:#'menu.hilightForegroundColor'.
+
+    DefaultHilightForegroundColor isNil ifTrue:[
+        styleSheet is3D ifTrue:[
+            DefaultHilightForegroundColor := DefaultForegroundColor.
+        ] ifFalse:[
+            DefaultHilightForegroundColor := DefaultBackgroundColor.
+        ].
+    ].
+
+    DefaultDisabledForegroundColor := styleSheet colorAt:#'menu.disabledForegroundColor'.
+    DefaultDisabledForegroundColor isNil ifTrue:[
+        DefaultDisabledForegroundColor := styleSheet colorAt:#'button.disabledForegroundColor'
+                                                     default:Color darkGray.
+    ].
+
+    DefaultHilightBackgroundColor := styleSheet colorAt:#'menu.hilightBackgroundColor'.
+
+    DefaultHilightBackgroundColor isNil ifTrue:[
+        style == #motif ifTrue:[
+            DefaultHilightBackgroundColor := DefaultBackgroundColor
+        ] ifFalse:[
+            DefaultHilightBackgroundColor := styleSheet is3D ifFalse:[DefaultForegroundColor]
+                                                              ifTrue:[DefaultBackgroundColor]
+        ]
+    ].
+
+    DefaultLevel := styleSheet at:#'pullDownMenu.level' default:0.
 
     (style == #motif or:[style == #iris]) ifTrue:[
-        DefaultHilightLevel     := 2.
-        DefaultLevel           := DefaultLevel + 1.
+        DefaultHilightLevel := 2.
+        DefaultLevel        := DefaultLevel + 1.
     ] ifFalse:[
-        (DefaultHilightLevel := menuStyle at:'pullDownMenu.hilightLevel') isNil ifTrue:[
-            DefaultHilightLevel := menuStyle at:'menu.hilightLevel' default:0.
+        (DefaultHilightLevel    := styleSheet at:'pullDownMenu.hilightLevel') isNil ifTrue:[
+            DefaultHilightLevel := styleSheet at:'menu.hilightLevel' default:0.
         ].
-        menuStyle is3D ifTrue:[DefaultLevel := DefaultLevel + 1].
-    ].
-
-    DefaultDisabledForegroundColor := menuStyle colorAt:#'menu.disabledForegroundColor'.
-    DefaultDisabledForegroundColor isNil ifTrue:[
-        DefaultDisabledForegroundColor := menuStyle colorAt:#'button.disabledForegroundColor'
-                                                    default:Color darkGray.
-    ].
-
-    style == #motif ifTrue:[
-        DefaultHilightBackgroundColor := DefaultBackgroundColor
-    ] ifFalse:[
-        DefaultHilightBackgroundColor := menuStyle is3D ifFalse:[DefaultForegroundColor] ifTrue:[DefaultBackgroundColor]
-    ].
-"/    DefaultHilightBackgroundColor := menuStyle colorAt:'pullDownMenu.hilightBackgroundColor'.
-"/    DefaultHilightBackgroundColor isNil ifTrue:[
-    DefaultHilightBackgroundColor := menuStyle colorAt:#'menu.hilightBackgroundColor' default:DefaultHilightBackgroundColor.
-
-    DefaultGroupDividerSize := menuStyle at:#'menu.groupDividerSize' default:6.
-    DefaultItemSpace        := menuStyle at:#'menu.itemSpace' default:0.
-    DefaultButtonItemSpace  := menuStyle at:#'menu.buttonItemSpace' default:0.
-    DefaultFitFirstPanel    := menuStyle at:#'menu.fitFirstPanel' default:true.
+        styleSheet is3D ifTrue:[DefaultLevel := DefaultLevel + 1].
+    ].
+
+    DefaultGroupDividerSize := styleSheet at:#'menu.groupDividerSize' default:6.
+    DefaultItemSpace        := styleSheet at:#'menu.itemSpace' default:0.
+    DefaultButtonItemSpace  := styleSheet at:#'menu.buttonItemSpace' default:0.
+    DefaultFitFirstPanel    := styleSheet at:#'menu.fitFirstPanel' default:true.
 
     MenuView updateStyleCache.
-    DefaultFont := MenuView defaultFont.
-"/    font := menuStyle fontAt:'pullDownMenu.font'.
-"/    font isNil ifTrue:[font := menuStyle fontAt:'menu.font'].
-"/    DefaultFont := font.
-
+    DefaultFont    := MenuView defaultFont.
     RightArrowForm := SelectionInListView rightArrowFormOn:Display.
 
     (style ~~ #os2 and:[style ~~ #win95]) ifTrue:[
@@ -404,48 +407,38 @@
     SelectionFrameBrightColor    := Color white.
     SelectionFrameDarkColor      := Color black.
 
-    ButtonActiveLevel            :=  menuStyle at:#'menu.buttonActiveLevel' default:(menuStyle is3D ifTrue:[-2] ifFalse:[0]).
+    ButtonActiveLevel            :=  styleSheet at:#'menu.buttonActiveLevel' default:(styleSheet is3D ifTrue:[-2] ifFalse:[0]).
     ButtonActiveLevel isNil ifTrue:[
-        ButtonActiveLevel        :=  menuStyle at:#'button.activeLevel' default:(menuStyle is3D ifTrue:[-2] ifFalse:[0]).
-    ].
-    ButtonPassiveLevel           :=  menuStyle at:#'menu.buttonPassiveLevel'.
+        ButtonActiveLevel        :=  styleSheet at:#'button.activeLevel' default:(styleSheet is3D ifTrue:[-2] ifFalse:[0]).
+    ].
+    ButtonPassiveLevel           :=  styleSheet at:#'menu.buttonPassiveLevel'.
     ButtonPassiveLevel isNil ifTrue:[
-        ButtonPassiveLevel       :=  menuStyle at:#'button.passiveLevel' default:(menuStyle is3D ifTrue:[2] ifFalse:[0]).
-    ].
-    ButtonActiveBackgroundColor  :=  menuStyle at:#'button.activeBackgroundColor' default: DefaultBackgroundColor.
-    ButtonPassiveBackgroundColor := (menuStyle at:#'button.backgroundColor') ? (menuStyle at:'viewBackground') ? DefaultBackgroundColor.
-
-    ButtonLightColor             := menuStyle at:#'button.lightColor'.
+        ButtonPassiveLevel       :=  styleSheet at:#'button.passiveLevel' default:(styleSheet is3D ifTrue:[2] ifFalse:[0]).
+    ].
+    ButtonActiveBackgroundColor  :=  styleSheet at:#'button.activeBackgroundColor' default: DefaultBackgroundColor.
+    ButtonPassiveBackgroundColor := (styleSheet at:#'button.backgroundColor') ? (styleSheet at:'viewBackground') ? DefaultBackgroundColor.
+
+    ButtonLightColor             := styleSheet at:#'button.lightColor'.
     ButtonLightColor isNil ifTrue:[
         ButtonLightColor := (ButtonPassiveBackgroundColor averageColorIn:(0@0 corner:7@7)) lightened. "/ Color white
     ].
-    ButtonShadowColor            :=  menuStyle at:#'button.shadowColor'.
+    ButtonShadowColor            :=  styleSheet at:#'button.shadowColor'.
     ButtonShadowColor isNil ifTrue:[
         ButtonShadowColor := (ButtonPassiveBackgroundColor averageColorIn:(0@0 corner:7@7)) darkened. "/ Color white
-"/        (style == #next ifTrue:[
-"/            ButtonShadowColor := Color black
-"/        ] ifFalse:[
-"/            ButtonShadowColor := Color gray
-"/        ]
-    ].
-    ButtonHalfLightColor         :=  menuStyle at:#'button.halfLightColor'.
-    ButtonHalfShadowColor        :=  menuStyle at:#'button.halfShadowColor'.
-    ButtonEdgeStyle              :=  menuStyle at:#'button.edgeStyle'.
-
-    ButtonEnteredBackgroundColor := menuStyle colorAt:#'menu.buttonEnteredBackgroundColor'.
+    ].
+    ButtonHalfLightColor         :=  styleSheet at:#'button.halfLightColor'.
+    ButtonHalfShadowColor        :=  styleSheet at:#'button.halfShadowColor'.
+    ButtonEdgeStyle              :=  styleSheet at:#'button.edgeStyle'.
+
+    ButtonEnteredBackgroundColor := styleSheet colorAt:#'menu.buttonEnteredBackgroundColor'.
     ButtonEnteredBackgroundColor isNil ifTrue:[
-        ButtonEnteredBackgroundColor := menuStyle colorAt:#'button.enteredBackgroundColor'
+        ButtonEnteredBackgroundColor := styleSheet colorAt:#'button.enteredBackgroundColor'
                                                   default:ButtonPassiveBackgroundColor.
     ].
-    ButtonEnteredLevel := menuStyle at:#'menu.buttonEnteredLevel' default:ButtonPassiveLevel.
-
-    style == #win95 ifTrue:[
-        DefaultEnteredLevel := 1.
-        DefaultSelectionFollowsMouse := true.
-    ] ifFalse:[
-        DefaultEnteredLevel := 0.
-        DefaultSelectionFollowsMouse := false.
-    ].
+    ButtonEnteredLevel := styleSheet at:#'menu.buttonEnteredLevel' default:ButtonPassiveLevel.
+
+    DefaultSelectionFollowsMouse := styleSheet at:#'menu.selectionFollowsMouse' default:false.
+    DefaultEnteredLevel          := styleSheet at:#'menu.enteredLevel'          default:0.
 
     Item updateStyleCache
 
@@ -535,14 +528,11 @@
 accept:anItem
     "this is the topMenu: accept item
     "
-    |value item tgState itemIdx recv panel masterGroup|
-
-"/    self ungrabMouseAndKeyboard.
+    |value item tgState itemIdx recv panel masterGroup winGrp|
 
     self superMenu notNil ifTrue:[
         ^ self topMenu accept:anItem
     ].
-    lastButtonSelected := nil.
     self selection:nil.
 
     (anItem notNil and:[anItem canAccept]) ifTrue:[
@@ -552,17 +542,20 @@
         item    := anItem.
         recv    := panel receiver.
     ].
+    self doUngrab:true.
 
     self isPopUpView ifFalse:[
         self do:[:el| el updateIndicators].
         self windowGroup processExposeEvents.
     ] ifTrue:[
         self unmap.
-        "/ give expose event a chance to arrive
-        [shown and:[realized]] whileTrue:[
-            self windowGroup processExposeEventsFor:self
+        (winGrp := self windowGroup) notNil ifTrue:[
+            "/ give expose event a chance to arrive
+            [shown and:[realized]] whileTrue:[
+                winGrp processExposeEventsFor:self
+            ].
+            masterGroup := winGrp previousGroup.
         ].
-        masterGroup := self windowGroup previousGroup.
         self destroy.
         masterGroup notNil ifTrue:[masterGroup processExposeEvents].
     ].
@@ -572,8 +565,7 @@
         self menuAdornmentAt:#value put:value.
         self menuAdornmentAt:#item  put:item.
     ].
-
-  ^ item.
+    ^ item.
 
     "Modified: / 22.2.1999 / 20:14:48 / cg"
 !
@@ -685,6 +677,8 @@
     ^ value
 
     "Modified: / 11.2.2000 / 11:04:52 / cg"
+
+
 !
 
 acceptItem:anItem inMenu:aMenu
@@ -1040,40 +1034,12 @@
     ^ activeBgColor
 !
 
-activeBackgroundColor:aColor
-    "set the background drawing color used to highlight selection. You should not 
-     use this method; instead leave the value as defined in the styleSheet.
-    "
-    activeBgColor ~~ aColor ifTrue:[
-        activeBgColor := aColor onDevice:device.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
-    ]
-
-    "Modified: / 6.6.1998 / 19:49:46 / cg"
-!
-
 activeForegroundColor
     "get the foreground color used to highlight selections
     "
     ^ activeFgColor
 !
 
-activeForegroundColor:aColor
-    "set the foreground color used to highlight selections; You should not
-     use this method; instead leave the value as defined in the styleSheet.
-    "
-    activeFgColor ~~ aColor ifTrue:[
-        activeFgColor := aColor onDevice:device.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
-    ]
-
-    "Modified: / 6.6.1998 / 19:50:01 / cg"
-!
-
 backgroundColor
     "return the background color
     "
@@ -1160,20 +1126,6 @@
 
 !
 
-disabledForegroundColor:aColor
-    "set the foregroundColor drawing color used by disabled items. You should not
-     use this method; instead leave the value as defined in the styleSheet.
-    "
-    disabledFgColor ~~ aColor ifTrue:[
-        disabledFgColor := aColor onDevice:device.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
-    ].
-
-    "Modified: / 6.6.1998 / 19:50:17 / cg"
-!
-
 font:aFont
     "set the font
     "
@@ -1217,18 +1169,14 @@
 
 !
 
-lightColor:aColor
-    "set the light drawing color. You should not use this method;
-     instead leave the value as defined in the styleSheet.
-    "
-    lightColor ~~ aColor ifTrue:[
-	super lightColor:aColor.
-	shown ifTrue:[
-	    self invalidate "/ RepairNow:true
-	]
-    ]
-
-    "Modified: / 6.6.1998 / 19:50:39 / cg"
+maxAbsoluteButtonLevel
+    "returns the maximum absolute button level; used to compute the preferred
+     extent of a button
+    "
+    |level|
+
+    level := (ButtonActiveLevel abs) max:(ButtonEnteredLevel abs).
+  ^ level max:(ButtonPassiveLevel abs)
 !
 
 selectionFrameBrightColor
@@ -1249,20 +1197,6 @@
     ^ shadowColor
 
 
-!
-
-shadowColor:aColor
-    "set the shadow drawing color. You should not use this method;
-     instead leave the value as defined in the styleSheet.
-    "
-    shadowColor ~~ aColor ifTrue:[
-	super shadowColor:aColor.
-	shown ifTrue:[
-	    self invalidate "/ RepairNow:true
-	]
-    ]
-
-    "Modified: / 6.6.1998 / 19:50:32 / cg"
 ! !
 
 !MenuPanel methodsFor:'accessing-dimensions'!
@@ -1273,11 +1207,7 @@
     |item|
 
     (explicitExtent ~~ true) ifTrue:[
-	(item := self itemAt:1) notNil ifTrue:[
-	    self rearrangeItems.
-	  ^ item height
-	].
-	^ 4 + (font height + (font descent * 2)).
+        ^ self preferredExtent y
     ].
     ^ super height
 !
@@ -1285,69 +1215,102 @@
 preferredExtent
     "compute and returns my preferred extent
     "
-    |hasMenu shCtKey
-     x        "{ Class:SmallInteger }"
-     y        "{ Class:SmallInteger }"
-     elY      "{ Class:SmallInteger }"
-     space    "{ Class:SmallInteger }"
-     hrzInset "{ Class:SmallInteger }"
+    |hasMenu shCtKey extent showAcc sck menuFont
+     x           "{ Class:SmallInteger }"
+     y           "{ Class:SmallInteger }"
+     elY         "{ Class:SmallInteger }"
+     space       "{ Class:SmallInteger }"
+     hrzInset    "{ Class:SmallInteger }"
+     size        "{ Class:SmallInteger }"
+     buttonInset "{ Class:SmallInteger }"
+     labelInset  "{ Class:SmallInteger }"
     |
 
-    self numberOfItems == 0 ifTrue:[
+    (size := items size) == 0 ifTrue:[
         ^ 32 @ 32
     ].
-    space := (items size + 1) * itemSpace.
-
-    self isFitPanel ifTrue:[
-        x := 0
-    ] ifFalse:[
-        x := groupSizes size * groupDividerSize.
-    ].
-    hrzInset := Item horizontalInset.
+
+    (superMenu notNil and:[(menuFont := superMenu font) ~~ font]) ifTrue:[
+        super font:(menuFont onDevice:device)
+    ].
+
+    buttonInset := 2 * (DefaultButtonItemSpace abs).
+
+    self isPopUpView ifFalse:[
+        labelInset := 2 * (DefaultEnteredLevel abs).
+    ] ifTrue:[
+        labelInset := 0.
+    ].
+
+    x := 0.
+    y := 0.
 
     self verticalLayout ifFalse:[
-        "/ horizontal - add x-extents; take max of y-extents
-        y := 0.
-
-        self do:[:el| |elPref|
-            el isVisible ifTrue:[
-                elPref := el preferredExtent.
-                x := x + elPref x.
-                elY := elPref y.
+        "/ HORIZONTAL LAYOUT
+
+        items keysAndValuesDo:[:key :el| |eX eY|
+            extent := el preferredExtent.
+
+            "/ check for visibility (extent x ~~ 0)
+            (eX := extent x) ~~ 0 ifTrue:[
+                eY := extent y.
+                
                 el isButton ifTrue:[
-                    elY := elY + (2 * DefaultButtonItemSpace).
-                    x := x + (2 * DefaultButtonItemSpace).
+                    eX := eX + buttonInset.
+                    eY := eY + buttonInset.
+                ] ifFalse:[
+                    eX := eX + labelInset.
+                    eY := eY + labelInset.
                 ].
-                y := y max:elY.
+                key ~~ size ifTrue:[
+                    (self hasGroupDividerAt:key) ifTrue:[
+                        x := x + groupDividerSize
+                    ] ifFalse:[
+                        x := x + itemSpace
+                    ]
+                ].
+                x := eX + x.
+                y := eY max:y.
             ]
-        ].
-        x := x + space.
+        ]
     ] ifTrue:[
-        "/ vertical - add y-extents
         hasMenu := false.
         shCtKey := 0.
+        showAcc := MenuView showAcceleratorKeys == true.
         y := x.
         x := 0.
 
-        self do:[:el| |l e|
-            el isVisible ifTrue:[
-                (l := el rawLabel) notNil ifTrue:[
-                    (e := l widthOn:self) > x ifTrue:[x := e].
-
-                    el hasSubmenu ifTrue:[
-                        hasMenu := true
-                    ].
-
-                    (     (l := el shortcutKeyAsString) notNil
-                     and:[(e := l widthOn:self) > shCtKey]
-                    ) ifTrue:[
-                        shCtKey := e
-                    ].
+        items keysAndValuesDo:[:key :el| |eX eY|
+            extent := el preferredExtent.
+
+            "/ check for visibility (extent x ~~ 0)
+            (eX := extent x) ~~ 0 ifTrue:[
+                eY := extent y.
+
+                el isButton ifTrue:[
+                    eX := eX + buttonInset.
+                    eY := eY + buttonInset.
+                ] ifFalse:[
+                    eX := eX + labelInset.
+                    eY := eY + labelInset.
                 ].
-                y := y + el preferredExtent y
-            ]
+                hasMenu ifFalse:[
+                    hasMenu := el hasSubmenu
+                ].
+                (showAcc and:[(sck := el shortcutKeyAsString) notNil]) ifTrue:[
+                    shCtKey := shCtKey max:(sck widthOn:self)
+                ].
+                key ~~ size ifTrue:[
+                    (self hasGroupDividerAt:key) ifTrue:[
+                        y := y + groupDividerSize
+                    ] ifFalse:[
+                        y := y + itemSpace
+                    ]
+                ].
+                y := eY + y.
+                x := eX max:x.
+            ].
         ].
-        x := x + hrzInset.
 
         (hasMenu or:[shCtKey ~~ 0]) ifTrue:[
             shortKeyInset := x + Item labelRightOffset.
@@ -1357,16 +1320,14 @@
                 x := x + (Item shortcutKeyOffset) 
             ]
         ].
-        y := y + space.
-        x := x + hrzInset.
-    ].
-
-    (superView notNil and:[DefaultEnteredLevel ~~ 0]) ifTrue:[
-        "/ is top menu and has an enterLevel
-        y :=  2 * DefaultEnteredLevel + y.
-    ].
-
-    ^ (x @ y) + margin.
+"/ to have a small inset
+        y := y + 1.
+"/        x := x + 1.
+    ].
+    x := x + margin + margin.
+    y := y + margin + margin.
+
+  ^ x @ y
 !
 
 shortKeyInset
@@ -1436,6 +1397,8 @@
 fitFirstPanel
     "gets true if the first panel in the menu hierarchy must be fit 
      to the extent of its superView
+
+     NOT SUPPORTED
     "
     ^ fitFirstPanel
 !
@@ -1443,11 +1406,10 @@
 fitFirstPanel:aState
     "sets true if the first panel in the menu hierarchy must be fit 
      to the extent of its superView
-    "
-    (fitFirstPanel == aState or:[self isPopUpView]) ifFalse:[
-	fitFirstPanel := aState.
-	self mustRearrange
-    ]
+
+     NOT SUPPORTED
+    "
+    fitFirstPanel := aState.
 !
 
 groupDividerSize
@@ -1530,6 +1492,7 @@
 verticalLayout
     "get the layout: or vertical( true ) or horizontal( false )
     "
+    superMenu notNil ifTrue:[^ true].
   ^ (self menuAdornmentAt:#verticalLayout)
 !
 
@@ -1605,7 +1568,6 @@
 
     self initPopUpDependentStyle:true.
     self rearrangeItemsIfItemVisibilityChanged.
-"/    self rearrangeItems.
 
     aBoolean ifTrue:[
         self fixSize.
@@ -1867,172 +1829,147 @@
 !
 
 rearrangeGroups
-    |layout
+    "implements the groupIdentifier #right in a horizontal menu
+    "
+    |layout point
      dltX  "{ Class:SmallInteger }"
      start "{ Class:SmallInteger }"
     |
 
     (self isPopUpView or:[self verticalLayout]) ifTrue:[
-	^ self
+        ^ self
     ].
 
     layout := items last layout.
 
-    (dltX := width "- margin" "- 2" - layout right) <= 0 ifTrue:[
-	^ self  "/ no free space
+    (dltX := width - margin - layout right) <= 0 ifTrue:[
+        ^ self  "/ no free space
     ].
     start := items findFirst:[:anItem| anItem startGroup == #right ].
 
     start == 0 ifTrue:[
-	^ self  "/ no item detected
-    ].
-
-    "/ change layout
+        ^ self  "/ no item detected
+    ].
+    point := dltX @ 0.
+
+    "/ move items layout to right
 
     items from:start do:[:anItem|
-	anItem isVisible ifTrue:[
-	    layout := anItem layout.
-	    layout  left:(layout  left + dltX).
-	    layout right:(layout right + dltX).
-	]
+        anItem isVisible ifTrue:[
+            anItem layout moveBy:point.
+        ]
     ].
 !
 
 rearrangeItems
-    "recompute layout of my items
-    "
-    |expLast e grpDivSz layout isVert labelInset
-     x  "{ Class:SmallInteger }"
-     y  "{ Class:SmallInteger }"
-     noItems "{ Class:SmallInteger }"
-     f
+    "recompute the layout of each item
+    "
+    |isVertical extent
+     x           "{ Class:SmallInteger }"
+     y           "{ Class:SmallInteger }"
+     x0          "{ Class:SmallInteger }"
+     y0          "{ Class:SmallInteger }"
+     x1          "{ Class:SmallInteger }"
+     y1          "{ Class:SmallInteger }"
+     size        "{ Class:SmallInteger }"
+     inset       "{ Class:SmallInteger }"
+     labelInset  "{ Class:SmallInteger }"
+     buttonInset "{ Class:SmallInteger }"
     |
-
-    mustRearrange ifFalse:[ ^ self ].
-
-"/  fetch font from superMenu
-    (superMenu notNil and:[(f := superMenu font) ~~ font]) ifTrue:[
-        super font:(f onDevice:device)
-    ].
-    (noItems := items size) == 0 ifTrue:[
+    (mustRearrange and:[(size := items size) ~~ 0]) ifFalse:[
         mustRearrange := false.
       ^ self
     ].
-    expLast  := false.
-    isVert   := self verticalLayout.
-    labelInset := 0.
-
-    superView notNil ifTrue:[
-        DefaultEnteredLevel ~~ 0 ifTrue:[labelInset := 1]
-    ].
-
-    self hasGroupDividers ifTrue:[
-        self isFitPanel ifFalse:[
-            grpDivSz := groupDividerSize
-        ] ifTrue:[
-            expLast := true.
-            x := margin.
-            e := self computeExtent.
-
-            isVert ifTrue:[
-                items do:[:el | x := x + el preferredExtent y].
-                y := e y.
-            ] ifFalse:[
-                items do:[:el|x := x + el preferredExtent x].
-                y := e x.
-            ].
-            x := x + (noItems + 1 * itemSpace).
-
-            (grpDivSz := (y - x) // (groupSizes size)) <= 0 ifTrue:[
-                grpDivSz := nil
-            ].
-            x > (width-margin) ifTrue:[
-                grpDivSz := nil
-            ]
-        ]
+    isVertical  := self verticalLayout.
+    buttonInset := DefaultButtonItemSpace abs.
+
+    self isPopUpView ifFalse:[
+        labelInset := DefaultEnteredLevel abs.
+    ] ifTrue:[
+        labelInset := 0
     ].
 
     (self isPopUpView or:[explicitExtent ~~ true]) ifTrue:[
-        e := self preferredExtent copy.
+        extent := self preferredExtent copy.
 
         self isPopUpView ifFalse:[
-            isVert ifTrue:[e y:1.0]
-                  ifFalse:[e x:1.0]
+            isVertical ifTrue:[extent y:1.0] ifFalse:[extent x:1.0]
         ].
-        self extent:e
+        self extent:extent
     ] ifFalse:[
-        e := self computeExtent
+        extent := self computeExtent
     ].
 
     x := y := margin.
 
-    isVert ifTrue:[y := y + itemSpace]
-          ifFalse:[x := x + itemSpace].
-
-    self keysAndValuesDo:[:anIndex :el| |org corn elPref|
-        el isVisible ifTrue:[
-            el isButton ifTrue:[
-                org := Point x:(x+DefaultButtonItemSpace) y:(y+DefaultButtonItemSpace).
-            ] ifFalse:[
-                org := Point x:x y:y.
-            ].
-            elPref := el preferredExtent.
-            isVert ifTrue:[
-                y := y + elPref y.
-                corn := (e x - margin @ y).
-                el isButton ifTrue:[
-                    corn := corn - (DefaultButtonItemSpace @ 0).
-                    el layout:(Rectangle origin:org corner:corn).
-                    y := y + (2 * DefaultButtonItemSpace).
-                ] ifFalse:[
-                    el layout:(Rectangle origin:org corner:corn).
-                ].
-                y := y + itemSpace.
-            ] ifFalse:[
-                x := x + elPref x.
+    isVertical ifFalse:[
+        y0 := margin.
+        y1 := extent y - margin.
+
+        items keysAndValuesDo:[:anIndex :el|
+            el isVisible ifFalse:[
+                el layout:(Rectangle left:x top:y0 right:x bottom:y1)
+            ] ifTrue:[
                 el isButton ifTrue:[
-                    x := x + DefaultButtonItemSpace.
-                    corn := (x @ (e y - margin)).
-                    corn := corn - (0 @ DefaultButtonItemSpace).
-                    el layout:(Rectangle origin:org corner:corn).
-                    x := x + DefaultButtonItemSpace.
+                    inset := DefaultButtonItemSpace
                 ] ifFalse:[
-                    corn := (x @ (e y - labelInset)).
-                    el layout:(Rectangle origin:org corner:corn).
+                    inset := labelInset
                 ].
-                x := x + itemSpace.
+                x0 := x  + inset.
+                x1 := x0 + el preferredExtent x.
+                el layout:(Rectangle left:x0 top:(y0 + inset) right:x1 bottom:(y1 - inset)).
+                x := x1 + inset.
+
+                size ~~ anIndex ifTrue:[
+                    (self hasGroupDividerAt:anIndex) ifTrue:[
+                        x := x + groupDividerSize
+                    ] ifFalse:[
+                        x := x + itemSpace
+                    ]
+                ]
             ].
-
-            (grpDivSz notNil and:[self hasGroupDividerAt:anIndex]) ifTrue:[
-                isVert ifTrue:[y := y + grpDivSz]
-                      ifFalse:[x := x + grpDivSz]
+        ].
+    ] ifTrue:[
+        x0 := margin.
+        x1 := extent x - margin.  "/ -1
+
+        items keysAndValuesDo:[:anIndex :el|
+            el isVisible ifFalse:[
+                el layout:(Rectangle left:x0 top:y right:x1 bottom:y)
+            ] ifTrue:[
+                el isButton ifTrue:[
+                    inset := DefaultButtonItemSpace
+                ] ifFalse:[
+                    inset := labelInset
+                ].
+                y0 := y  + inset.
+                y1 := y0 + el preferredExtent y.
+                el layout:(Rectangle left:(x0 + inset) top:y0 right:(x1 - inset) bottom:y1).
+                y := y1 + inset.
+
+                size ~~ anIndex ifTrue:[
+                    (self hasGroupDividerAt:anIndex) ifTrue:[
+                        y := y + groupDividerSize
+                    ] ifFalse:[
+                        y := y + itemSpace
+                    ]
+                ]
             ]
-        ] ifFalse:[
-            org := Point x:x y:y.
-            el layout:(Rectangle origin:org corner:org)
-        ]
-    ].
-
-    expLast ifTrue:[
-        e := items last.
-
-        e isVisible ifTrue:[
-            layout := items last layout.
-
-            isVert ifTrue:[layout bottom:((self extent y) + 1)]
-                  ifFalse:[layout  right:((self extent x) + 1)].
         ]
     ].
     self rearrangeGroups.
     mustRearrange := false.
 
-    "Modified: / 19.1.1999 / 16:00:14 / cg"
+
+
 !
 
 rearrangeItemsIfItemVisibilityChanged
-    "if I have any items with changing visibility, rearrange"
-
+    "check for items which can change its visibility;
+     if at least one item exists, rearrange all items
+    "
     items isNil ifTrue:[^ self].
+
     items do:[:item |
         item canChangeVisibility ifTrue:[
             mustRearrange := true.
@@ -2045,91 +1982,92 @@
 redrawX:x y:y width:w height:h
     "redraw a rectangle
     "
-    |start end isVrt x1 x2 y1 y2 item layout lnSz hrzInset 
-     prevClip didRearrange|
+    |isVertical item layout prevClip
+     x1             "{ Class:SmallInteger }"
+     x2             "{ Class:SmallInteger }"
+     y1             "{ Class:SmallInteger }"
+     y2             "{ Class:SmallInteger }"
+     start          "{ Class:SmallInteger }"
+     stop           "{ Class:SmallInteger }"
+     size           "{ Class:SmallInteger }"
+     groupDivInset  "{ Class:SmallInteger }"
+    |
 
     (shown and:[w ~~ 0]) ifFalse:[^ self].
 
-    self  paint:(self backgroundColor).
-    self  clearRectangleX:x y:y width:w height:h.
-
-    isVrt := self verticalLayout.
-    end   := items size.
-
-    (didRearrange := mustRearrange) ifTrue:[
-        self isPopUpView not ifTrue:[
-            explicitExtent := true
-        ].
+    mustRearrange ifTrue:[
+        self isPopUpView not ifTrue:[explicitExtent := true].
         self rearrangeItems.
-        start := 1
+      ^ self invalidate
+    ].
+
+    self paint:(self backgroundColor).
+    self clearRectangleX:x y:y width:w height:h.
+
+    (size := items size) == 0 ifTrue:[
+        ^ self
+    ].
+
+    isVertical := self verticalLayout.
+
+    isVertical ifTrue:[
+        start := items findFirst:[:el| el layout bottom > y ].
+        start == 0 ifTrue:[ ^ self ].
+        y1 := y + h.
+        stop := items findFirst:[:el| el layout top > y1 ] startingAt:(start + 1).
     ] ifFalse:[
-        end == 0 ifTrue:[ ^ self ].
-
-        isVrt ifTrue:[
-            start := self findFirst:[:el| (el layout bottom) >= y ].
-            start == 0 ifTrue:[ ^ self ].
-            end := y + h.
-            end := self findLast:[:el| (el layout top) < end ].
-        ] ifFalse:[
-            start := self findFirst:[:el| (el layout right) >= x ].
-            start == 0 ifTrue:[ ^ self ].
-            end := x + w.
-            end := self findLast:[:el| (el layout left) < end ].
+        start := items findFirst:[:el| el layout right > x ].
+        start == 0 ifTrue:[ ^ self ].
+        x1  := x + w.
+        stop := items findFirst:[:el| el layout left > x1] startingAt:(start + 1).
+    ].
+
+    stop == 0 ifTrue:[stop := size] ifFalse:[stop := stop - 1].
+
+    (groupSizes size ~~ 0 and:[self showGroupDivider]) ifTrue:[
+        groupDivInset := groupDividerSize // 2.
+
+        groupDivInset ~~ 0 ifTrue:[
+            (start ~~ 1 and:[self hasGroupDividerAt:(start-1)]) ifTrue:[
+                start := start - 1
+            ]
         ].
-
-        (start ~~ 1 and:[self hasGroupDividerAt:(start-1)]) ifTrue:[
-            start := start - 1
-        ]
-    ].
-
-    (     self hasGroupDividers
-     and:[self showGroupDivider
-     and:[self isFitPanel not]]
-    ) ifTrue:[
-        lnSz := groupDividerSize // 2
-    ].
-
-    end == 0 ifTrue:[^ self ].
-
-    hrzInset := items first horizontalInset.
-
-    didRearrange ifFalse:[
-        prevClip := clipRect.
-        self clippingRectangle:(Rectangle left:x top:y width:w height:h).
-    ].
-
-    start to:end do:[:i|
+    ] ifFalse:[
+        groupDivInset := 0
+    ].
+
+    prevClip := clipRect.
+    self clippingRectangle:(Rectangle left:x top:y width:w height:h).
+
+    start to:stop do:[:i|
         item := items at:i.
         item redraw.
 
-        (lnSz notNil and:[self hasGroupDividerAt:i]) ifTrue:[
+        (groupDivInset ~~ 0 and:[i ~~ size and:[self hasGroupDividerAt:i]]) ifTrue:[
             layout := item layout.
 
-            isVrt ifTrue:[
-                x1 := layout left  + hrzInset.
-                x2 := layout right - hrzInset.
-                y1 := (layout bottom) + lnSz.
+            isVertical ifTrue:[
+                x1 := layout left.
+                x2 := layout right.
+                y1 := layout bottom + groupDivInset.
                 y2 := y1.
             ] ifFalse:[
-                x1 := (layout right) + lnSz.
-                x2 := x1.
                 y1 := layout top.
                 y2 := layout bottom.
+                x1 := layout right + groupDivInset.
+                x2 := x1.
             ].
-            self paint:(self shadowColor).
+            self paint:shadowColor.
             self displayLineFromX:x1 y:y1 toX:x2 y:y2.
-            self paint:(self lightColor).
-
-            isVrt ifTrue:[y1 := y1 + 1. y2 := y1 ]
-                 ifFalse:[x1 := x1 + 1. x2 := x1 ].
+            self paint:lightColor.
+
+            isVertical ifTrue:[y1 := y1 + 1. y2 := y1 ]
+                      ifFalse:[x1 := x1 + 1. x2 := x1 ].
 
             self displayLineFromX:x1 y:y1 toX:x2 y:y2
         ]
     ].
-
-    didRearrange ifFalse:[
-        self clippingRectangle:prevClip
-    ].
+    self clippingRectangle:prevClip.
 
     "Modified: / 21.5.1999 / 20:14:07 / cg"
 ! !
@@ -2220,30 +2158,205 @@
 buttonMotion:state x:x y:y
     "open or close the corresponding submenus
     "
-    |menu point sensor sel|
-
-    (    (sensor := self sensor) notNil
-     and:[sensor hasButtonMotionEventFor:nil]
+    |menue point sensor|
+
+    sensor := self sensor.
+
+    (sensor isNil or:[sensor hasButtonMotionEventFor:nil]) ifTrue:[
+        ^ self
+    ].
+    menue := self detectGrabMenu.
+    point := menue translateGrabPoint:(x@y).
+    menue handleButtonMotion:state x:(point x) y:(point y).
+
+    (self isPopUpView or:[sensor anyButtonPressed]) ifTrue:[
+        ^ self
+    ].
+
+    (selection notNil and:[selection currentSubmenu isNil]) ifTrue:[
+        "/ selection on grabView withou a submenu (Button ...); check whether moving out
+        (self containsPointX:x y:y) ifFalse:[
+            ^ self accept:nil
+        ]
+    ].
+
+!
+
+buttonPress:button x:x y:y
+    "any button pressed; open or close the corresponding submenus
+    "
+    |srcPoint dstMenu dstPoint dstItem|
+
+    srcPoint := x@y.
+    dstMenu  := self detectMenuAtGrabPoint:srcPoint.
+
+    dstMenu isNil ifTrue:[
+        ^ self accept:nil.
+    ].
+
+    dstPoint := dstMenu translateGrabPoint:srcPoint.
+    dstItem  := dstMenu itemAtX:(dstPoint x) y:(dstPoint y).
+    dstMenu selection:dstItem.
+!
+
+buttonRelease:button x:x y:y
+    "button release action; accept selection and close all views
+    "
+    |topMenu dstMenu item srcPoint dstPoint|
+
+    topMenu := self topMenu.
+    dstMenu := topMenu activeMenu.
+
+    (    dstMenu selection notNil
+     or:[dstMenu isPopUpView not
+     or:[(OperatingSystem millisecondTimeDeltaBetween:(Time millisecondClockValue)
+         and:(dstMenu mapTime)) > 400]]
     ) ifTrue:[
+        srcPoint := x@y.
+        
+        (     (dstMenu := self detectMenuAtGrabPoint:srcPoint) notNil
+         and:[(item    := dstMenu selection) notNil]
+        ) ifTrue:[
+            item currentSubmenu notNil ifTrue:[
+                dstMenu selection:nil.
+
+                (selection isNil and:[self isPopUpView not]) ifTrue:[
+                    self accept:nil
+                ].
+                ^ self
+            ].
+            dstPoint := dstMenu translateGrabPoint:srcPoint.
+
+            (dstMenu itemAtX:(dstPoint x) y:(dstPoint y)) == dstMenu selection ifFalse:[
+                item := nil
+            ].
+            topMenu acceptItem:item inMenu:dstMenu.
+        ].
+        (selection notNil and:[dstMenu == self]) ifTrue:[
+            selection currentSubmenu notNil ifTrue:[
+                ^ self
+            ]
+        ].
+        self accept:nil.
+    ].
+
+!
+
+keyPress:key x:x y:y
+    "any key is pressed
+    "
+    |menu point|
+
+       (key == #Tab 
+    or:[key == #FocusNext
+    or:[key == #FocusPrevious]]) ifTrue:[
+        self accept:nil.
+      ^ super keyPress:key x:x y:y
+    ].
+
+    menu := self detectGrabMenu.
+
+    key == #Escape ifTrue:[
+        "/ must hide the active menu
+
+        menu superMenu notNil ifTrue:[
+            menu superMenu selection:nil.
+        ] ifFalse:[
+            self accept:nil
+        ].
         ^ self
     ].
 
-    sensor anyButtonPressed ifFalse:[
+    [   menu shown ifTrue:[
+            point := menu translateGrabPoint:(x@y).
+            menu handleKeyPress:key x:(point x) y:(point y).
+
+            selection isNil ifTrue:[
+                self accept:nil.
+            ].
+          ^ self
+        ].
+        (menu := menu superMenu) notNil
+    ] whileTrue.
+
+    self accept:nil
+!
+
+pointerLeave:state
+
+    self detectGrabMenu handlePointerLeave:state.
+
+    self isPopUpView ifTrue:[
+        ^ self
+    ].
+    (selection notNil and:[selection currentSubmenu isNil]) ifTrue:[
+        "/ selection on grabView withou a submenu (Button ...); check whether moving out
+        self sensor anyButtonPressed ifFalse:[
+            ^ self accept:nil
+        ]
+    ].
+
+!
+
+sizeChanged:how
+    "redraw #right groups
+    "
+    |index layout invRect w right|
+
+    (mustRearrange or:[self isPopUpView]) ifTrue:[
+        ^ super sizeChanged:how
+    ].
+
+    index := self findFirst:[:anItem| anItem startGroup == #right ].
+        
+    index ~~ 0 ifTrue:[
+        (shown not or:[index == 1]) ifTrue:[
+            self mustRearrange.
+        ] ifFalse:[
+            layout := (items at:(index -1)) layout.
+            right  := 1 + layout right.
+
+            (w := width - right) > margin ifTrue:[
+                invRect := Rectangle left:right top:0 width:w height:height.
+
+                items from:index do:[:anItem|
+                    anItem isVisible ifTrue:[
+                        layout := anItem layout.
+                        layout setLeft:right.
+                        right := layout right.
+                    ]
+                ].
+                self rearrangeGroups.
+                self invalidate:invRect
+            ]
+        ]
+    ].
+    super sizeChanged:how
+! !
+
+!MenuPanel methodsFor:'event handling processing'!
+
+handleButtonMotion:state x:x y:y
+    "open or close the corresponding submenus
+    "
+    |menu point sel|
+
+    self sensor anyButtonPressed ifFalse:[
         "/ highlight enterItem if no selection exists
         selection isNil ifTrue:[
             (self containsPointX:x y:y) ifTrue:[
                 ((sel := self itemAtX:x y:y) isNil or:[sel canSelect not]) ifTrue:[
-                    ^ self itemEntered:nil
+                    ^ self pointerEntersItem:nil
                 ].
                 (DefaultSelectionFollowsMouse and:[superMenu notNil]) ifTrue:[
                     self selection:sel
                 ] ifFalse:[
-                    self itemEntered:sel
+                    self pointerEntersItem:sel
                 ].
                 ^ self
             ].
         ].
-        self itemEntered:nil.
+        self pointerEntersItem:nil.
 
         (DefaultSelectionFollowsMouse and:[(menu := self superMenuAtX:x y:y) notNil]) ifTrue:[
             point := self translatePoint:(x@y) to:menu.
@@ -2255,85 +2368,32 @@
         ].
       ^ self
     ].
-    self itemEntered:nil.
-
-    (self containsPointX:x y:y) ifTrue:[
-        (sel := self itemAtX:x y:y) notNil ifTrue:[
-            self selection:sel.
-        ].
-        ^ self
-    ].
+    self pointerEntersItem:nil.
 
     (menu := self superMenuAtX:x y:y) isNil ifTrue:[
         self isPopUpView ifTrue:[
-            self selection:nil.
+            self selection:nil
         ].
         ^ self
     ].
 
-    point := self translatePoint:(x@y) to:menu.
-    sel   := menu itemAtX:(point x) y:(point y).
-
-    (sel isNil and:[menu isPopUpView not]) ifTrue:[
-        sel := menu selection.
-    ].
-    menu selection:sel
-
-
-!
-
-buttonPress:button x:x y:y
-    "any button pressed; open or close the corresponding submenus
-    "
-    |menu point item|
-
-    menu := self superMenuAtX:x y:y.
-
-    menu isNil ifTrue:[
-        menu := self topMenu.
+    menu == self ifTrue:[
+        (sel := self itemAtX:x y:y) notNil ifTrue:[
+            self selection:sel.
+        ].
     ] ifFalse:[
         point := self translatePoint:(x@y) to:menu.
-        item  := menu itemAtX:(point x) y:(point y)
-    ].
-    menu selection:item.
-
-    self requestFocus
-!
-
-buttonRelease:button x:x y:y
-    "button release action; accept selection and close all views
-    "
-    |menu item|
-
-    menu := self topMenu activeMenu.
-
-    (    menu selection notNil
-     or:[menu isPopUpView not
-     or:[(OperatingSystem millisecondTimeDeltaBetween:(Time millisecondClockValue)
-                                and:(menu mapTime)) > 400]]
-    ) ifTrue:[
-        item := nil.
-
-        (     (menu := self superMenuAtX:x y:y) notNil
-         and:[(item := menu selection) notNil
-         and:[item hasSubmenu]]
-        ) ifTrue:[
-            menu selection:nil
-        ] ifFalse:[
-            (    lastButtonSelected isNil
-             or:[item isNil
-             or:[(menu itemAtX:x y:y) == lastButtonSelected]]
-            ) ifFalse:[
-                item := nil
-            ].
-            self acceptItem:item inMenu:menu
-        ]
-    ].
-
-    "Modified: / 27.2.1998 / 17:41:23 / cg"
-!
-
-cursorPressed:aKey
+        sel   := menu itemAtX:(point x) y:(point y).
+
+        (sel isNil and:[menu isPopUpView not]) ifTrue:[
+            sel := menu selection.
+        ].
+        menu selection:sel
+    ]
+
+!
+
+handleCursorKey:aKey
     "handle a cursor key
     "
     |next submenu item
@@ -2342,27 +2402,34 @@
      first "{ Class:SmallInteger }"
     |
 
-    (self selection isNil 
-    and:[superMenu notNil]) ifTrue:[
-	^ superMenu cursorPressed:aKey
+    (selection isNil and:[superMenu notNil]) ifTrue:[
+        ^ superMenu handleCursorKey:aKey
     ].
 
     self verticalLayout ifTrue:[
-	aKey == #CursorLeft  ifTrue:[^ self selection:nil].
-	aKey ~~ #CursorRight ifTrue:[next := aKey == #CursorDown].
+        aKey == #CursorLeft ifTrue:[
+            ^ self selection:nil
+        ].
+        aKey ~~ #CursorRight ifTrue:[
+            next := aKey == #CursorDown
+        ].
     ] ifFalse:[
-	aKey == #CursorUp ifTrue:[^ self selection:nil].
-	aKey ~~ #CursorDown ifTrue:[next := aKey == #CursorRight].        
+        aKey == #CursorUp ifTrue:[
+            ^ self selection:nil
+        ].
+        aKey ~~ #CursorDown ifTrue:[
+            next := aKey == #CursorRight
+        ].        
     ].
 
     next isNil ifTrue:[
-	(item := self selection) notNil ifTrue:[
-	    (submenu := item submenu) notNil ifTrue:[
-		idx := submenu findFirst:[:el| el canSelect ].
-	      ^ submenu selectionIndex:idx
-	    ].
-	  ^ self selection:nil
-	].
+        (item := self selection) notNil ifTrue:[
+            (submenu := item submenu) notNil ifTrue:[
+                idx := submenu findFirst:[:el| el canSelect ].
+              ^ submenu selectionIndex:idx
+            ].
+          ^ self selection:nil
+        ].
       ^ self
     ].
     first := self findFirst:[:el| el canSelect ].
@@ -2372,43 +2439,81 @@
     n   := 1 + (self sensor compressKeyPressEventsWithKey:aKey).
 
     n timesRepeat:[
-	next ifTrue:[
-	    [((idx := idx + 1) <= items size and:[(items at:idx) canSelect not])
-	    ] whileTrue.
-
-	    idx > items size ifTrue:[
-		idx := first
-	    ].
-	] ifFalse:[    
-	    [((idx := idx - 1) > 0  and:[(items at:idx) canSelect not])
-	    ] whileTrue.
+        next ifTrue:[
+            [((idx := idx + 1) <= items size and:[(items at:idx) canSelect not])
+            ] whileTrue.
+
+            idx > items size ifTrue:[
+                idx := first
+            ].
+        ] ifFalse:[    
+            [((idx := idx - 1) > 0  and:[(items at:idx) canSelect not])
+            ] whileTrue.
             
-	    idx < 1 ifTrue:[ idx := self findLast:[:el| el canSelect ] ]
-	]
+            idx < 1 ifTrue:[ idx := self findLast:[:el| el canSelect ] ]
+        ]
     ].
     self selectionIndex:idx.
 
 !
 
-itemEntered:anItem
-    "an item is entered; check whether display of item changed; than
-     force a redraw of the item
+handleKeyPress:key x:x y:y
+    "any key is pressed
+    "
+    |item|
+
+    (key == #Return or:[key == Character space]) ifTrue:[
+        ^ self accept.
+    ].
+
+    key isCharacter ifFalse:[
+        (     key == #CursorDown or:[key == #CursorUp
+          or:[key == #CursorLeft or:[key == #CursorRight]]]
+        ) ifTrue:[
+            self handleCursorKey:key
+        ] ifFalse:[
+            self processShortcutKeyInMenuBar:key
+        ].
+        ^ self
+    ].
+
+    (item := self detectItemForKey:key) notNil ifTrue:[
+        self selection:item.
+    ] ifFalse:[
+        superMenu notNil ifTrue:[
+            item := superMenu detectItemForKey:key.
+
+            (item notNil or:[superMenu superMenu notNil]) ifTrue:[
+                superMenu selection:item
+            ]
+        ]
+    ].
+!
+
+handlePointerLeave:state
+    self  pointerEntersItem:nil.
+    super pointerLeave:state
+!
+
+pointerEntersItem:anItemOrNil
+    "the pointer moves over an item or nil; restore the old item and
+     redraw the new item highlighted.
     "
     |oldItem newItem|
 
-    (     anItem notNil
-     and:[anItem canSelect
+    (     anItemOrNil notNil
+     and:[anItemOrNil canSelect
      and:[selection isNil
      and:[self isPopUpView not]]]) ifTrue:[
-        anItem isButton ifTrue:[
+        anItemOrNil isButton ifTrue:[
             (    buttonEnteredBgColor ~= ButtonPassiveBackgroundColor
              or:[ButtonEnteredLevel   ~~ ButtonPassiveLevel]
             ) ifTrue:[
-                newItem := anItem
+                newItem := anItemOrNil
             ]
         ] ifFalse:[
             DefaultEnteredLevel ~~ 0 ifTrue:[
-                newItem := anItem
+                newItem := anItemOrNil
             ]
         ]
     ].
@@ -2428,71 +2533,6 @@
 
 !
 
-keyPress:key x:x y:y
-    "any key is pressed
-    "
-    |item|
-
-    shown ifFalse:[
-        superMenu notNil ifTrue:[superMenu keyPress:key x:x y:y].
-      ^ self
-    ].
-
-    key == #Return ifTrue:[^ self accept].
-    key == Character space ifTrue:[^ self accept].
-
-    "/ cg: must hide the active menu ...
-    key == #Escape ifTrue:[
-        superMenu notNil ifTrue:[superMenu selection:nil].
-      ^ self
-    ].
-
-    "/ tabbing to the next view ...
-       (key == #Tab 
-    or:[key == #FocusNext
-    or:[key == #FocusPrevious]]) ifTrue:[
-        "/ if there is a menu open, hide it ...
-        superMenu notNil ifTrue:[
-            superMenu selection:nil
-        ] ifFalse:[
-            super keyPress:key x:x y:y
-        ].
-        ^ self
-    ].
-
-    (     key == #CursorDown or:[key == #CursorUp
-      or:[key == #CursorLeft or:[key == #CursorRight]]]
-    ) ifTrue:[
-        ^ self cursorPressed:key
-    ].
-
-    (self processShortcutKeyInMenuBar:key) ifTrue:[
-        ^ self
-    ].
-
-    (item := self detectItemForKey:key) notNil ifTrue:[
-        ^ self selection:item.
-    ].
-
-    superMenu notNil ifTrue:[
-        item := superMenu detectItemForKey:key.
-
-        (item notNil or:[superMenu superMenu notNil]) ifTrue:[
-            superMenu selection:item
-        ]
-    ].
-    "/ nothing changed, nothing closed
-
-    "Modified: / 29.1.2000 / 23:24:27 / cg"
-!
-
-pointerLeave:state
-    self itemEntered:nil.
-    super pointerLeave:state
-
-    "Created: / 20.8.1998 / 14:04:29 / cg"
-!
-
 processShortcutKeyEventInMenuBar:event
     "an event as forwarded from the keyboardProcessor -
      if there is a short-key for that character, process it
@@ -2520,45 +2560,55 @@
         ]
     ].
     ^ false
-!
-
-sizeChanged:how
-    "redraw #right groups
-    "
-    |index layout invRect w right|
-
-    mustRearrange ifTrue:[
-        ^ super sizeChanged:how
-    ].
-
-    index := self findFirst:[:anItem| anItem startGroup == #right ].
-    index ~~ 0 ifTrue:[
-        (shown not or:[index == 1]) ifTrue:[
-            self mustRearrange.
-        ] ifFalse:[
-            layout := (items at:(index -1)) layout.
-            right  := 1 + layout right.
-
-            (w := width - right) > margin ifTrue:[
-                invRect := Rectangle left:right top:0 width:w height:height.
-
-                items from:index do:[:anItem|
-                    anItem isVisible ifTrue:[
-                        layout := anItem layout.
-                        layout setLeft:right.
-                        right := layout right.
-                    ]
-                ].
-                self rearrangeGroups.
-                self invalidate:invRect
-            ]
-        ]
-    ].
-    super sizeChanged:how
 ! !
 
 !MenuPanel methodsFor:'grabbing'!
 
+doGrab
+    relativeGrabOrigin := nil.
+
+    superMenu notNil ifTrue:[
+        superMenu doGrab
+    ] ifFalse:[
+        hasImplicitGrap ~~ true ifTrue:[
+            self grabMouseAndKeyboard.
+            hasImplicitGrap := true
+        ]
+    ]
+!
+
+doUngrab:forceDo
+    |winGrp|
+
+    relativeGrabOrigin := nil.
+
+    superMenu notNil ifTrue:[
+        forceDo ifTrue:[
+            superMenu doUngrab:true
+        ].
+        ^ self
+    ].
+
+    hasImplicitGrap ~~ true ifTrue:[
+        ^ self
+    ].
+
+    forceDo ifFalse:[
+        self selection notNil ifTrue:[
+            ^ self
+        ].
+        
+        (winGrp := self windowGroup) notNil ifTrue:[
+            winGrp focusView == self ifTrue:[
+                ^ self
+            ]
+        ].
+    ].
+    self ungrabMouseAndKeyboard.
+    self selection:nil.
+    hasImplicitGrap := nil.
+!
+
 grabKeyboard
     "grap the keyboard; keep previous grab
     "
@@ -2617,6 +2667,7 @@
     "grap the pointer; keep previous grab
     "
     previousPointerGrab := device activePointerGrab.
+    hasImplicitGrap := true.
   ^ super grabPointerWithCursor:aCursorOrNil
 
 
@@ -2628,7 +2679,7 @@
     super ungrabKeyboard.
 
     previousKeyboardGrab notNil ifTrue:[
-        device grabKeyboardInView:previousKeyboardGrab
+        device grabKeyboardInView:previousKeyboardGrab.
     ].
 
 
@@ -2639,7 +2690,6 @@
     "
     self ungrabPointer.
     self ungrabKeyboard.
-
 !
 
 ungrabPointer
@@ -2648,7 +2698,7 @@
     super ungrabPointer.
 
     previousPointerGrab notNil ifTrue:[
-        device grabPointerInView:previousPointerGrab
+        device grabPointerInView:previousPointerGrab.
     ].
 
 
@@ -2662,27 +2712,20 @@
     ^ self helpTextForItem:selection
 !
 
-helpTextAt:aPoint
+helpTextAt:srcPoint
     "return the helpText for aPoint (i.e. when mouse-pointer is moved over an item).
      If there is a selection, that items helpText is used (ignoreing the given point).
      "
-    |menu point|
-
-    selection notNil ifTrue:[
-        ^ self helpTextForItem:selection
-    ].
-
-    (self containsPoint:aPoint) ifFalse:[
-        superMenu notNil ifTrue:[
-            ^ superMenu helptext
-        ]
-    ].
-
-    (menu := self superMenuAtX:aPoint x y:aPoint y) isNil ifTrue:[
+    |dstMenu dstPoint|
+
+    dstMenu := self detectMenuAtGrabPoint:srcPoint.
+
+    dstMenu isNil ifTrue:[
         ^ ''
     ].
-    point := self translatePoint:aPoint to:menu.
-  ^ menu helpTextForItem:(menu itemAtX:(point x) y:(point y)).
+
+    dstPoint := dstMenu translateGrabPoint:srcPoint.
+  ^ dstMenu helpTextForItem:(dstMenu itemAtX:(dstPoint x) y:(dstPoint y)).
 !
 
 helpTextForItem:anItem
@@ -2850,12 +2893,11 @@
 
     viewBackground := DefaultBackgroundColor.
 
-    onLevel   := DefaultHilightLevel.
-    offLevel  := 0. "/ DefaultLevel.
-    itemSpace := DefaultItemSpace.
-
+    onLevel          := DefaultHilightLevel.
+    offLevel         := 0. "/ DefaultLevel.
+    itemSpace        := DefaultItemSpace.
     groupDividerSize := DefaultGroupDividerSize.
-    fitFirstPanel := DefaultFitFirstPanel.
+    fitFirstPanel    := DefaultFitFirstPanel.
 
     "/ for now, assume not popUp (since superMenu is always nil at this time)
     self initPopUpDependentStyle:false.  
@@ -2889,8 +2931,6 @@
     enteredItem := nil.
 
     self enableMotionEvents.
-
-    lastButtonSelected := nil.
     self becomesActiveMenu.
     super map.
 
@@ -2899,7 +2939,7 @@
     self do:[:anItem| anItem fetchImages ].
 
     self isPopUpView ifTrue:[
-        self grabMouseAndKeyboard
+        self doGrab
     ] ifFalse:[
         super viewBackground:(self backgroundColor).
     ].
@@ -2965,30 +3005,13 @@
      If we have a popup supermenu, it will get all keyboard and mouse events."
 
     self clearLastActiveMenu.
-
-self isPopUpView ifTrue:[
-     self ungrabMouseAndKeyboard.
-].
-
-"/        "/
-"/        "/ Kludge for X11: after grabbing and ungrabbing other views may get buttonMotionEvents
-"/        "/ when a mouse button is still pressed. To avoid this we grab the mouse for the superview.
-"/        "/ (Move from upperMenuPanel of NewLauncher to lowerMenuPanel)
-"/        "/
-"/        (superMenu notNil 
-"/        and:[superMenu shown 
-"/        and:[superMenu isPopUpView 
-"/             or:[superMenu sensor anyButtonPressed]]]) 
-"/        ifTrue:[
-"/    "/        superMenu grabMouseAndKeyboard
-"/        ] ifFalse:[
-"/            self ungrabMouseAndKeyboard.
-"/        ].
+    self doUngrab:(superMenu isNil).
+"/    self isPopUpView ifTrue:[
+"/         self doUngrab:(superMenu isNil)
+"/    ].
+
     super unmap.
     shadowView notNil ifTrue:[shadowView unmap].
-
-    "Modified: / 2.2.1998 / 10:27:06 / stefan"
-    "Modified: / 27.2.1998 / 17:41:24 / cg"
 ! !
 
 !MenuPanel methodsFor:'misc'!
@@ -3083,11 +3106,13 @@
     "
     |cIdx uKey lKey item|
 
+    items isNil ifTrue:[^ nil].
+
     cIdx := self selectionIndex.
     uKey := aKey asUppercase.
     lKey := aKey asLowercase.
 
-    self keysAndValuesDo:[:anIndex :anItem| |char label|
+    items keysAndValuesDo:[:anIndex :anItem| |char label|
         (     anIndex ~~ cIdx
          and:[anItem canSelect
          and:[(label := anItem textLabel) notNil
@@ -3241,17 +3266,6 @@
   ^ nil
 
     "Created: / 19.1.1999 / 16:00:16 / cg"
-!
-
-translatePoint:aPoint to:aView
-    "translate a point into a views point; in case of no view nil is returned
-    "
-    aView == self ifTrue:[^ aPoint].
-    aView notNil ifTrue:[
-      ^ device translatePoint:aPoint from:(self id) to:(aView id)
-    ].
-    ^ nil
-
 ! !
 
 !MenuPanel methodsFor:'private activation'!
@@ -3310,37 +3324,100 @@
 
 !MenuPanel methodsFor:'private searching'!
 
+detectGrabMenu
+    "returns the menu which is responsible for the grap; the last opened menu
+    "
+    |subMenu|
+
+    selection notNil ifTrue:[
+        (subMenu := selection currentSubmenu) notNil ifTrue:[
+            ^ subMenu detectGrabMenu
+        ]
+    ].
+    ^ self
+!
+
+detectMenuAtGrabPoint:aGrabPoint
+    "returns the menu which contains the grab-point
+    "
+    |dstMenu dstPoint firstMenu|
+
+    dstPoint := self translateGrabPoint:aGrabPoint.
+
+    ((dstPoint x between:0 and:width) and:[dstPoint y between:0 and:height]) ifTrue:[
+        firstMenu := self.
+    ].
+
+    (selection isNil or:[(dstMenu := selection currentSubmenu) isNil]) ifTrue:[
+        ^ firstMenu
+    ].
+    dstMenu := dstMenu detectMenuAtGrabPoint:aGrabPoint.
+  ^ dstMenu ? firstMenu
+
+!
+
 itemAtX:x y:y
-    "returns item at a point or nil
-    "
-    self do:[:el| (el containsPointX:x y:y) ifTrue:[^el] ].
-  ^ nil
+    "returns the item at a point x@y or nil if none detected
+    "
+    items notNil ifTrue:[
+        ^ items detect:[:el| el containsPointX:x y:y] ifNone:nil
+    ].
+    ^ nil
 !
 
 superMenuAtX:x y:y
-    "returns supermenu at a point or nil
-    "
-    |menu|
-
-    (self containsPointX:x y:y) ifTrue:[^ self].
-    menu := self.
-
-    [ (menu := menu superMenu) notNil ] whileTrue:[
-	(menu containsPoint:(self translatePoint:(x@y) to:menu)) ifTrue:[
-	    ^ menu
-	]
+    "returns the superMenu which contains the point x@y or nil if none detected
+    "
+    |grabPoint superMenu|
+
+    (self containsPointX:x y:y) ifTrue:[
+        ^ self
+    ].
+
+    grabPoint := (x@y) - (self translateGrabPoint:0@0).
+    superMenu := self.
+
+    [ (superMenu := superMenu superMenu) notNil ] whileTrue:[
+        (superMenu containsPoint:(superMenu translateGrabPoint:grabPoint)) ifTrue:[
+            ^ superMenu
+        ]
     ].
   ^ nil
+
+!
+
+translateGrabPoint:aGrabPoint
+    "translate the grab point into self
+    "
+    |myPoint|
+
+    superMenu isNil ifTrue:[
+        "I am the grapView"
+        ^ aGrabPoint
+    ].
+
+    relativeGrabOrigin isNil ifTrue:[
+        relativeGrabOrigin := device translatePoint:0@0 from:(self topMenu id) to:(self id).
+    ].
+    ^ relativeGrabOrigin + aGrabPoint
+
+!
+
+translatePoint:aPoint to:aMenu
+    "translate a point into another menu its point
+    "
+    |grapPoint|
+
+    aMenu == self ifTrue:[
+        ^ aPoint
+    ].
+    grapPoint := aPoint - (self translateGrabPoint:0@0).
+
+  ^ aMenu translateGrabPoint:grapPoint
 ! !
 
 !MenuPanel methodsFor:'queries'!
 
-canDrawItem
-    "returns true if an item could be drawn otherwise false
-    "
-    ^ (mustRearrange not and:[shown])
-!
-
 containsPoint:aPoint
     "returns true if point is contained by the view
     "
@@ -3352,15 +3429,6 @@
     "
     ^ (x between:0 and:width) and:[y between:0 and:height]
 
-"/    |ext|
-"/
-"/    (x >= 0 and:[y >= 0]) ifTrue:[
-"/        ext := self computeExtent.
-"/      ^ (x < ext x and:[y < ext y])
-"/    ].
-"/    ^ false
-
-    "Modified: / 29.1.1998 / 16:46:10 / cg"
 !
 
 hasGroupDividerAt:anIndex
@@ -3369,13 +3437,13 @@
     |i|
 
     groupSizes size ~~ 0 ifTrue:[
-	i := 0.
-
-	groupSizes do:[:t|
-	    (i := i + t) == anIndex ifTrue:[
-		^ true
-	    ]
-	]
+        i := 0.
+
+        groupSizes do:[:t|
+            (i := i + t) == anIndex ifTrue:[
+                ^ true
+            ]
+        ]
     ].
   ^ false
 
@@ -3395,9 +3463,10 @@
 
 isFitPanel
     "returns true if the panel is the first in the menu hierarchy in must
-     be fit to the extent of its superView
-    "
-    ^ self isPopUpView ifTrue:[false] ifFalse:[fitFirstPanel]
+     be fit to the extent of its superView;
+     NOT SUPPORTED
+    "
+    ^ false
 !
 
 isPopUpView
@@ -3412,7 +3481,7 @@
 isVerticalLayout
     "returns true if vertical layout otherwise false( horizontal layout )
     "
-  ^ self verticalLayout
+    ^ self verticalLayout
 
 
 !
@@ -3470,7 +3539,7 @@
         item selected:false.
     ].
     newSel notNil ifTrue:[
-        self itemEntered:nil.
+        self pointerEntersItem:nil.
         selection := newSel.
 
         ActiveHelp isActive ifTrue:[
@@ -3520,20 +3589,18 @@
 
 !MenuPanel::Item class methodsFor:'defaults'!
 
-separatorSize:aType
+separatorSize
     "returns size of a separator
     "
-    aType == #doubleLine ifTrue:[^ 10 ].
-    aType == #singleLine ifTrue:[^ 10 ].
-  ^ 10
+    ^ 10
 !
 
 updateStyleCache
     "setup defaults
      self updateStyleCache
     "
-    HorizontalInset       := 4.
-    VerticalInset         := 3.
+    HorizontalInset       := 2.
+    VerticalInset         := 2.
 
     HorizontalButtonInset := 3.
     VerticalButtonInset   := 3.
@@ -3658,21 +3725,19 @@
 toggleIndication
     "toggle indication or choice
     "
-    |arg|
-
-    self hasIndication ifTrue:[    
-	arg := self indicationValue not.
-	self indicationValue:arg.
+    |arg choiceHolder|
+
+    self indication notNil ifTrue:[    
+        arg := self indicationValue not.
+        self indicationValue:arg.
     ] ifFalse:[
-	self hasChoice ifTrue:[
-	    arg := self choiceValue.
-	    self choice value:arg.
-	    arg := true.
-	]
+        (choiceHolder := self choice) notNil ifTrue:[
+            arg := self choiceValue.
+            choiceHolder value:arg.
+          ^ true
+        ]
     ].
     ^ arg
-
-    "Modified: / 14.8.1998 / 16:13:37 / cg"
 ! !
 
 !MenuPanel::Item methodsFor:'accessing'!
@@ -3731,6 +3796,12 @@
 
 !
 
+currentSubmenu
+    "returns the current submenu or nil
+    "
+    ^ subMenu
+!
+
 label
     "returns the label
     "
@@ -3864,10 +3935,8 @@
 textLabel
     "returns my textLabel or nil if none text
     "
-    (rawLabel respondsTo:#string) ifTrue:[
-	^ rawLabel string
-    ].
-  ^ nil
+    ^ rawLabel perform:#string ifNotUnderstood:nil
+
 !
 
 value
@@ -3908,19 +3977,19 @@
     old := self choice.
     old == something ifTrue:[^ self].
 
-    (self isKindOfValueHolder:old) ifTrue:[
-	old removeDependent:self
+    old isValueModel ifTrue:[
+        old removeDependent:self
     ].
 
     new := something.
     new isSymbol ifTrue:[
-	new := self aspectAt:new.
-	new isNil ifTrue:[
-	    new := something
-	]
-    ].
-    (self isKindOfValueHolder:new) ifTrue:[
-	new addDependent:self
+        new := self aspectAt:new.
+        new isNil ifTrue:[
+            new := something
+        ]
+    ].
+    new isValueModel ifTrue:[
+        new addDependent:self
     ].
     self adornment choice:new.
     self updateRawLabel.
@@ -3956,19 +4025,19 @@
     |state|
 
     menuPanel enabled ifTrue:[
-	enableChannel isSymbol ifTrue:[
-	    state := self aspectAt:enableChannel.
-
-	    (self isKindOfValueHolder:state) ifTrue:[
-		enableChannel := state.
-		enableChannel addDependent:self.
-		state := enableChannel value.
-	    ] ifFalse:[
-		state := state value
-	    ]
-	] ifFalse:[
-	    state := enableChannel value
-	].
+        enableChannel isSymbol ifTrue:[
+            state := self aspectAt:enableChannel.
+
+            state isValueModel ifTrue:[
+                enableChannel := state.
+                enableChannel addDependent:self.
+                state := enableChannel value.
+            ] ifFalse:[
+                state := state value
+            ]
+        ] ifFalse:[
+            state := enableChannel value
+        ].
       ^ state ~~ false
     ].
     ^ false
@@ -3983,7 +4052,7 @@
         oldState := true
     ] ifFalse:[
         oldState := enableChannel value.
-        (self isKindOfValueHolder:enableChannel) ifTrue:[
+        enableChannel isValueModel ifTrue:[
             enableChannel removeDependent:self
         ]
     ].
@@ -3993,7 +4062,7 @@
         menuPanel shown ifFalse:[^ self].
         newState := true
     ] ifFalse:[
-        (self isKindOfValueHolder:enableChannel) ifTrue:[
+        enableChannel isValueModel ifTrue:[
             enableChannel addDependent:self
         ] ifFalse:[
             enableChannel isSymbol ifTrue:[^ self]
@@ -4039,12 +4108,12 @@
     old := self indication.
     old == something ifTrue:[^ self].
 
-    (self isKindOfValueHolder:old) ifTrue:[
-	old removeDependent:self
-    ].
-
-    (self isKindOfValueHolder:something) ifTrue:[
-	something addDependent:self
+    old isValueModel ifTrue:[
+        old removeDependent:self
+    ].
+
+    something isValueModel ifTrue:[
+        something addDependent:self
     ].
     self adornment indication:something.
     self updateRawLabel.
@@ -4075,6 +4144,8 @@
 
     adornment isNil ifTrue:[^ false ].
   ^ adornment showBusyCursorWhilePerforming
+
+
 !
 
 showBusyCursorWhilePerforming:aBoolean
@@ -4085,6 +4156,7 @@
         self adornment showBusyCursorWhilePerforming:aBoolean.
     ]
 
+
 !
 
 submenuChannel
@@ -4101,15 +4173,6 @@
 
 !MenuPanel::Item methodsFor:'accessing-dimension'!
 
-height
-    "gets height
-    "
-    layout isNil ifTrue:[
-	^ self preferredExtent y
-    ].
-    ^ layout height
-!
-
 horizontalInset
 
     isButton ifTrue: [^menuPanel buttonPassiveLevel + HorizontalButtonInset].
@@ -4130,20 +4193,49 @@
 
 !
 
+preferredExtent
+    "compute my preferred extent excluding the shortCutKey and the menu identifier
+    "
+    |isVertical
+     x "{ Class:SmallInteger }"
+     y "{ Class:SmallInteger }"
+     s "{ Class:SmallInteger }"
+    |
+    self isVisible ifFalse:[^ 0@0 ].
+
+    isButton ifTrue:[
+        s := menuPanel maxAbsoluteButtonLevel.
+        x := s + HorizontalButtonInset.
+        y := s + VerticalButtonInset.
+    ] ifFalse:[
+        x  := HorizontalInset.
+        y  := VerticalInset.
+    ].
+    x := x * 2.
+    y := y * 2.
+
+    rawLabel isNil ifTrue:[
+        "/ SEPARATOR
+        s := self class separatorSize.
+
+        menuPanel verticalLayout ifFalse:[
+            x := x max:s.
+            y := y + 5.
+        ] ifTrue:[
+            y := y max:s.
+            x := x + 5.
+        ].
+    ] ifFalse:[
+        x := x + (rawLabel  widthOn:menuPanel).
+        y := y + (rawLabel heightOn:menuPanel).
+    ].
+    ^ x@y
+!
+
 verticalInset
 
     isButton ifTrue: [^menuPanel buttonPassiveLevel + VerticalButtonInset].
     ^VerticalInset
-!
-
-width
-    "gets width
-    "
-
-    layout isNil ifTrue:[
-	^ self preferredExtent x
-    ].
-    ^ layout width
 ! !
 
 !MenuPanel::Item methodsFor:'accessing-help'!
@@ -4542,7 +4634,7 @@
         menuPanel paint:paint.
         menuPanel fillRectangle:layout.
     ] ifFalse:[
-        self hasIndication ifFalse:[
+        self indication notNil ifFalse:[
             menuPanel paint:ownBgCol.
             menuPanel fillRectangle:layout.
         ] ifTrue:[
@@ -4681,21 +4773,22 @@
 
     self submenu:nil.
 
-    (enableChannel notNil and:[self isKindOfValueHolder:enableChannel]) ifTrue:[
-	enableChannel removeDependent:self
-    ].
-
-    (isVisible notNil and:[self isKindOfValueHolder:isVisible]) ifTrue:[
-	isVisible removeDependent:self
+    enableChannel isValueModel ifTrue:[
+        enableChannel removeDependent:self
+    ].
+
+    isVisible isValueModel ifTrue:[
+        isVisible removeDependent:self
     ].
 
     channel := self indication.
-    (channel notNil and:[self isKindOfValueHolder:channel]) ifTrue:[
-	channel removeDependent:self
-    ].
+    channel isValueModel ifTrue:[
+        channel removeDependent:self
+    ].
+
     channel := self choice.
-    (channel notNil and:[self isKindOfValueHolder:channel]) ifTrue:[
-	channel removeDependent:self
+    channel isValueModel ifTrue:[
+        channel removeDependent:self
     ].
 
     menuPanel := nil.
@@ -5040,7 +5133,7 @@
         ].
         indication := self aspectAt:indication.
 
-        (self isKindOfValueHolder:indication) ifTrue:[
+        indication isValueModel ifTrue:[
             self adornment indication:indication.
             indication addDependent:self.
         ]
@@ -5177,21 +5270,23 @@
 !MenuPanel::Item methodsFor:'queries'!
 
 canChangeVisibility
-    "return true if I am not always visible
-    "
-
-    ^ isVisible notNil and:[isVisible ~~ true]
+    "return true if I am not always visible; can only be changed by a selector
+     otherwise there is a change notification raised if the model changed
+    "
+    ^ isVisible isSymbol
+"/  ^ isVisible notNil and:[isVisible ~~ true]
 !
 
 canSelect
-    "returns true if item is selectable
+    "returns true if item is selectable; no separator, visible and enabled.
+     in case of a choice (RadioButton) i have to check for the choiceValue
     "
     |holder|
 
-    (self isVisible and:[self enabled and:[rawLabel notNil]]) ifTrue:[
-	((holder := self choice) isNil or:[holder value ~= self choiceValue]) ifTrue:[
-	    ^ true
-	].
+    (rawLabel notNil and:[self isVisible and:[self enabled]]) ifTrue:[
+        ((holder := self choice) isNil or:[holder value ~= self choiceValue]) ifTrue:[
+            ^ true
+        ].
     ].
     ^ false
 !
@@ -5200,23 +5295,11 @@
     "returns true if point is contained in my layout
     "
     (self isVisible and:[layout notNil]) ifTrue:[
-	^ (     (x >= layout left)
-	    and:[x <  layout right
-	    and:[y >  layout top
-	    and:[y <= layout bottom]]]
-	  )
+        ^ layout containsPointX:x y:y
     ].
     ^ false
 !
 
-hasChoice
-    "returns true if a choice indication (RadioButton) exists
-    "
-  ^ self choice notNil
-
-    "Created: / 14.8.1998 / 14:38:20 / cg"
-!
-
 hasIndication
     "returns true if on/off indication exists
     "
@@ -5235,17 +5318,6 @@
     ^ self enabled
 !
 
-isKindOfValueHolder:something
-    "returns true if something is kind of vlaue holder
-    "
-    ^ ((something respondsTo:#value:) and:[something isBlock not])
-
-
-
-
-
-!
-
 isSeparator
     "returns true if item is a separator
     "
@@ -5258,15 +5330,15 @@
     |state|
 
     isVisible isSymbol ifTrue:[
-	state := self aspectAt:isVisible.
-
-	(self isKindOfValueHolder:state) ifTrue:[
-	    isVisible := state.
-	    isVisible addDependent:self.
-	    state := isVisible.
-	]
+        state := self aspectAt:isVisible.
+
+        state isValueModel ifTrue:[
+            isVisible := state.
+            isVisible addDependent:self.
+            state := isVisible.
+        ]
     ] ifFalse:[
-	state := isVisible
+        state := isVisible
     ].
   ^ state value ~~ false
 
@@ -5279,86 +5351,34 @@
     |oldState newState|
 
     isVisible isNil ifTrue:[
-	oldState := true
+        oldState := true
     ] ifFalse:[
-	oldState := isVisible value.
-	(self isKindOfValueHolder:isVisible) ifTrue:[
-	    isVisible removeDependent:self
-	]
+        oldState := isVisible value.
+        isVisible isValueModel ifTrue:[
+            isVisible removeDependent:self
+        ]
     ].
     isVisible := something.
 
     isVisible isNil ifTrue:[
-	newState := true
+        newState := true
     ] ifFalse:[
-	(self isKindOfValueHolder:isVisible) 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"
 !
 
-preferredExtent
-    "compute my preferred extent
-    "
-    |x y s isVertical sepSize|
-
-    self isVisible ifFalse:[^ (0 @ 0) ].
-
-    x := self horizontalInset * 2.
-    y := self verticalInset * 2.
-
-    isVertical := menuPanel verticalLayout.
-
-    self isSeparator ifFalse:[
-        x := x + (rawLabel widthOn:menuPanel).
-        y := y + (rawLabel heightOn:menuPanel).
-
-        MenuView showAcceleratorKeys == true ifTrue:[
-            isVertical ifTrue:[ "/ only for vertical menus ...
-                (s := self shortcutKeyAsString) notNil ifTrue:[
-                    x := x + LabelRightOffset + (s widthOn:menuPanel)
-                ].
-            ].
-        ].
-        (isVertical and:[self hasSubmenu]) ifTrue:[
-            x := x + menuPanel subMenuIndicationWidth.
-
-            s notNil ifTrue:[x := x + ShortcutKeyOffset]
-                    ifFalse:[x := x + LabelRightOffset]
-        ].
-    ] ifTrue:[
-
-        sepSize := (self class separatorSize:(self separatorType)).
-        isVertical ifFalse:[
-            x := x max:sepSize.
-            y := y + (menuPanel font height)
-        ] ifTrue:[
-            y := y max:sepSize
-        ].
-    ].
-
-    ^ (x @ y)
-
-    "Modified: / 8.8.1998 / 01:38:26 / cg"
-!
-
-preferredExtentX
-    "compute my preferred extent x
-    "
-    ^ self preferredExtent x
-
-!
-
 shortcutKeyAsString
     "converts shortcutKey to a text object
     "
@@ -5459,7 +5479,7 @@
     ].
     menuPanel realized ifFalse:[^ self].
 
-    (self hasIndication not or:[isButton not]) ifTrue:[
+    (self indication isNil or:[isButton not]) ifTrue:[
         menuPanel invalidateItem:self repairNow:true.
     ].
     (subMenu := self setupSubmenu) isNil ifTrue:[|m|
@@ -5592,6 +5612,8 @@
      while performing the menu action. Defaults to false."
 
     ^ showBusyCursorWhilePerforming ? false
+
+
 !
 
 showBusyCursorWhilePerforming:aBoolean
@@ -5599,11 +5621,14 @@
      while performing the menu action. Defaults to false."
 
     showBusyCursorWhilePerforming := aBoolean
+
+
 ! !
 
 !MenuPanel class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/MenuPanel.st,v 1.196 2000-02-12 15:37:01 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/MenuPanel.st,v 1.197 2000-02-13 11:42:17 ca Exp $'
+
 ! !
 MenuPanel initialize!