#UI_ENHANCEMENT
authorClaus Gittinger <cg@exept.de>
Wed, 07 Oct 2015 01:04:27 +0200
changeset 4854 23fe12653489
parent 4853 ee048f425b2b
child 4855 3270acbceaad
child 4856 e30db8df7505
#UI_ENHANCEMENT class: MenuPanel class definition added: #suppressSeparatingLines comment/format in: #preferredExtent #updateEnteredItem changed:9 methods extra margin
MenuPanel.st
--- a/MenuPanel.st	Mon Oct 05 09:19:46 2015 +0200
+++ b/MenuPanel.st	Wed Oct 07 01:04:27 2015 +0200
@@ -28,7 +28,8 @@
 		activeBackgroundColor stringOffsetX doAccessCharacterTranslation
 		lastItem hasPerformed focusComesByTab lastDrawnScrollerNextBounds
 		buttonActiveBackgroundColor buttonEnteredBackgroundColor
-		buttonPassiveBackgroundColor maxExtent sizeFixed'
+		buttonPassiveBackgroundColor maxExtent sizeFixed extraMargin
+		buttonActiveLevel buttonPassiveLevel buttonEnteredLevel'
 	classVariableNames:'InitialSelectionQuerySignal Images LigthenedImages
 		DefaultForegroundColor DefaultBackgroundColor IconIndicationOn
 		IconIndicationOff IconRadioOn IconRadioOff
@@ -720,29 +721,29 @@
     "extract values from the styleSheet and cache them in class variables"
 
     <resource: #style (
-	#'selection.disabledForegroundColor'
-	#'pullDownMenu.foregroundColor' #'pullDownMenu.backgroundColor' #'pullDownMenu.level'
-	#'menu.itemHorizontalSpace' #'menu.buttonItemHorizontalSpace' #'menu.buttonItemSpace'
-	#'menu.itemSpace' #'menu.buttonItemVerticalSpace'
-	#'menu.buttonActiveLevel' #'menu.buttonPassiveLevel' #'menu.buttonEnteredLevel'
-	#'menu.hilightLevel' #'menu.enteredLevel'
-	#'menu.groupDividerSize' #'menu.itemMargin'
-	#'menu.disabledEtchedForegroundColor' #'menu.hilightForegroundColor'
-	#'menu.enteredBackgroundColor' #'menu.enteredForegroundColor'
-	#'menu.disabledForegroundColor' #'menu.buttonEnteredBackgroundColor'
-	#'menu.selectionFollowsMouse'
-	#'button.disabledEtchedForegroundColor' #'button.disabledForegroundColor'
-	#'button.activeBackgroundColor' #'button.backgroundColor' #'button.lightColor'
-	#'button.enteredBackgroundColor' #'button.halfLightColor' #'button.halfShadowColor'
-	#'button.activeLevel' #'button.passiveLevel' #'button.edgeStyle'
-	#'menu.iconIndicationOn' #'menu.iconIndicationOff'
-	#'menu.iconIndicationOn.bitmapFile' #'menu.iconIndication.bitmapOffFile'
-	#'menu.iconDisabledIndicationOn' #'menu.iconDisabledIndicationOff'
-	#'menu.iconDisabledIndicationOn.bitmapFile' #'menu.iconDisabledIndication.bitmapOffFile'
-	#'menu.iconRadioOn' #'menu.iconRadioOff'
-	#'menu.iconRadioOn.bitmapFile' #'menu.iconRadioOff.bitmapFile'
-	#'menu.iconDisabledRadioOn' #'menu.iconDisabledRadioOff'
-	#'menu.iconDisabledRadioOn.bitmapFile' #'menu.iconDisabledRadioOff.bitmapFile'
+        #'selection.disabledForegroundColor'
+        #'pullDownMenu.foregroundColor' #'pullDownMenu.backgroundColor' #'pullDownMenu.level'
+        #'menu.itemHorizontalSpace' #'menu.buttonItemHorizontalSpace' #'menu.buttonItemSpace'
+        #'menu.itemSpace' #'menu.buttonItemVerticalSpace'
+        #'menu.buttonActiveLevel' #'menu.buttonPassiveLevel' #'menu.buttonEnteredLevel'
+        #'menu.hilightLevel' #'menu.enteredLevel'
+        #'menu.groupDividerSize' #'menu.itemMargin'
+        #'menu.disabledEtchedForegroundColor' #'menu.hilightForegroundColor'
+        #'menu.enteredBackgroundColor' #'menu.enteredForegroundColor'
+        #'menu.disabledForegroundColor' #'menu.buttonEnteredBackgroundColor'
+        #'menu.selectionFollowsMouse'
+        #'button.disabledEtchedForegroundColor' #'button.disabledForegroundColor'
+        #'button.activeBackgroundColor' #'button.backgroundColor' #'button.lightColor'
+        #'button.enteredBackgroundColor' #'button.halfLightColor' #'button.halfShadowColor'
+        #'button.activeLevel' #'button.passiveLevel' #'button.edgeStyle'
+        #'menu.iconIndicationOn' #'menu.iconIndicationOff'
+        #'menu.iconIndicationOn.bitmapFile' #'menu.iconIndication.bitmapOffFile'
+        #'menu.iconDisabledIndicationOn' #'menu.iconDisabledIndicationOff'
+        #'menu.iconDisabledIndicationOn.bitmapFile' #'menu.iconDisabledIndication.bitmapOffFile'
+        #'menu.iconRadioOn' #'menu.iconRadioOff'
+        #'menu.iconRadioOn.bitmapFile' #'menu.iconRadioOff.bitmapFile'
+        #'menu.iconDisabledRadioOn' #'menu.iconDisabledRadioOff'
+        #'menu.iconDisabledRadioOn.bitmapFile' #'menu.iconDisabledRadioOff.bitmapFile'
     )>
 
     |styleSheet style var foregroundColor backgroundColor buttonPassiveBackgroundColor
@@ -761,15 +762,15 @@
 
     DefaultFont     := MenuView defaultFont.
     foregroundColor := DefaultForegroundColor := styleSheet colorAt:#'pullDownMenu.foregroundColor'
-							    default:[styleSheet
-									colorAt:#'menu.foregroundColor'
-									default:Color black].
+                                                            default:[styleSheet
+                                                                        colorAt:#'menu.foregroundColor'
+                                                                        default:Color black].
     backgroundColor := DefaultBackgroundColor := self defaultBackgroundColor.
 
     var := styleSheet colorAt:#'menu.hilightBackgroundColor'.
     var isNil ifTrue:[
-	style == #motif ifTrue:[ var := backgroundColor ]
-		       ifFalse:[ var := styleSheet is3D ifFalse:[foregroundColor] ifTrue:[backgroundColor] ]
+        style == #motif ifTrue:[ var := backgroundColor ]
+                       ifFalse:[ var := styleSheet is3D ifFalse:[foregroundColor] ifTrue:[backgroundColor] ]
     ].
     styleSheet at:#'menuPanel.activeBackgroundColor' put:var.
 
@@ -779,8 +780,8 @@
 
     var := styleSheet colorAt:#'menu.disabledForegroundColor'.
     var isNil ifTrue:[
-	var := styleSheet colorAt:#'selection.disabledForegroundColor'.
-	var isNil ifTrue:[ var := styleSheet colorAt:#'button.disabledForegroundColor' default:Color darkGray ]
+        var := styleSheet colorAt:#'selection.disabledForegroundColor'.
+        var isNil ifTrue:[ var := styleSheet colorAt:#'button.disabledForegroundColor' default:Color darkGray ]
     ].
     styleSheet at:#'menuPanel.disabledForegroundColor' put:var.
 
@@ -791,21 +792,21 @@
 
     buttonActiveLevel := styleSheet at:#'menu.buttonActiveLevel' default:(styleSheet is3D ifTrue:[-2] ifFalse:[0]).
     buttonActiveLevel isNil ifTrue:[ buttonActiveLevel := styleSheet at:#'button.activeLevel' default:(styleSheet is3D ifTrue:[-2] ifFalse:[0]) ].
-    styleSheet at:#'menuPanel.buttonActiveLevel' put:buttonActiveLevel.
+    "/ styleSheet at:#'menuPanel.buttonActiveLevel' put:buttonActiveLevel.
 
     buttonPassiveLevel := styleSheet at:#'menu.buttonPassiveLevel'.
     buttonPassiveLevel isNil ifTrue:[ buttonPassiveLevel :=  styleSheet at:#'button.passiveLevel' default:(styleSheet is3D ifTrue:[2] ifFalse:[0])].
-    styleSheet at:#'menuPanel.buttonPassiveLevel' put:buttonPassiveLevel.
+    "/ styleSheet at:#'menuPanel.buttonPassiveLevel' put:buttonPassiveLevel.
 
     buttonEnteredLevel := styleSheet at:#'menu.buttonEnteredLevel' default:buttonPassiveLevel.
-    styleSheet at:#'menuPanel.buttonEnteredLevel' put:buttonEnteredLevel.
+    "/ styleSheet at:#'menuPanel.buttonEnteredLevel' put:buttonEnteredLevel.
 
     var := (buttonActiveLevel abs max:(buttonPassiveLevel abs)) max:(buttonEnteredLevel abs).
     styleSheet at:#'menuPanel.maxAbsoluteButtonLevel' put:var.
 
     buttonPassiveBackgroundColor := styleSheet at:#'button.backgroundColor'.
     buttonPassiveBackgroundColor isNil ifTrue:[
-	buttonPassiveBackgroundColor := (styleSheet at:'viewBackground') ? backgroundColor
+        buttonPassiveBackgroundColor := (styleSheet at:'viewBackground') ? backgroundColor
     ].
     styleSheet at:#'menuPanel.buttonPassiveBackgroundColor' put:buttonPassiveBackgroundColor.
 
@@ -824,16 +825,16 @@
     Item updateStyleCache.
 
     getBitmapOrFile := [:key :fileKey |
-	|var|
-
-	var := styleSheet at:key ifAbsent:nil.
-	var isNil ifTrue:[
-	    var := styleSheet at:fileKey ifAbsent:nil.
-	    var notNil ifTrue:[
-		var := Smalltalk imageFromFileNamed:var forClass:self.
-	    ].
-	].
-	var
+        |var|
+
+        var := styleSheet at:key ifAbsent:nil.
+        var isNil ifTrue:[
+            var := styleSheet at:fileKey ifAbsent:nil.
+            var notNil ifTrue:[
+                var := Smalltalk imageFromFileNamed:var forClass:self.
+            ].
+        ].
+        var
     ].
 
     IconIndicationOn := getBitmapOrFile value:#'menu.iconIndicationOn' value:#'menu.iconIndicationOn.bitmapFile'.
@@ -1645,7 +1646,7 @@
 buttonEnteredLevel
     "get the 3D-level used to highlight entered button items"
 
-    ^ styleSheet at:#'menuPanel.buttonEnteredLevel'
+    ^ buttonEnteredLevel "/ ? (styleSheet at:#'menuPanel.buttonEnteredLevel') ? 0
 !
 
 buttonHalfLightColor
@@ -1775,6 +1776,11 @@
 	super font:aFont.
     ].
     ^ currentFont
+!
+
+suppressSeparatingLines
+    ^ self verticalLayout not
+    and:[ (styleSheet at:#'menu.suppressSeparatingLinesInToolbar' default:false) ] 
 ! !
 
 !MenuPanel methodsFor:'accessing-dimensions'!
@@ -1841,31 +1847,30 @@
 
     "/ If I have an explicit preferredExtent..
     explicitExtent notNil ifTrue:[
-	^ explicitExtent
+        ^ explicitExtent
     ].
     "/ If I have a cached preferredExtent value..
     preferredExtent notNil ifTrue:[
-	^ preferredExtent
+        ^ preferredExtent
     ].
 
     usedExtent := self preferredExtentOfItems.
-
     superView isNil ifTrue:[
-	"/ is standalone
-	preferredWidth notNil ifTrue:[
-	    usedExtent x < preferredWidth ifTrue:[
-		usedExtent := preferredWidth @ usedExtent y.
-	    ]
-	]
+        "/ is standalone
+        preferredWidth notNil ifTrue:[
+            usedExtent x < preferredWidth ifTrue:[
+                usedExtent := preferredWidth @ usedExtent y.
+            ]
+        ]
     ].
 
     maxExtent := self maxExtent.
     maxExtent notNil ifTrue:[
-	usedExtent := usedExtent min:maxExtent.
+        usedExtent := usedExtent min:maxExtent.
     ].
     "/ changed due to menu in horizontal panel
     (superView notNil and:[items size == 0] ) ifTrue:[
-	self isViewWrapper ifFalse:[ ^ usedExtent ].
+        self isViewWrapper ifFalse:[ ^ usedExtent ].
     ].
 
     preferredExtent := usedExtent.
@@ -1876,7 +1881,7 @@
 
 preferredExtentOfItems
     "compute and returns my preferred extent including all items
-	!!!!!! changes have influence on method #rearrangeItems !!!!!!"
+        !!!!!! changes have influence on method #rearrangeItems !!!!!!"
 
     |hasMenu shCtKey extent showAcc sck
      x            "{ Class:SmallInteger }"
@@ -1891,17 +1896,17 @@
     |
 
     (size := items size) == 0 ifTrue:[
-	self isViewWrapper ifTrue:[ ^ subViews first extent ].
-	^ 32 @ 32
+        self isViewWrapper ifTrue:[ ^ subViews first extent ].
+        ^ 32 @ 32
     ].
     stringOffsetX := nil.
     buttonInsetX2 := 2 * buttonInsetX.
     buttonInsetY2 := 2 * buttonInsetY.
 
     self isPopUpView ifFalse:[
-	labelInsetX := labelInsetY := 2 * (self enteredLevel abs).
+        labelInsetX := labelInsetY := 2 * (self enteredLevel abs).
     ] ifTrue:[
-	labelInsetX := labelInsetY := 0.
+        labelInsetX := labelInsetY := 0.
     ].
 
     x := 0.
@@ -1909,86 +1914,86 @@
     groupDividerSize := self groupDividerSize.
 
     self verticalLayout ifFalse:[
-	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 + buttonInsetX2.
-		    eY := eY + buttonInsetY2.
-		] ifFalse:[
-		    eX := eX + labelInsetX.
-		    eY := eY + labelInsetY.
-		].
-		key ~~ size ifTrue:[
-		    (self hasGroupDividerAt:key) ifTrue:[
-			x := x + groupDividerSize
-		    ] ifFalse:[
-			el needsItemSpaceWhenDrawing ifTrue:[
-			    x := x + itemSpace
-			]
-		    ]
-		].
-		x := x + eX.
-		y := y max:eY.
-	    ]
-	]
+        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 + buttonInsetX2.
+                    eY := eY + buttonInsetY2.
+                ] ifFalse:[
+                    eX := eX + labelInsetX.
+                    eY := eY + labelInsetY.
+                ].
+                key ~~ size ifTrue:[
+                    (self hasGroupDividerAt:key) ifTrue:[
+                        x := x + groupDividerSize
+                    ] ifFalse:[
+                        el needsItemSpaceWhenDrawing ifTrue:[
+                            x := x + itemSpace
+                        ]
+                    ]
+                ].
+                x := x + eX.
+                y := y max:eY.
+            ]
+        ]
     ] ifTrue:[
-	hasMenu := false.
-	shCtKey := 0.
-	showAcc := MenuView showAcceleratorKeys == true.
-	y := x.
-	x := 0.
-	itemMargin := 2 * self itemMargin.
-
-	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 + buttonInsetX2.
-		    eY := eY + buttonInsetY2.
-		] ifFalse:[
-		    eX := eX + labelInsetX.
-		    eY := eY + labelInsetY.
-		].
-		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
-		    ]
-		].
-		y := y + eY.
-		x := x max:eX.
-	    ].
-	].
-	x := x + itemMargin.
-
-	(hasMenu or:[shCtKey ~~ 0]) ifTrue:[
-	    shortKeyInset := x + Item labelRightOffset.
-	    x := shortKeyInset + shCtKey + self subMenuIndicationWidth.
-
-	    (shCtKey ~~ 0 and:[hasMenu]) ifTrue:[
-		x := x + self shortcutKeyOffset.
-	    ]
-	].
+        hasMenu := false.
+        shCtKey := 0.
+        showAcc := MenuView showAcceleratorKeys == true.
+        y := x.
+        x := 0.
+        itemMargin := 2 * self itemMargin.
+
+        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 + buttonInsetX2.
+                    eY := eY + buttonInsetY2.
+                ] ifFalse:[
+                    eX := eX + labelInsetX.
+                    eY := eY + labelInsetY.
+                ].
+                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
+                    ]
+                ].
+                y := y + eY.
+                x := x max:eX.
+            ].
+        ].
+        x := x + itemMargin.
+
+        (hasMenu or:[shCtKey ~~ 0]) ifTrue:[
+            shortKeyInset := x + Item labelRightOffset.
+            x := shortKeyInset + shCtKey + self subMenuIndicationWidth.
+
+            (shCtKey ~~ 0 and:[hasMenu]) ifTrue:[
+                x := x + self shortcutKeyOffset.
+            ]
+        ].
 "/ to have a small inset
-	y := y + 1.
+        y := y + 1.
 "/        x := x + 1.
     ].
-    x := x + margin + margin.
-    y := y + margin + margin.
+    x := x + ((margin + extraMargin)*2).
+    y := y + ((margin + extraMargin)*2).
 
     ^ x @ y
 !
@@ -2175,15 +2180,13 @@
 buttonActiveLevel
     "get the buttons active level"
 
-    ^ styleSheet at:#'menuPanel.buttonActiveLevel'
+    ^ buttonActiveLevel "/ ? (styleSheet at:#'menuPanel.buttonActiveLevel') ? 0
 !
 
 buttonPassiveLevel
     "get the buttons passive level"
 
-    ^ (styleSheet at:#'menuPanel.buttonPassiveLevel') ? 0
-
-    "Modified: / 19-01-2011 / 21:21:26 / cg"
+    ^ buttonPassiveLevel "/ ? (styleSheet at:#'menuPanel.buttonPassiveLevel') ? 0
 !
 
 centerItems
@@ -2949,14 +2952,14 @@
     |
 
     (self isPopUpView or:[self verticalLayout]) ifTrue:[
-	^ self
+        ^ self
     ].
 
     layout := items last layout.
     layout notNil ifTrue:[
-	(dltX := width - margin - layout right) <= 0 ifTrue:[
-	    ^ self  "/ no free space
-	].
+        (dltX := width - margin - extraMargin - layout right) <= 0 ifTrue:[
+            ^ self  "/ no free space
+        ].
     ].
 
     "/ The behavior of #conditionalRight is controlled by the styleSheet.
@@ -2965,20 +2968,21 @@
     "/ This allows for groups to be specified as #right under motif, but
     "/ non-right under win32 (as is used woth the help-menus).
     (StyleSheet at:#'menuPanel.ignoreConditionalStartGroupRight' ifAbsent:false) ifTrue:[
-	start := items findFirst:[:anItem| anItem startGroup == #right ].
+        start := items findFirst:[:anItem| anItem startGroup == #right ].
     ] ifFalse:[
-	start := items findFirst:[:anItem| anItem startGroup == #right or:[ anItem startGroup == #conditionalRight ] ].
+        start := items findFirst:[:anItem| anItem startGroup == #right or:[ anItem startGroup == #conditionalRight ] ].
     ].
     start == 0 ifTrue:[
-	^ self  "/ no right-group item detected
-    ].
+        ^ self  "/ no right-group item detected
+    ].
+    
     point := dltX @ 0.
 
     "/ move items layout to right
     items from:start do:[:anItem|
-	anItem isVisible ifTrue:[
-	    anItem layout moveBy:point.
-	]
+        anItem isVisible ifTrue:[
+            anItem layout moveBy:point.
+        ]
     ].
     self updateEnteredItem.
 
@@ -2987,7 +2991,7 @@
 
 rearrangeItems
     "recompute the layout of each item
-	!!!!!! changes have influence on method #preferredExtentOfItems !!!!!!"
+        !!!!!! changes have influence on method #preferredExtentOfItems !!!!!!"
 
     |isVertical extent isPopUpMenu
      x            "{ Class:SmallInteger }"
@@ -3006,8 +3010,8 @@
     |
 
     (mustRearrange and:[(size := items size) ~~ 0]) ifFalse:[
-	mustRearrange := false.
-	^ self
+        mustRearrange := false.
+        ^ self
     ].
 
 "/  DON'T SET THIS!!
@@ -3023,91 +3027,91 @@
     isPopUpMenu      := self isPopUpView.
 
     isPopUpMenu ifFalse:[
-	labelInsetX := labelInsetY := self enteredLevel abs.
+        labelInsetX := labelInsetY := self enteredLevel abs.
     ] ifTrue:[
-	labelInsetX := labelInsetY := 0
+        labelInsetX := labelInsetY := 0
     ].
 
     (isPopUpMenu or:[self hasExplicitExtent not]) ifTrue:[
-	|saveExtent maxExtent extentToSet|
-
-	extent := self preferredExtent.
-
-	isPopUpMenu ifTrue:[
-	    maxExtent := self maxExtent.
-	    maxExtent notNil ifTrue:[
-		extentToSet := isVertical ifTrue:[extent x @ (extent y min:(maxExtent y))]
-					  ifFalse:[(extent x min:(maxExtent x)) @ extent y].
-	    ].
-	] ifFalse:[
-	    extent := extentToSet := isVertical ifTrue:[extent x @ 1.0] ifFalse:[1.0 @ extent y].
-	].
-	self extent:extentToSet.
+        |saveExtent maxExtent extentToSet|
+
+        extent := self preferredExtent.
+
+        isPopUpMenu ifTrue:[
+            maxExtent := self maxExtent.
+            maxExtent notNil ifTrue:[
+                extentToSet := isVertical ifTrue:[extent x @ (extent y min:(maxExtent y))]
+                                          ifFalse:[(extent x min:(maxExtent x)) @ extent y].
+            ].
+        ] ifFalse:[
+            extent := extentToSet := isVertical ifTrue:[extent x @ 1.0] ifFalse:[1.0 @ extent y].
+        ].
+        self extent:extentToSet.
     ] ifFalse:[
-	extent := self computeExtent
-    ].
-
-    x := y := margin.
-
+        extent := self computeExtent
+    ].
+
+    x := y := margin + extraMargin.
+    
     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:[
-		    insetX := buttonInsetX.
-		    insetY := buttonInsetY.
-		] ifFalse:[
-		    insetX := labelInsetX.
-		    insetY := labelInsetY.
-		].
-		x0 := x  + insetX.
-		x1 := x0 + (el preferredWidth).
-		el layout:(Rectangle left:x0 top:(y0 + insetY) right:x1 bottom:(y1 - insetY)).
-		x := x1 + insetX.
-
-		size ~~ anIndex ifTrue:[
-		    (self hasGroupDividerAt:anIndex) ifTrue:[
-			x := x + groupDividerSize
-		    ] ifFalse:[
-			el needsItemSpaceWhenDrawing ifTrue:[
-			    x := x + itemSpace
-			]
-		    ]
-		]
-	    ].
-	].
+        y0 := y.
+        y1 := extent y - margin - extraMargin.
+
+        items keysAndValuesDo:[:anIndex :el|
+            el isVisible ifFalse:[
+                el layout:(Rectangle left:x top:y0 right:x bottom:y1)
+            ] ifTrue:[
+                el isButton ifTrue:[
+                    insetX := buttonInsetX.
+                    insetY := buttonInsetY.
+                ] ifFalse:[
+                    insetX := labelInsetX.
+                    insetY := labelInsetY.
+                ].
+                x0 := x  + insetX.
+                x1 := x0 + (el preferredWidth).
+                el layout:(Rectangle left:x0 top:(y0 + insetY) right:x1 bottom:(y1 - insetY)).
+                x := x1 + insetX.
+
+                size ~~ anIndex ifTrue:[
+                    (self hasGroupDividerAt:anIndex) ifTrue:[
+                        x := x + groupDividerSize
+                    ] ifFalse:[
+                        el needsItemSpaceWhenDrawing ifTrue:[
+                            x := x + itemSpace
+                        ]
+                    ]
+                ]
+            ].
+        ].
     ] ifTrue:[
-	itemMargin := self itemMargin.
-	x0 := margin.
-	x1 := extent x - margin - itemMargin.  "/ -1
-
-	items keysAndValuesDo:[:anIndex :el|
-	    el isVisible ifFalse:[
-		el layout:(Rectangle left:x0 top:y right:x1 bottom:y)
-	    ] ifTrue:[
-		el isButton ifTrue:[
-		    insetX := buttonInsetX.
-		    insetY := buttonInsetY.
-		] ifFalse:[
-		    insetX := labelInsetX.
-		    insetY := labelInsetY.
-		].
-		y0 := y  + insetY.
-		y1 := y0 + el preferredHeight.
-		el layout:(Rectangle left:(x0 + insetX + itemMargin) top:y0 right:(x1 - insetX) bottom:y1).
-		y := y1 + insetY.
-
-		size ~~ anIndex ifTrue:[
-		    (self hasGroupDividerAt:anIndex) ifTrue:[
-			y := y + groupDividerSize
-		    ]
-		]
-	    ]
-	]
+        itemMargin := self itemMargin.
+        x0 := margin.
+        x1 := extent x - margin - itemMargin.  "/ -1
+
+        items keysAndValuesDo:[:anIndex :el|
+            el isVisible ifFalse:[
+                el layout:(Rectangle left:x0 top:y right:x1 bottom:y)
+            ] ifTrue:[
+                el isButton ifTrue:[
+                    insetX := buttonInsetX.
+                    insetY := buttonInsetY.
+                ] ifFalse:[
+                    insetX := labelInsetX.
+                    insetY := labelInsetY.
+                ].
+                y0 := y  + insetY.
+                y1 := y0 + el preferredHeight.
+                el layout:(Rectangle left:(x0 + insetX + itemMargin) top:y0 right:(x1 - insetX) bottom:y1).
+                y := y1 + insetY.
+
+                size ~~ anIndex ifTrue:[
+                    (self hasGroupDividerAt:anIndex) ifTrue:[
+                        y := y + groupDividerSize
+                    ]
+                ]
+            ]
+        ]
     ].
     self rearrangeGroups.
     selection notNil ifTrue:[self makeItemVisible:selection].
@@ -3218,11 +3222,10 @@
     |mousePoint|
 
     mousePoint  := self graphicsDevice translatePoint:(self graphicsDevice pointerPosition)
-			   fromView:nil
-			     toView:self.
+                           fromView:nil toView:self.
 
     (self containsPoint:mousePoint) ifTrue:[
-	enteredItem := self itemAtPoint:mousePoint
+        enteredItem := self itemAtPoint:mousePoint
     ].
 ! !
 
@@ -4660,10 +4663,14 @@
     "initialize style specific stuff"
 
     <resource: #style (#'menu.buttonItemHorizontalSpace' #'menu.buttonItemSpace'
-		       #'menu.buttonItemVerticalSpace'   #'menu.itemSpace'
-		       #'menu.itemHorizontalSpace'
-		       #'popup.hideOnRelease'
-		       )>
+                       #'menu.buttonItemVerticalSpace'   #'menu.itemSpace'
+                       #'menu.itemHorizontalSpace'
+                       #'menu.extraMargin'
+                       #'button.activeBackgroundColor'
+                       #'button.buttonEnteredBackgroundColor'
+                       #'button.buttonPassiveBackgroundColor'
+                       #'popup.hideOnRelease'
+                       )>
     |fn|
 
     super initStyle.
@@ -4677,8 +4684,10 @@
     buttonInsetY := buttonInsetY abs.
 
     itemSpace := styleSheet at:#'menu.itemHorizontalSpace'.
-    itemSpace isNil ifTrue:[ itemSpace := styleSheet at:#'menu.itemSpace' default:[ gc font widthOf:' '] ].
-
+    itemSpace isNil ifTrue:[ 
+        itemSpace := styleSheet at:#'menu.itemSpace' default:[ gc font widthOf:' '] 
+    ].
+    extraMargin := styleSheet at:#'menu.extraMargin' default:0.
 
     fgColor := DefaultForegroundColor.
     fgColor isNil ifTrue:[ fgColor := Color black ].
@@ -4692,6 +4701,19 @@
     buttonEnteredBackgroundColor := styleSheet colorAt:#'button.buttonEnteredBackgroundColor'.
     buttonPassiveBackgroundColor := styleSheet colorAt:#'button.buttonPassiveBackgroundColor'.
 
+    buttonActiveLevel := styleSheet at:#'menu.buttonActiveLevel' default:nil.
+    buttonActiveLevel isNil ifTrue:[
+        buttonActiveLevel := styleSheet at:#'button.activeLevel' default:0.
+    ].    
+    buttonPassiveLevel := styleSheet at:#'menu.buttonPassiveLevel' default:nil.
+    buttonPassiveLevel isNil ifTrue:[
+        buttonPassiveLevel := styleSheet at:#'button.passiveLevel' default:0.
+    ].    
+    buttonEnteredLevel := styleSheet at:#'menu.buttonEnteredLevel' default:nil.
+    buttonEnteredLevel isNil ifTrue:[
+        buttonEnteredLevel := styleSheet at:#'button.enteredLevel' default:0.
+    ].    
+    
     self updateLevelAndBorder.
 
     "Modified (format): / 19-01-2012 / 13:19:19 / cg"
@@ -4702,7 +4724,8 @@
 
     mustRearrange       := false.
     sizeFixed := true.
-
+    extraMargin := 0.
+    
     super initialize.
 
     self enableMotionEvents.  "/ for flyByHelp
@@ -8005,8 +8028,10 @@
     rtSep := nextItem notNil and:[nextItem isButton not].
 
     (lfSep or:[rtSep]) ifFalse:[
-	^ self
-    ].
+        ^ self
+    ].
+
+    menuPanel suppressSeparatingLines ifTrue:[^ self].
 
     lightColor := menuPanel lightColor.
     shadowColor := menuPanel shadowColor.
@@ -8019,19 +8044,19 @@
     b := layout bottom.
 
     menuPanel verticalLayout ifTrue:[
-	lfSep ifTrue:[menuPanel displayLineFromX:l y:t-1 toX:r y:t-1].
-	rtSep ifTrue:[menuPanel displayLineFromX:l y:b-1 toX:r y:b-1].
-
-	menuPanel paint:shadowColor.
-	lfSep ifTrue:[menuPanel displayLineFromX:l y:t-2 toX:r y:t-2].
-	rtSep ifTrue:[menuPanel displayLineFromX:l y:b-2 toX:r y:b-2].
+        lfSep ifTrue:[menuPanel displayLineFromX:l y:t-1 toX:r y:t-1].
+        rtSep ifTrue:[menuPanel displayLineFromX:l y:b-1 toX:r y:b-1].
+
+        menuPanel paint:shadowColor.
+        lfSep ifTrue:[menuPanel displayLineFromX:l y:t-2 toX:r y:t-2].
+        rtSep ifTrue:[menuPanel displayLineFromX:l y:b-2 toX:r y:b-2].
     ] ifFalse:[
-	lfSep ifTrue:[menuPanel displayLineFromX:l-1 y:t toX:l-1 y:b].
-	rtSep ifTrue:[menuPanel displayLineFromX:r-1 y:t toX:r-1 y:b].
-
-	menuPanel paint:shadowColor.
-	lfSep ifTrue:[menuPanel displayLineFromX:l-2 y:t toX:l-2 y:b].
-	rtSep ifTrue:[menuPanel displayLineFromX:r-2 y:t toX:r-2 y:b].
+        lfSep ifTrue:[menuPanel displayLineFromX:l-1 y:t toX:l-1 y:b].
+        rtSep ifTrue:[menuPanel displayLineFromX:r-1 y:t toX:r-1 y:b].
+
+        menuPanel paint:shadowColor.
+        lfSep ifTrue:[menuPanel displayLineFromX:l-2 y:t toX:l-2 y:b].
+        rtSep ifTrue:[menuPanel displayLineFromX:r-2 y:t toX:r-2 y:b].
     ]
 !
 
@@ -8048,9 +8073,10 @@
 
     type := self separatorType.
     (type isNil or:[type == #blankLine]) ifTrue:[
-	^ self
-    ].
-
+        ^ self
+    ].
+    menuPanel suppressSeparatingLines ifTrue:[^ self].
+    
     isDouble := type == #doubleLine.
 
     lightColor := menuPanel lightColor.
@@ -8061,30 +8087,30 @@
     top := layout top.
 
     menuPanel verticalLayout ifTrue:[
-	x0 := left  + HorizontalInset.
-	x1 := layout right - HorizontalInset.
-	y0 := top   - 1 + (layout height // 2).
-	isDouble ifTrue:[y0 := y0 - 2].
-
-	menuPanel displayLineFromX:x0 y:y0   toX:x1 y:y0.
-	isDouble ifTrue:[menuPanel displayLineFromX:x0 y:y0+4 toX:x1 y:y0+4].
-
-	menuPanel paint:lightColor.
-	menuPanel displayLineFromX:x0 y:y0+1 toX:x1 y:y0+1.
-	isDouble ifTrue:[menuPanel displayLineFromX:x0 y:y0+5 toX:x1 y:y0+5].
+        x0 := left  + HorizontalInset.
+        x1 := layout right - HorizontalInset.
+        y0 := top   - 1 + (layout height // 2).
+        isDouble ifTrue:[y0 := y0 - 2].
+
+        menuPanel displayLineFromX:x0 y:y0   toX:x1 y:y0.
+        isDouble ifTrue:[menuPanel displayLineFromX:x0 y:y0+4 toX:x1 y:y0+4].
+
+        menuPanel paint:lightColor.
+        menuPanel displayLineFromX:x0 y:y0+1 toX:x1 y:y0+1.
+        isDouble ifTrue:[menuPanel displayLineFromX:x0 y:y0+5 toX:x1 y:y0+5].
 
     ] ifFalse:[
-	y1 := layout bottom.
-	x0 := left - 1 + (layout width // 2).
-	y0 := top.
-	isDouble ifTrue:[x0 := x0 - 2].
-
-	menuPanel displayLineFromX:x0   y:y0 toX:x0   y:y1.
-	isDouble ifTrue:[menuPanel displayLineFromX:x0+4 y:y0 toX:x0+4 y:y1].
-
-	menuPanel paint:lightColor.
-	menuPanel displayLineFromX:x0+1 y:y0 toX:x0+1 y:y1.
-	isDouble ifTrue:[menuPanel displayLineFromX:x0+5 y:y0 toX:x0+5 y:y1].
+        y1 := layout bottom.
+        x0 := left - 1 + (layout width // 2).
+        y0 := top.
+        isDouble ifTrue:[x0 := x0 - 2].
+
+        menuPanel displayLineFromX:x0   y:y0 toX:x0   y:y1.
+        isDouble ifTrue:[menuPanel displayLineFromX:x0+4 y:y0 toX:x0+4 y:y1].
+
+        menuPanel paint:lightColor.
+        menuPanel displayLineFromX:x0+1 y:y0 toX:x0+1 y:y1.
+        isDouble ifTrue:[menuPanel displayLineFromX:x0+5 y:y0 toX:x0+5 y:y1].
     ]
 !