background color setting
authorClaus Gittinger <cg@exept.de>
Tue, 08 Sep 1998 12:17:48 +0200
changeset 1117 3181b8002e05
parent 1116 441ff42c1472
child 1118 a49afa5a9f10
background color setting
MenuPanel.st
--- a/MenuPanel.st	Tue Sep 08 12:17:12 1998 +0200
+++ b/MenuPanel.st	Tue Sep 08 12:17:48 1998 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -61,7 +61,7 @@
 copyright
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -86,12 +86,12 @@
 
 
     [author:]
-        Claus Atzkern
+	Claus Atzkern
 
     [see also:]
-        Menu
-        MenuItem
-        MenuEditor
+	Menu
+	MenuItem
+	MenuEditor
 "
 
 !
@@ -100,7 +100,7 @@
 
 "
     start as PullDownMenu
-                                                                                [exBegin]
+										[exBegin]
     |top subView mview desc s1 s2 s3 img lbs labels|
 
     top := StandardSystemView new.
@@ -141,11 +141,11 @@
     mview subMenuAt:2 put:(MenuPanel labels:labels).
     top extent:(mview preferredExtent).
     top open.
-                                                                                [exEnd]
+										[exEnd]
 
 
     start as PopUpMenu
-                                                                                [exBegin]
+										[exBegin]
     |subView mview desc s1 s2 s3 img lbs labels|
 
     mview := MenuPanel new.
@@ -173,52 +173,52 @@
 
     mview subMenuAt:2 put:(MenuPanel labels:labels).
     mview startUp
-                                                                                [exEnd]
+										[exEnd]
 
 
     start from menu spec
-                                                                                [exBegin]
+										[exBegin]
     |menu|
 
     menu := MenuPanel menu:
-        #(#Menu #( #(#MenuItem 
-                    #label: 'File' 
-                    #submenu:
-                      #(#Menu #(#(#MenuItem #label: 'quit' #value:#quit )     
-                                 (#MenuItem 
-                                    #label: 'edit' 
-                                    #submenu:
-                                      #(#Menu #( #(#MenuItem #label: 'edit'  #value:#edit )     
-                                                 #(#MenuItem #label: 'close' #value:#close)     
-                                               )
-                                               nil
-                                               nil
-                                       )     
-                                  )
-                                 #(#MenuItem #label: 'help' #value:#help )     
-                               )
-                               nil
-                               nil
-                       )     
-                 ) 
-                #(#MenuItem #label: 'Inspect' #value:#inspectMenu ) 
-                #(#MenuItem #label: 'Bar' 
-                            #submenu:
-                               #(#Menu #( #(#MenuItem #label: 'bar 1' #value:#bar1 )     
-                                          #(#MenuItem #label: 'bar 2' #value:#bar2 )     
-                                        )
-                                        nil
-                                        nil
-                                )     
-                 ) 
-              ) 
-              #( 2 )
-              nil
-         ) decodeAsLiteralArray.  
+	#(#Menu #( #(#MenuItem 
+		    #label: 'File' 
+		    #submenu:
+		      #(#Menu #(#(#MenuItem #label: 'quit' #value:#quit )     
+				 (#MenuItem 
+				    #label: 'edit' 
+				    #submenu:
+				      #(#Menu #( #(#MenuItem #label: 'edit'  #value:#edit )     
+						 #(#MenuItem #label: 'close' #value:#close)     
+					       )
+					       nil
+					       nil
+				       )     
+				  )
+				 #(#MenuItem #label: 'help' #value:#help )     
+			       )
+			       nil
+			       nil
+		       )     
+		 ) 
+		#(#MenuItem #label: 'Inspect' #value:#inspectMenu ) 
+		#(#MenuItem #label: 'Bar' 
+			    #submenu:
+			       #(#Menu #( #(#MenuItem #label: 'bar 1' #value:#bar1 )     
+					  #(#MenuItem #label: 'bar 2' #value:#bar2 )     
+					)
+					nil
+					nil
+				)     
+		 ) 
+	      ) 
+	      #( 2 )
+	      nil
+	 ) decodeAsLiteralArray.  
 
     menu verticalLayout:false.
     Transcript showCR:(menu startUp).
-                                                                                [exEnd]
+										[exEnd]
 
 "
 
@@ -234,8 +234,8 @@
     |menu|
 
     aSpec notNil ifTrue:[
-        menu := Menu new.
-        menu fromLiteralArrayEncoding:aSpec.
+	menu := Menu new.
+	menu fromLiteralArrayEncoding:aSpec.
     ].
   ^ self menu:menu receiver:aReceiver
 !
@@ -276,7 +276,7 @@
 "/ thus we do not overwrite the receiver
 
     aReceiver notNil ifTrue:[
-        mview receiver:aReceiver
+	mview receiver:aReceiver
     ].
   ^ mview
 
@@ -291,17 +291,17 @@
     "
 
     InitialSelectionQuerySignal isNil ifTrue:[
-        InitialSelectionQuerySignal := QuerySignal new.
+	InitialSelectionQuerySignal := QuerySignal new.
     ].
 
     DefaultAdornment isNil ifTrue:[
-        DefaultAdornment := IdentityDictionary new
-            at:#showSeparatingLines put:false;
-            at:#showGroupDivider    put:true;
-            at:#verticalLayout      put:true;
-            at:#item                put:nil;
-            at:#value               put:nil;
-            yourself
+	DefaultAdornment := IdentityDictionary new
+	    at:#showSeparatingLines put:false;
+	    at:#showGroupDivider    put:true;
+	    at:#verticalLayout      put:true;
+	    at:#item                put:nil;
+	    at:#value               put:nil;
+	    yourself
     ].
 
     "Modified: / 15.1.1998 / 23:08:31 / stefan"
@@ -323,9 +323,9 @@
 
     menuStyle := MenuView styleSheet.
     menuStyle isNil ifTrue:[
-        "make sure that style sheet is present"
-        MenuView updateStyleCache.        
-        menuStyle := MenuView styleSheet.
+	"make sure that style sheet is present"
+	MenuView updateStyleCache.        
+	menuStyle := MenuView styleSheet.
     ].
     style := menuStyle name.
 
@@ -333,48 +333,48 @@
     DefaultForegroundColor := menuStyle colorAt:'pullDownMenu.foregroundColor'.
 
     DefaultForegroundColor isNil ifTrue:[
-        DefaultForegroundColor := menuStyle colorAt:'menu.foregroundColor'
-                                            default:Color black.
+	DefaultForegroundColor := menuStyle colorAt:'menu.foregroundColor'
+					    default:Color black.
     ].
 
     (style == #motif or:[style == #iris]) ifTrue:[
-        DefaultBackgroundColor        := DefaultViewBackgroundColor.
-        DefaultHilightForegroundColor := DefaultForegroundColor.
-        DefaultHilightLevel     := 2.
-        DefaultLevel            := 0.
+	DefaultBackgroundColor        := DefaultViewBackgroundColor.
+	DefaultHilightForegroundColor := DefaultForegroundColor.
+	DefaultHilightLevel     := 2.
+	DefaultLevel            := 0.
     ] ifFalse:[
-        (DefaultHilightLevel := menuStyle at:'pullDownMenu.hilightLevel') isNil ifTrue:[
-            DefaultHilightLevel := menuStyle at:'menu.hilightLevel' default:0.
-        ].
-        DefaultLevel           := menuStyle at:'pullDownMenu.level' default:1.
-        DefaultBackgroundColor := menuStyle colorAt:'pullDownMenu.backgroundColor'.
-
-        DefaultBackgroundColor isNil ifTrue:[
-            DefaultBackgroundColor := menuStyle colorAt:'menu.backgroundColor'
-                                                default:DefaultViewBackgroundColor.
-        ].
-
-        DefaultHilightForegroundColor := menuStyle colorAt:'pullDownMenu.hilightForegroundColor'.
-        DefaultHilightForegroundColor isNil ifTrue:[
-            DefaultHilightForegroundColor := menuStyle colorAt:'menu.hilightForegroundColor'
-                                                       default:DefaultBackgroundColor
-        ].
+	(DefaultHilightLevel := menuStyle at:'pullDownMenu.hilightLevel') isNil ifTrue:[
+	    DefaultHilightLevel := menuStyle at:'menu.hilightLevel' default:0.
+	].
+	DefaultLevel           := menuStyle at:'pullDownMenu.level' default:1.
+	DefaultBackgroundColor := menuStyle colorAt:'pullDownMenu.backgroundColor'.
+
+	DefaultBackgroundColor isNil ifTrue:[
+	    DefaultBackgroundColor := menuStyle colorAt:'menu.backgroundColor'
+						default:DefaultViewBackgroundColor.
+	].
+
+	DefaultHilightForegroundColor := menuStyle colorAt:'pullDownMenu.hilightForegroundColor'.
+	DefaultHilightForegroundColor isNil ifTrue:[
+	    DefaultHilightForegroundColor := menuStyle colorAt:'menu.hilightForegroundColor'
+						       default:DefaultBackgroundColor
+	].
     ].
 
     DefaultDisabledForegroundColor := menuStyle colorAt:'menu.disabledForegroundColor'.
     DefaultDisabledForegroundColor isNil ifTrue:[
-        DefaultDisabledForegroundColor := menuStyle colorAt:'button.disabledForegroundColor'
-                                                    default:Color darkGray.
+	DefaultDisabledForegroundColor := menuStyle colorAt:'button.disabledForegroundColor'
+						    default:Color darkGray.
     ].
 
     style == #motif ifTrue:[
-        DefaultHilightBackgroundColor := DefaultBackgroundColor
+	DefaultHilightBackgroundColor := DefaultBackgroundColor
     ] ifFalse:[
-        DefaultHilightBackgroundColor := menuStyle colorAt:'pullDownMenu.hilightBackgroundColor'.
-        DefaultHilightBackgroundColor isNil ifTrue:[
-            DefaultHilightBackgroundColor := menuStyle colorAt:'menu.hilightBackgroundColor'
-                                                       default:(menuStyle is3D ifFalse:[DefaultForegroundColor] ifTrue:[DefaultBackgroundColor]).
-        ]
+	DefaultHilightBackgroundColor := menuStyle colorAt:'pullDownMenu.hilightBackgroundColor'.
+	DefaultHilightBackgroundColor isNil ifTrue:[
+	    DefaultHilightBackgroundColor := menuStyle colorAt:'menu.hilightBackgroundColor'
+						       default:(menuStyle is3D ifFalse:[DefaultForegroundColor] ifTrue:[DefaultBackgroundColor]).
+	]
     ].
 
     DefaultGroupDividerSize := menuStyle at:'menu.groupDividerSize' default:6.
@@ -391,9 +391,9 @@
     RightArrowForm := SelectionInListView rightArrowFormOn:Display.
 
     (style ~~ #os2 and:[style ~~ #win95]) ifTrue:[
-        RightArrowShadowForm := SelectionInListView rightArrowShadowFormOn:Display.
+	RightArrowShadowForm := SelectionInListView rightArrowShadowFormOn:Display.
     ] ifFalse:[
-        RightArrowShadowForm := nil
+	RightArrowShadowForm := nil
     ].
 
     SelectionFrameBrightColor    := Color white.
@@ -401,11 +401,11 @@
 
     ButtonActiveLevel            :=  menuStyle at:'menu.buttonActiveLevel' default:(menuStyle is3D ifTrue:[-2] ifFalse:[0]).
     ButtonActiveLevel isNil ifTrue:[
-        ButtonActiveLevel        :=  menuStyle at:'button.activeLevel' default:(menuStyle is3D ifTrue:[-2] ifFalse:[0]).
+	ButtonActiveLevel        :=  menuStyle at:'button.activeLevel' default:(menuStyle is3D ifTrue:[-2] ifFalse:[0]).
     ].
     ButtonPassiveLevel           :=  menuStyle at:'menu.buttonPassiveLevel'.
     ButtonPassiveLevel isNil ifTrue:[
-        ButtonPassiveLevel       :=  menuStyle at:'button.passiveLevel' default:(menuStyle is3D ifTrue:[2] ifFalse:[0]).
+	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.
@@ -417,8 +417,8 @@
 
     ButtonEnteredBackgroundColor := menuStyle colorAt:'menu.buttonEnteredBackgroundColor'.
     ButtonEnteredBackgroundColor isNil ifTrue:[
-        ButtonEnteredBackgroundColor := menuStyle colorAt:'button.enteredBackgroundColor'
-                                                  default:ButtonPassiveBackgroundColor.
+	ButtonEnteredBackgroundColor := menuStyle colorAt:'button.enteredBackgroundColor'
+						  default:ButtonPassiveBackgroundColor.
     ].
     ButtonEnteredLevel := menuStyle at:'menu.buttonEnteredLevel' default:ButtonPassiveLevel.
 
@@ -442,11 +442,11 @@
     Images isNil ifTrue:[ Images := IdentityDictionary new ].
 
     (deviceImages := Images at:aDevice ifAbsent:nil) isNil ifTrue:[
-        Images at:aDevice put:(deviceImages := Dictionary new)
+	Images at:aDevice put:(deviceImages := Dictionary new)
     ].
 
     (image := deviceImages at:anImage ifAbsent:nil) notNil ifTrue:[
-        ^ image
+	^ image
     ].
 
     image := anImage copy onDevice:aDevice.
@@ -466,18 +466,18 @@
     LigthenedImages isNil ifTrue:[ LigthenedImages := IdentityDictionary new ].
 
     (deviceImages := LigthenedImages at:aDevice ifAbsent:nil) isNil ifTrue:[
-        LigthenedImages at:aDevice put:(deviceImages := Dictionary new)
+	LigthenedImages at:aDevice put:(deviceImages := Dictionary new)
     ].
 
     (image := deviceImages at:anImage ifAbsent:nil) notNil ifTrue:[
-        ^ image
+	^ image
     ].
 
     ((anImage respondsTo:#colorMap) and:[anImage colorMap notNil]) ifTrue:[
-        image := anImage copy lightened onDevice:aDevice.
-        image clearMaskedPixels.
+	image := anImage copy lightened onDevice:aDevice.
+	image clearMaskedPixels.
     ] ifFalse:[
-        image := self image:anImage onDevice:aDevice
+	image := self image:anImage onDevice:aDevice
     ].
     deviceImages at:anImage put:image.
     ^ image
@@ -509,30 +509,30 @@
     |value item tgState itemIdx recv|
 
     self superMenu notNil ifTrue:[
-        ^ self topMenu accept:anItem
+	^ self topMenu accept:anItem
     ].
     lastButtonSelected := nil.
     self selection:nil.
     self forceUngrabMouseAndKeyboard.
 
     (anItem notNil and:[anItem canAccept]) ifTrue:[
-        tgState := anItem toggleIndication.
-        itemIdx := anItem menuPanel findFirst:[:el| el == anItem ].
-        item    := anItem.
-        recv    := anItem menuPanel receiver.
+	tgState := anItem toggleIndication.
+	itemIdx := anItem menuPanel findFirst:[:el| el == anItem ].
+	item    := anItem.
+	recv    := anItem menuPanel receiver.
     ].
 
     self isPopUpView ifFalse:[
-        self do:[:el| el updateIndicators].
-        self windowGroup processExposeEvents.
+	self do:[:el| el updateIndicators].
+	self windowGroup processExposeEvents.
     ] ifTrue:[
-        self destroy
+	self destroy
     ].
     value := self accept:item index:itemIdx toggle:tgState receiver:recv.
 
     self isPopUpView ifTrue:[
-        self menuAdornmentAt:#value put:value.
-        self menuAdornmentAt:#item  put:item.
+	self menuAdornmentAt:#value put:value.
+	self menuAdornmentAt:#item  put:item.
     ].
 
   ^ item.
@@ -546,50 +546,50 @@
     |value argument numArgs isKindOfValueModel|
 
     anItem isNil ifTrue:[
-        self menuAdornmentAt:#hasPerformed put:true.
+	self menuAdornmentAt:#hasPerformed put:true.
       ^ nil
     ].
 
     self menuAdornmentAt:#hasPerformed put:(aReceiver isKindOf:ValueModel).
 
     (value := anItem value) isNil ifTrue:[
-        ^ anIndex
+	^ anIndex
     ].
 
     (argument := anItem argument) isNil ifTrue:[
-        argument := aState ? anItem
+	argument := aState ? anItem
     ].
 
     value isSymbol ifFalse:[
-        (value respondsTo:#numArgs) ifTrue:[numArgs := value numArgs]
-                                   ifFalse:[numArgs := 0].
-
-        numArgs == 0 ifTrue:[
-            value value
-        ] ifFalse:[
-            numArgs == 1 ifTrue:[value value:argument]
-                        ifFalse:[value value:argument value:self]
-        ].
-        self menuAdornmentAt:#hasPerformed put:true.
+	(value respondsTo:#numArgs) ifTrue:[numArgs := value numArgs]
+				   ifFalse:[numArgs := 0].
+
+	numArgs == 0 ifTrue:[
+	    value value
+	] ifFalse:[
+	    numArgs == 1 ifTrue:[value value:argument]
+			ifFalse:[value value:argument value:self]
+	].
+	self menuAdornmentAt:#hasPerformed put:true.
       ^ anIndex
     ].
 
     aReceiver isNil ifTrue:[
-        ^ value
+	^ value
     ].
     isKindOfValueModel := aReceiver isKindOf:ValueModel.
 
     (numArgs := value numArgs) == 0 ifTrue:[
-        isKindOfValueModel ifFalse:[aReceiver perform:value]
-                            ifTrue:[aReceiver value:value]
+	isKindOfValueModel ifFalse:[aReceiver perform:value]
+			    ifTrue:[aReceiver value:value]
     ] ifFalse:[
-        numArgs == 1 ifTrue:[
-            isKindOfValueModel ifFalse:[aReceiver perform:value with:argument]
-                                ifTrue:[aReceiver value:value value:argument]
-        ] ifFalse:[
-            isKindOfValueModel ifFalse:[aReceiver perform:value with:argument with:self]
-                                ifTrue:[aReceiver value:value value:argument value:self]
-        ]
+	numArgs == 1 ifTrue:[
+	    isKindOfValueModel ifFalse:[aReceiver perform:value with:argument]
+				ifTrue:[aReceiver value:value value:argument]
+	] ifFalse:[
+	    isKindOfValueModel ifFalse:[aReceiver perform:value with:argument with:self]
+				ifTrue:[aReceiver value:value value:argument value:self]
+	]
     ].
     self menuAdornmentAt:#hasPerformed put:true.
   ^ value
@@ -687,8 +687,8 @@
     "sets collection of group sizes
     "
     aGroupSizes = groupSizes ifFalse:[
-        groupSizes := aGroupSizes copy.
-        self mustRearrange.
+	groupSizes := aGroupSizes copy.
+	self mustRearrange.
     ].
 !
 
@@ -715,11 +715,11 @@
     "define labels for each item
     "
     self disabledRedrawDo:[
-        self removeAll.
-
-        labels notNil ifTrue:[
-            labels do:[:aLabel|(self createAtIndex:nil) label:aLabel]
-        ]
+	self removeAll.
+
+	labels notNil ifTrue:[
+	    labels do:[:aLabel|(self createAtIndex:nil) label:aLabel]
+	]
     ]
 !
 
@@ -758,7 +758,7 @@
      from all submenus no specific receiver is defined ).
     "
     (receiver isNil and:[superMenu notNil]) ifTrue:[
-        ^ superMenu receiver
+	^ superMenu receiver
     ].
   ^ receiver
 !
@@ -870,12 +870,12 @@
     state := aState ? true.
 
     self enabled == state ifTrue:[
-        ^ self
+	^ self
     ].
     enabled := state.
 
     self canDrawItem ifTrue:[
-        self do:[:anItem| anItem enabledStateOfMenuChangedTo:enabled]
+	self do:[:anItem| anItem enabledStateOfMenuChangedTo:enabled]
     ].
 !
 
@@ -909,11 +909,11 @@
     "set my enableChannel
     "
     enableChannel notNil ifTrue:[
-        enableChannel removeDependent:self
+	enableChannel removeDependent:self
     ].
 
     (enableChannel := aValueHolder) notNil ifTrue:[
-        enableChannel addDependent:self.
+	enableChannel addDependent:self.
     ].
     self enabled:(enableChannel value).
 !
@@ -928,11 +928,11 @@
     "set my menuHolder
     "
     menuHolder notNil ifTrue:[
-        menuHolder removeDependent:self
+	menuHolder removeDependent:self
     ].
 
     (menuHolder := aValueHolder) notNil ifTrue:[
-        menuHolder addDependent:self.
+	menuHolder addDependent:self.
     ].
     self menu:(menuHolder value)
 ! !
@@ -950,10 +950,10 @@
      use this method; instead leave the value as defined in the styleSheet.
     "
     activeBgColor ~~ aColor ifTrue:[
-        activeBgColor := aColor on:device.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	activeBgColor := aColor on:device.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ]
 
     "Modified: / 6.6.1998 / 19:49:46 / cg"
@@ -970,10 +970,10 @@
      use this method; instead leave the value as defined in the styleSheet.
     "
     activeFgColor ~~ aColor ifTrue:[
-        activeFgColor := aColor on:device.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	activeFgColor := aColor on:device.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ]
 
     "Modified: / 6.6.1998 / 19:50:01 / cg"
@@ -990,10 +990,10 @@
      instead leave the value as defined in the styleSheet.
     "
     super viewBackground ~~ aColor ifTrue:[
-        super viewBackground:aColor.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	super viewBackground:aColor.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ]
 
     "Modified: / 6.6.1998 / 19:50:06 / cg"
@@ -1070,10 +1070,10 @@
      use this method; instead leave the value as defined in the styleSheet.
     "
     disabledFgColor ~~ aColor ifTrue:[
-        disabledFgColor := aColor on:device.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	disabledFgColor := aColor on:device.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ].
 
     "Modified: / 6.6.1998 / 19:50:17 / cg"
@@ -1083,12 +1083,12 @@
     "set the font
     "
     (aFont notNil and:[aFont ~= font]) ifTrue:[
-        super font:(aFont on:device).
-
-        superMenu notNil ifTrue:[
-            self extent:(self preferredExtent)
-        ].
-        self mustRearrange.
+	super font:(aFont on:device).
+
+	superMenu notNil ifTrue:[
+	    self extent:(self preferredExtent)
+	].
+	self mustRearrange.
     ]
 !
 
@@ -1105,10 +1105,10 @@
      instead leave the value as defined in the styleSheet.
     "
     fgColor ~~ aColor ifTrue:[
-        fgColor := aColor on:device.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	fgColor := aColor on:device.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ]
 
     "Modified: / 6.6.1998 / 19:50:46 / cg"
@@ -1127,10 +1127,10 @@
      instead leave the value as defined in the styleSheet.
     "
     lightColor ~~ aColor ifTrue:[
-        super lightColor:aColor.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	super lightColor:aColor.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ]
 
     "Modified: / 6.6.1998 / 19:50:39 / cg"
@@ -1161,10 +1161,10 @@
      instead leave the value as defined in the styleSheet.
     "
     shadowColor ~~ aColor ifTrue:[
-        super shadowColor:aColor.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	super shadowColor:aColor.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ]
 
     "Modified: / 6.6.1998 / 19:50:32 / cg"
@@ -1178,11 +1178,11 @@
     |item|
 
     (explicitExtent ~~ true) ifTrue:[
-        (item := self itemAt:1) notNil ifTrue:[
-            self rearrangeItems.
-          ^ item height
-        ].
-        ^ 4 + (font height + (font descent * 2)).
+	(item := self itemAt:1) notNil ifTrue:[
+	    self rearrangeItems.
+	  ^ item height
+	].
+	^ 4 + (font height + (font descent * 2)).
     ].
     ^ super height
 !
@@ -1193,71 +1193,71 @@
     |x y hasMenu shCtKey space hrzInset|
 
     self numberOfItems == 0 ifTrue:[
-        ^ 32 @ 32
+	^ 32 @ 32
     ].
     space := (items size + 1) * itemSpace.
 
     self isFitPanel ifTrue:[
-        x := 0
+	x := 0
     ] ifFalse:[
-        x := groupSizes size * groupDividerSize.
+	x := groupSizes size * groupDividerSize.
     ].
     hrzInset := items first horizontalInset.
 
     self verticalLayout ifFalse:[
-        "/ horizontal - add x-extents; take max of y-extents
-        y := 0.
-
-        self do:[:el| |elY elPref|
-            el isVisible ifTrue:[
-                elPref := el preferredExtent.
-                x := x + elPref x.
-                elY := elPref y.
-                el isButton ifTrue:[
-                    elY := elY + (2 * DefaultButtonItemSpace).
-                    x := x + (2 * DefaultButtonItemSpace).
-                ].
-                y := y max:elY.
-            ]
-        ].
-        x := x + space.
+	"/ horizontal - add x-extents; take max of y-extents
+	y := 0.
+
+	self do:[:el| |elY elPref|
+	    el isVisible ifTrue:[
+		elPref := el preferredExtent.
+		x := x + elPref x.
+		elY := elPref y.
+		el isButton ifTrue:[
+		    elY := elY + (2 * DefaultButtonItemSpace).
+		    x := x + (2 * DefaultButtonItemSpace).
+		].
+		y := y max:elY.
+	    ]
+	].
+	x := x + space.
     ] ifTrue:[
-        "/ vertical - add y-extents
-        hasMenu := false.
-        shCtKey := 0.
-        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 or:[el submenuChannel notNil]) ifTrue:[
-                        hasMenu := true
-                    ].
-
-                    (     (l := el shortcutKeyAsString) notNil
-                     and:[(e := l widthOn:self) > shCtKey]
-                    ) ifTrue:[
-                        shCtKey := e
-                    ].
-                ].
-                y := y + el preferredExtent y
-            ]
-        ].
-        x := x + hrzInset.
-
-        (hasMenu or:[shCtKey ~~ 0]) ifTrue:[
-            shortKeyInset := x + Item labelRightOffset.
-            x := shortKeyInset + shCtKey + self subMenuIndicationWidth.
-
-            (shCtKey ~~ 0 and:[hasMenu]) ifTrue:[
-                x := x + (Item shortcutKeyOffset) 
-            ]
-        ].
-        y := y + space.
-        x := x + hrzInset.
+	"/ vertical - add y-extents
+	hasMenu := false.
+	shCtKey := 0.
+	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 or:[el submenuChannel notNil]) ifTrue:[
+			hasMenu := true
+		    ].
+
+		    (     (l := el shortcutKeyAsString) notNil
+		     and:[(e := l widthOn:self) > shCtKey]
+		    ) ifTrue:[
+			shCtKey := e
+		    ].
+		].
+		y := y + el preferredExtent y
+	    ]
+	].
+	x := x + hrzInset.
+
+	(hasMenu or:[shCtKey ~~ 0]) ifTrue:[
+	    shortKeyInset := x + Item labelRightOffset.
+	    x := shortKeyInset + shCtKey + self subMenuIndicationWidth.
+
+	    (shCtKey ~~ 0 and:[hasMenu]) ifTrue:[
+		x := x + (Item shortcutKeyOffset) 
+	    ]
+	].
+	y := y + space.
+	x := x + hrzInset.
     ].
     ^ (x @ y) + (margin + margin)
 
@@ -1340,8 +1340,8 @@
      to the extent of its superView
     "
     (fitFirstPanel == aState or:[self isPopUpView]) ifFalse:[
-        fitFirstPanel := aState.
-        self mustRearrange
+	fitFirstPanel := aState.
+	self mustRearrange
     ]
 !
 
@@ -1357,8 +1357,8 @@
      method; instead leave the value as defined in the styleSheet.
     "
     aSize ~~ groupDividerSize ifTrue:[
-        groupDividerSize := aSize.
-        self mustRearrange.
+	groupDividerSize := aSize.
+	self mustRearrange.
     ].
 
 !
@@ -1375,8 +1375,8 @@
      method; instead leave the value as defined in the styleSheet.
     "
     aSize ~~ itemSpace ifTrue:[
-        itemSpace := aSize.
-        self mustRearrange
+	itemSpace := aSize.
+	self mustRearrange
     ].
 
 !
@@ -1404,7 +1404,7 @@
     "set the enabled flag for showing groupDiveders
     "
     (self menuAdornmentAt:#showGroupDivider put:aState) ifTrue:[
-        self mustRearrange.
+	self mustRearrange.
     ]
 !
 
@@ -1418,7 +1418,7 @@
     "turn on/off drawing of separating lines.
     "
     (self menuAdornmentAt:#showSeparatingLines put:aState) ifTrue:[
-        self mustRearrange
+	self mustRearrange
     ]
 !
 
@@ -1432,7 +1432,7 @@
     "set the layout: or vertical( true ) or horizontal( false )
     "
     (self menuAdornmentAt:#verticalLayout put:aState) ifTrue:[        
-        self mustRearrange
+	self mustRearrange
     ]
 ! !
 
@@ -1457,7 +1457,7 @@
     |item|
 
     (item := self selection) notNil ifTrue:[
-        ^ item submenu
+	^ item submenu
     ].
   ^ nil
 ! !
@@ -1500,7 +1500,7 @@
     self rearrangeItems.
 
     aBoolean ifTrue:[
-        self fixSize.
+	self fixSize.
     ].
     self origin:aPoint.
     self makeFullyVisible.
@@ -1510,7 +1510,7 @@
     "/ return nil - to avoid items triggering twice.
 
     (self topMenu menuAdornmentAt:#hasPerformed) == true ifTrue:[
-        ^ nil
+	^ nil
     ].
     ^ self lastValueAccepted
 
@@ -1557,11 +1557,11 @@
     |appl item key|
 
     (item := self selection) notNil ifTrue:[
-        (key := item activeHelpKey) notNil ifTrue:[
-            (appl := self application) notNil ifTrue:[
-                ^ appl helpTextForKey:key.
-            ].
-        ]
+	(key := item activeHelpKey) notNil ifTrue:[
+	    (appl := self application) notNil ifTrue:[
+		^ appl helpTextForKey:key.
+	    ].
+	]
     ].
     ^ nil.
 
@@ -1575,17 +1575,17 @@
 
     menu isNil ifTrue:[
 "/        'nil menu' printCR.
-        ^ ''
+	^ ''
     ].
 
     point := self translatePoint:aPoint to:menu.
     item  := menu itemAtX:(point x) y:(point y).
     item  notNil ifTrue:[
-        (key := item activeHelpKey) notNil ifTrue:[
-            (appl := self application) notNil ifTrue:[
-                ^ appl helpTextForKey:key.
-            ].
-        ]
+	(key := item activeHelpKey) notNil ifTrue:[
+	    (appl := self application) notNil ifTrue:[
+		^ appl helpTextForKey:key.
+	    ].
+	]
     ].
 "/    'nil item' printCR.
     ^ nil.
@@ -1605,19 +1605,19 @@
     max := (items size) + 1.
 
     anIndexOrNil notNil ifTrue:[
-        (anIndexOrNil < 1 or:[anIndexOrNil > max]) ifTrue:[
-            ^ nil
-        ]
+	(anIndexOrNil < 1 or:[anIndexOrNil > max]) ifTrue:[
+	    ^ nil
+	]
     ].
     items isNil ifTrue:[
-        items := OrderedCollection new
+	items := OrderedCollection new
     ].
     item := Item in:self.
 
     (anIndexOrNil isNil or:[anIndexOrNil == max]) ifTrue:[
-        items add:item
+	items add:item
     ] ifFalse:[
-        items add:item beforeIndex:anIndexOrNil
+	items add:item beforeIndex:anIndexOrNil
     ].
     ^ item
 !
@@ -1629,10 +1629,10 @@
     |item|
 
     (item := self itemAt:stringOrNumber) notNil ifTrue:[
-        items remove:item.
-        item  destroy.
-        items isEmpty ifTrue:[items := nil].
-        self mustRearrange.
+	items remove:item.
+	item  destroy.
+	items isEmpty ifTrue:[items := nil].
+	self mustRearrange.
     ].
   ^ item
 !
@@ -1641,10 +1641,10 @@
     "remove all items and submenus
     "
     self disabledRedrawDo:[
-        self selection:nil.
-        groupSizes := nil.
-        self do:[:el| el destroy ].
-        items := nil
+	self selection:nil.
+	groupSizes := nil.
+	self do:[:el| el destroy ].
+	items := nil
     ].
 ! !
 
@@ -1686,28 +1686,28 @@
     "convert to Menu
     "
     self disabledRedrawDo:[
-        |menu newItems|
-
-        self removeAll.
-
-        (menu := aMenu) notNil ifTrue:[
-            (aMenu isCollection) ifTrue:[
-                menu := Menu new.
-                menu fromLiteralArrayEncoding:aMenu.
-            ] ifFalse:[
-                menu receiver notNil ifTrue:[receiver := menu receiver]
-            ].
-            (newItems := menu menuItems) notNil ifTrue:[
-                items := newItems collect:[:ni | 
-                                |i|
-
-                                i:= Item in:self.
-                                i menuItem:ni.
-                                i.
-                            ].
-            ].
-            self groupSizes:(menu groupSizes).
-        ]
+	|menu newItems|
+
+	self removeAll.
+
+	(menu := aMenu) notNil ifTrue:[
+	    (aMenu isCollection) ifTrue:[
+		menu := Menu new.
+		menu fromLiteralArrayEncoding:aMenu.
+	    ] ifFalse:[
+		menu receiver notNil ifTrue:[receiver := menu receiver]
+	    ].
+	    (newItems := menu menuItems) notNil ifTrue:[
+		items := newItems collect:[:ni | 
+				|i|
+
+				i:= Item in:self.
+				i menuItem:ni.
+				i.
+			    ].
+	    ].
+	    self groupSizes:(menu groupSizes).
+	]
     ]
 
     "Modified: / 8.8.1998 / 02:05:04 / cg"
@@ -1732,22 +1732,22 @@
     |shadow|
 
     styleSheet is3D ifFalse:[
-        ^ self displayRectangle:layout.
+	^ self displayRectangle:layout.
     ].
 
     shadow := buttonShadowColor.
     isSelected ifTrue:[
-        buttonShadowColor == self buttonActiveBackgroundColor ifTrue:[
-            shadow := self buttonActiveBackgroundColor darkened
-        ].
+	buttonShadowColor == self buttonActiveBackgroundColor ifTrue:[
+	    shadow := self buttonActiveBackgroundColor darkened
+	].
     ].
 
     self drawEdgesForX: layout left y: layout top width: layout width height: layout height level: aLevel 
-        shadow:      shadow 
-        light:       buttonLightColor
-        halfShadow:  buttonHalfShadowColor 
-        halfLight:   buttonHalfLightColor
-        style:       ButtonEdgeStyle
+	shadow:      shadow 
+	light:       buttonLightColor
+	halfShadow:  buttonHalfShadowColor 
+	halfLight:   buttonHalfLightColor
+	style:       ButtonEdgeStyle
 
     "Created: / 20.8.1998 / 15:43:38 / cg"
     "Modified: / 20.8.1998 / 19:09:05 / cg"
@@ -1757,11 +1757,11 @@
     |level|
 
     level := selectedBool 
-                ifTrue:[onLevel] 
-                ifFalse:[offLevel].
+		ifTrue:[onLevel] 
+		ifFalse:[offLevel].
 
     level ~~ 0 ifTrue:[
-        self drawEdgesForX:x y:y width:w height:height level:level
+	self drawEdgesForX:x y:y width:w height:height level:level
     ].
 
     "Modified: / 20.8.1998 / 15:43:11 / cg"
@@ -1771,10 +1771,10 @@
     "force rearrange (i.e. set the rearrange flag)
     "
     mustRearrange == true ifFalse:[
-        mustRearrange := true.
-        shown ifTrue:[
-            self invalidate "/ RepairNow:true
-        ]
+	mustRearrange := true.
+	shown ifTrue:[
+	    self invalidate "/ RepairNow:true
+	]
     ]
 
     "Modified: / 6.6.1998 / 19:51:07 / cg"
@@ -1787,28 +1787,28 @@
     |
 
     (self isPopUpView or:[self verticalLayout]) ifTrue:[
-        ^ self
+	^ self
     ].
 
     layout := items last layout.
 
     (dltX := width - margin "- 2" - layout right) <= 0 ifTrue:[
-        ^ self  "/ no free space
+	^ self  "/ no free space
     ].
     start := items findFirst:[:anItem| anItem startGroup == #right ].
 
     start == 0 ifTrue:[
-        ^ self  "/ no item detected
+	^ self  "/ no item detected
     ].
 
     "/ change layout
 
     items from:start do:[:anItem|
-        anItem isVisible ifTrue:[
-            layout := anItem layout.
-            layout  left:(layout  left + dltX).
-            layout right:(layout right + dltX).
-        ]
+	anItem isVisible ifTrue:[
+	    layout := anItem layout.
+	    layout  left:(layout  left + dltX).
+	    layout right:(layout right + dltX).
+	]
     ].
 !
 
@@ -1825,111 +1825,111 @@
 
 "/  fetch font from superMenu
     (superMenu notNil and:[superMenu font ~~ font]) ifTrue:[
-        super font:(superMenu font on:device)
+	super font:(superMenu font on:device)
     ].
     (noItems := items size) == 0 ifTrue:[
-        mustRearrange := false.
+	mustRearrange := false.
       ^ self
     ].
     expLast  := false.
     isVert   := self verticalLayout.
 
     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
-            ]
-        ]
+	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
+	    ]
+	]
     ].
 
     (self isPopUpView or:[explicitExtent ~~ true]) ifTrue:[
-        e := self preferredExtent copy.
-
-        self isPopUpView ifFalse:[
-            isVert ifTrue:[e y:1.0]
-                  ifFalse:[e x:1.0]
-        ].
-        self extent:e
+	e := self preferredExtent copy.
+
+	self isPopUpView ifFalse:[
+	    isVert ifTrue:[e y:1.0]
+		  ifFalse:[e x:1.0]
+	].
+	self extent:e
     ] ifFalse:[
-        e := self computeExtent
+	e := self computeExtent
     ].
 
     x := y := margin.
 
     isVert ifTrue:[y := y + itemSpace]
-          ifFalse:[x := x + 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.
-                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.
-                ] ifFalse:[
-                    corn := (x @ e y).
-                    el layout:(Rectangle origin:org corner:corn).
-                ].
-                x := x + itemSpace.
-            ].
-
-            (grpDivSz notNil and:[self hasGroupDividerAt:anIndex]) ifTrue:[
-                isVert ifTrue:[y := y + grpDivSz]
-                      ifFalse:[x := x + grpDivSz]
-            ]
-        ] ifFalse:[
-            org := Point x:x y:y.
-            el layout:(Rectangle origin:org corner:org)
-        ]
+	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.
+		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.
+		] ifFalse:[
+		    corn := (x @ e y).
+		    el layout:(Rectangle origin:org corner:corn).
+		].
+		x := x + itemSpace.
+	    ].
+
+	    (grpDivSz notNil and:[self hasGroupDividerAt:anIndex]) ifTrue:[
+		isVert ifTrue:[y := y + grpDivSz]
+		      ifFalse:[x := x + grpDivSz]
+	    ]
+	] 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)].
-        ]
+	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.
@@ -1951,36 +1951,36 @@
     end   := items size.
 
     mustRearrange ifTrue:[
-        self isPopUpView not ifTrue:[
-            explicitExtent := true
-        ].
-        self rearrangeItems.
-        start := 1
+	self isPopUpView not ifTrue:[
+	    explicitExtent := true
+	].
+	self rearrangeItems.
+	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 ~~ 1 and:[self hasGroupDividerAt:(start-1)]) ifTrue:[
-            start := start - 1
-        ]
+	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 ~~ 1 and:[self hasGroupDividerAt:(start-1)]) ifTrue:[
+	    start := start - 1
+	]
     ].
 
     (     self hasGroupDividers
      and:[self showGroupDivider
      and:[self isFitPanel not]]
     ) ifTrue:[
-        lnSz := groupDividerSize // 2
+	lnSz := groupDividerSize // 2
     ].
 
     end == 0 ifTrue:[^ self ].
@@ -1993,37 +1993,37 @@
     device setClipX:x y:y width:w height:h in:drawableId gc:gcId.
 
     start to:end do:[:i|
-        item := items at:i.
-        item redraw.
-
-        (lnSz notNil and:[self hasGroupDividerAt:i]) ifTrue:[
-            layout := item layout.
-
-            isVrt ifTrue:[
-                x1 := layout left  + hrzInset.
-                x2 := layout right - hrzInset.
-                y1 := (layout bottom) + lnSz.
-                y2 := y1.
-            ] ifFalse:[
-                x1 := (layout right) + lnSz.
-                x2 := x1.
-                y1 := layout top.
-                y2 := layout bottom.
-            ].
-            self paint:(self 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 displayLineFromX:x1 y:y1 toX:x2 y:y2
-        ]
+	item := items at:i.
+	item redraw.
+
+	(lnSz notNil and:[self hasGroupDividerAt:i]) ifTrue:[
+	    layout := item layout.
+
+	    isVrt ifTrue:[
+		x1 := layout left  + hrzInset.
+		x2 := layout right - hrzInset.
+		y1 := (layout bottom) + lnSz.
+		y2 := y1.
+	    ] ifFalse:[
+		x1 := (layout right) + lnSz.
+		x2 := x1.
+		y1 := layout top.
+		y2 := layout bottom.
+	    ].
+	    self paint:(self 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 displayLineFromX:x1 y:y1 toX:x2 y:y2
+	]
     ].
 
     clipRect := nil.
     prevClipArea isNil ifTrue:[device noClipIn:drawableId  gc:gcId]
-                      ifFalse:[self clippingRectangle:prevClipArea].
+		      ifFalse:[self clippingRectangle:prevClipArea].
 
 
 
@@ -2077,21 +2077,21 @@
     i := self findFirst:[:el|(el nameKey = something) or: [el = something]].
 
     i ~~ 0 ifTrue:[
-        ^ i
+	^ i
     ].
 
     something isSymbol ifTrue:[
-        i := self findFirst:[:el|
-            v := el value.
-            v isSymbol and:[v == something]
-        ].
-        i ~~ 0 ifTrue:[
-            ^ i
-        ]
+	i := self findFirst:[:el|
+	    v := el value.
+	    v isSymbol and:[v == something]
+	].
+	i ~~ 0 ifTrue:[
+	    ^ i
+	]
     ].
 
     (something respondsTo:#string) ifTrue:[
-        v := something string.
+	v := something string.
       ^ self findFirst:[:el|el textLabel = v].
     ].
   ^ 0
@@ -2120,47 +2120,47 @@
     (    (sensor := self sensor) notNil
      and:[sensor hasButtonMotionEventFor:nil]
     ) ifTrue:[
-        ^ self
+	^ self
     ].
 
     sensor anyButtonPressed ifFalse:[
-        "/ TODO: remember item over which pointer is
-        "/ (for enteredFG/enteredBG/enteredLevel handling)
+	"/ TODO: remember item over which pointer is
+	"/ (for enteredFG/enteredBG/enteredLevel handling)
 
         
-        (buttonEnteredBgColor ~= ButtonPassiveBackgroundColor
-        or:[ButtonEnteredLevel ~~ ButtonPassiveLevel]) ifTrue:[
-            (self containsPointX:x y:y) ifTrue:[
-                ((sel := self itemAtX:x y:y) notNil 
-                and:[sel isButton 
-                and:[superMenu isNil
-                and:[sel canSelect]]]) ifTrue:[
-                    self itemEntered:sel.
-                ] ifFalse:[
-                    self itemEntered:nil
-                ]
-            ].
-        ].
-        ^ self
+	(buttonEnteredBgColor ~= ButtonPassiveBackgroundColor
+	or:[ButtonEnteredLevel ~~ ButtonPassiveLevel]) ifTrue:[
+	    (self containsPointX:x y:y) ifTrue:[
+		((sel := self itemAtX:x y:y) notNil 
+		and:[sel isButton 
+		and:[superMenu isNil
+		and:[sel canSelect]]]) ifTrue:[
+		    self itemEntered:sel.
+		] ifFalse:[
+		    self itemEntered:nil
+		]
+	    ].
+	].
+	^ self
     ].
 
     "/ ok, a button is pressed.
     (buttonEnteredBgColor ~= ButtonPassiveBackgroundColor
     or:[ButtonEnteredLevel ~~ ButtonPassiveLevel]) ifTrue:[
-        self itemEntered:nil.
+	self itemEntered:nil.
     ].
 
     lastButtonSelected notNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     (self containsPointX:x y:y) ifTrue:[
-        ((sel := self itemAtX:x y:y) notNil and:[sel isButton and:[superMenu isNil]]) ifTrue:[
-            sel canSelect ifTrue:[
-                lastButtonSelected := sel
-            ]
-        ].
-        ^ self selection:sel
+	((sel := self itemAtX:x y:y) notNil and:[sel isButton and:[superMenu isNil]]) ifTrue:[
+	    sel canSelect ifTrue:[
+		lastButtonSelected := sel
+	    ]
+	].
+	^ self selection:sel
     ].
 
     menu := self superMenuAtX:x y:y.
@@ -2182,10 +2182,10 @@
     menu := self superMenuAtX:x y:y.
 
     menu isNil ifTrue:[
-        menu := self topMenu.
+	menu := self topMenu.
     ] ifFalse:[
-        point := self translatePoint:(x@y) to:menu.
-        item  := menu itemAtX:(point x) y:(point y)
+	point := self translatePoint:(x@y) to:menu.
+	item  := menu itemAtX:(point x) y:(point y)
     ].
     menu selection:item
 !
@@ -2200,24 +2200,24 @@
     (    menu hasSelection
      or:[menu isPopUpView not
      or:[(OperatingSystem millisecondTimeDeltaBetween:(Time millisecondClockValue)
-                                and:(menu mapTime)) > 200]]
+				and:(menu mapTime)) > 200]]
     ) ifTrue:[
-        item := nil.
-
-        (     (menu := self superMenuAtX:x y:y) notNil
-         and:[(item := menu selection) notNil
-         and:[item submenu notNil]]
-        ) ifTrue:[
-            menu selection:nil
-        ] ifFalse:[
-            (    lastButtonSelected isNil
-             or:[item isNil
-             or:[(menu itemAtX:x y:y) == lastButtonSelected]]
-            ) ifFalse:[
-                item := nil
-            ].
-            self topMenu accept:item
-        ]
+	item := nil.
+
+	(     (menu := self superMenuAtX:x y:y) notNil
+	 and:[(item := menu selection) notNil
+	 and:[item submenu notNil]]
+	) ifTrue:[
+	    menu selection:nil
+	] ifFalse:[
+	    (    lastButtonSelected isNil
+	     or:[item isNil
+	     or:[(menu itemAtX:x y:y) == lastButtonSelected]]
+	    ) ifFalse:[
+		item := nil
+	    ].
+	    self topMenu accept:item
+	]
     ].
 
     "Modified: / 27.2.1998 / 17:41:23 / cg"
@@ -2232,25 +2232,25 @@
      first "{ Class:SmallInteger }"
     |
     (self hasSelection not and:[superMenu notNil]) ifTrue:[
-        ^ superMenu cursorPressed:aKey
+	^ superMenu cursorPressed: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 ].
@@ -2260,19 +2260,19 @@
     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
 !
@@ -2286,10 +2286,10 @@
     enteredItem := anItem.
 
     prevEnteredItem notNil ifTrue:[
-        prevEnteredItem redraw
+	prevEnteredItem redraw
     ].
     enteredItem notNil ifTrue:[
-        enteredItem redraw
+	enteredItem redraw
     ].
 
     "Created: / 20.8.1998 / 13:18:23 / cg"
@@ -2304,38 +2304,38 @@
     menu := self.
 
     [ menu shown ] whileFalse:[
-        (menu := superMenu) isNil ifTrue:[^ self]
+	(menu := superMenu) isNil ifTrue:[^ self]
     ].
 
     key == #Return ifTrue:[
-        ^ menu accept
+	^ menu accept
     ].
 
     (     key == #CursorDown or:[key == #CursorUp
       or:[key == #CursorLeft or:[key == #CursorRight]]]
     ) ifTrue:[
-        ^ menu cursorPressed:key
+	^ menu cursorPressed:key
     ].
 
     rawKey := device keyboardMap keyAtValue:key ifAbsent:key.
 
     listOfItems := self selectItemsForShortcutKey:rawKey.
     listOfItems isNil ifTrue:[
-        listOfItems := self selectItemsForShortcutKey:key.
+	listOfItems := self selectItemsForShortcutKey:key.
     ].
     listOfItems notNil ifTrue:[
-        item := listOfItems first.
-
-        item hasSubmenu ifFalse:[
-            ^ menu accept:item
-        ].
-        ^ self openMenusFromItems:listOfItems
+	item := listOfItems first.
+
+	item hasSubmenu ifFalse:[
+	    ^ menu accept:item
+	].
+	^ self openMenusFromItems:listOfItems
     ].
 
     (self hasSelection not and:[superMenu notNil]) ifTrue:[
-        (superMenu containsPoint:(self translatePoint:(x@y) to:superMenu)) ifTrue:[
-            menu := superMenu
-        ]
+	(superMenu containsPoint:(self translatePoint:(x@y) to:superMenu)) ifTrue:[
+	    menu := superMenu
+	]
     ].
 
     cIdx := menu selectionIndex.
@@ -2345,39 +2345,39 @@
     lowerKey := key asLowercase.
 
     menu keysAndValuesDo:[:anIndex :el| |c l|
-        (el canSelect and:[(l := el textLabel) notNil]) ifTrue:[
-            l size ~~ 0 ifTrue:[
-                (c := el accessCharacter) notNil ifTrue:[
-                    (c == upperKey or:[c == lowerKey]) ifTrue:[
-                        ^ menu selection:el
-                    ]
-                ] ifFalse:[
-                    ((c := l first) == upperKey or:[c == lowerKey]) ifTrue:[
-                        anIndex > cIdx ifTrue:[
-                            ^ menu selection:el
-                        ] ifFalse:[
-                            idx isNil ifTrue:[
-                                idx := anIndex
-                            ] ifFalse:[
-                                anIndex > idx ifTrue:[
-                                    anIndex ~~ cIdx ifTrue:[
-                                        idx := anIndex
-                                    ]
-                                ]
-                            ]
-                        ]
+	(el canSelect and:[(l := el textLabel) notNil]) ifTrue:[
+	    l size ~~ 0 ifTrue:[
+		(c := el accessCharacter) notNil ifTrue:[
+		    (c == upperKey or:[c == lowerKey]) ifTrue:[
+			^ menu selection:el
+		    ]
+		] ifFalse:[
+		    ((c := l first) == upperKey or:[c == lowerKey]) ifTrue:[
+			anIndex > cIdx ifTrue:[
+			    ^ menu selection:el
+			] ifFalse:[
+			    idx isNil ifTrue:[
+				idx := anIndex
+			    ] ifFalse:[
+				anIndex > idx ifTrue:[
+				    anIndex ~~ cIdx ifTrue:[
+					idx := anIndex
+				    ]
+				]
+			    ]
+			]
                         
-                    ]
-                ]
-            ]
-        ]
+		    ]
+		]
+	    ]
+	]
     ].
     (item := menu itemAt:idx) isNil ifTrue:[
-        menu hasSelection ifFalse:[
-            (menu := menu superMenu) isNil ifTrue:[
-                ^ super keyPress:key x:x y:y
-            ]
-        ]
+	menu hasSelection ifFalse:[
+	    (menu := menu superMenu) isNil ifTrue:[
+		^ super keyPress:key x:x y:y
+	    ]
+	]
     ].
     menu selection:item.
 
@@ -2393,7 +2393,7 @@
 
 sizeChanged:how
     self isFitPanel ifTrue:[
-        self mustRearrange.
+	self mustRearrange.
     ].
     super sizeChanged:how
 ! !
@@ -2408,11 +2408,11 @@
     device ungrabPointer.
 
     (sensor := self sensor) notNil ifTrue:[
-        "/ make certain all X events have been received
-        device sync.
-        "/ now all events have been received.
-        "/ now, flush all pointer events
-        sensor flushKeyboardFor:nil
+	"/ make certain all X events have been received
+	device sync.
+	"/ now all events have been received.
+	"/ now, flush all pointer events
+	sensor flushKeyboardFor:nil
     ].
     device ungrabKeyboard.
 
@@ -2426,34 +2426,34 @@
     |sensor|
 
     realized ifTrue:[
-        sensor := self sensor.
-
-        device activePointerGrab ~~ self ifTrue:[
-            sensor notNil ifTrue:[
-                sensor flushMotionEventsFor:nil.
-            ].
-
-            (device grabPointerInView:self) ifFalse:[
-                Delay waitForSeconds:0.1.
-                (device grabPointerInView:self) ifFalse:[
-                    "give up"
-                    'MenuPanel [warning]: could not grab pointer' errorPrintCR.
-                    self unmap
-                ]
-            ]
-        ].
-
-        device activeKeyboardGrab ~~ self ifTrue:[
-            sensor notNil ifTrue:[
-                device sync.
-                sensor flushKeyboardFor:nil
-            ].
-            device grabKeyboardInView:self.
-
-            superMenu notNil ifTrue:[
-                self getKeyboardFocus
-            ]
-        ]
+	sensor := self sensor.
+
+	device activePointerGrab ~~ self ifTrue:[
+	    sensor notNil ifTrue:[
+		sensor flushMotionEventsFor:nil.
+	    ].
+
+	    (device grabPointerInView:self) ifFalse:[
+		Delay waitForSeconds:0.1.
+		(device grabPointerInView:self) ifFalse:[
+		    "give up"
+		    'MenuPanel [warning]: could not grab pointer' errorPrintCR.
+		    self unmap
+		]
+	    ]
+	].
+
+	device activeKeyboardGrab ~~ self ifTrue:[
+	    sensor notNil ifTrue:[
+		device sync.
+		sensor flushKeyboardFor:nil
+	    ].
+	    device grabKeyboardInView:self.
+
+	    superMenu notNil ifTrue:[
+		self getKeyboardFocus
+	    ]
+	]
     ]
 
     "Modified: / 2.2.1998 / 23:43:59 / stefan"
@@ -2465,18 +2465,18 @@
     |sensor|
 
     device activePointerGrab == self ifTrue:[
-        device ungrabPointer.
+	device ungrabPointer.
     ].
     device activeKeyboardGrab == self ifTrue:[
-        sensor := self sensor.
-        sensor notNil ifTrue:[
-            "/ make certain all X events have been received
-            device sync.
-            "/ now all events have been received.
-            "/ now, flush all pointer events
-            sensor flushKeyboardFor:self
-        ].
-        device ungrabKeyboard.
+	sensor := self sensor.
+	sensor notNil ifTrue:[
+	    "/ make certain all X events have been received
+	    device sync.
+	    "/ now all events have been received.
+	    "/ now, flush all pointer events
+	    sensor flushKeyboardFor:self
+	].
+	device ungrabKeyboard.
     ].
 
     "Modified: / 2.2.1998 / 10:27:12 / stefan"
@@ -2510,29 +2510,29 @@
     |style|
 
     self isPopUpView ifTrue:[
-        style := styleSheet name.
-
-        (style ~~ #normal and:[style ~~ #mswindows]) ifTrue:[
-            self borderWidth:1.
-        ]
+	style := styleSheet name.
+
+	(style ~~ #normal and:[style ~~ #mswindows]) ifTrue:[
+	    self borderWidth:1.
+	]
     ].
 
     super create.
 
     self isPopUpView ifTrue:[
-        (PopUpView styleSheet at:'popup.shadow' default:false) ifTrue:[
-            shadowView isNil ifTrue:[
-                shadowView := (ShadowView onDevice:device) for:self
-            ] ifFalse:[
-                self saveUnder:true.
-            ].
-        ]
+	(PopUpView styleSheet at:'popup.shadow' default:false) ifTrue:[
+	    shadowView isNil ifTrue:[
+		shadowView := (ShadowView onDevice:device) for:self
+	    ] ifFalse:[
+		self saveUnder:true.
+	    ].
+	]
     ] ifFalse:[
-        explicitExtent == true ifTrue:[
-            (self width) == (superView width) ifTrue:[
-                self verticalLayout:false
-            ]
-        ]
+	explicitExtent == true ifTrue:[
+	    (self width) == (superView width) ifTrue:[
+		self verticalLayout:false
+	    ]
+	]
     ]
 
     "Modified: / 28.7.1998 / 02:11:44 / cg"
@@ -2568,54 +2568,54 @@
     "/ (i.e. read menu.buttonActiveLevel & menu.buttonPassiveLevel)
 
     self isPopUpView ifFalse:[
-        (style == #motif or:[style == #iris]) ifTrue:[
-            self topView == self superView ifTrue:[
-                self level:2
-            ]
-        ]
+	(style == #motif or:[style == #iris]) ifTrue:[
+	    self topView == self superView ifTrue:[
+		self level:2
+	    ]
+	]
     ] ifTrue:[
-        (style == #next or:[style == #normal]) ifTrue:[
-            onLevel := offLevel := 0
-        ] ifFalse:[
-            style == #openwin ifTrue:[
-                offLevel := 0.
-            ]
-        ]
+	(style == #next or:[style == #normal]) ifTrue:[
+	    onLevel := offLevel := 0
+	] ifFalse:[
+	    style == #openwin ifTrue:[
+		offLevel := 0.
+	    ]
+	]
     ].
 
     superMenu isNil ifTrue:[
-        fgColor                   := DefaultForegroundColor         onDevice:device.
-        activeBgColor             := DefaultHilightBackgroundColor  onDevice:device.
-        activeFgColor             := DefaultHilightForegroundColor  onDevice:device.
-        disabledFgColor           := DefaultDisabledForegroundColor onDevice:device.
-        rightArrow                := RightArrowForm                 onDevice:device.
-        selectionFrameBrightColor := SelectionFrameBrightColor      onDevice:device.
-        selectionFrameDarkColor   := SelectionFrameDarkColor        onDevice:device.
-        buttonLightColor          := ButtonLightColor               onDevice:device.
-        buttonShadowColor         := ButtonShadowColor              onDevice:device.
-        ButtonHalfLightColor notNil ifTrue: [
-            buttonHalfLightColor      := ButtonHalfLightColor           onDevice:device].
-        ButtonHalfShadowColor notNil ifTrue: [
-            buttonHalfShadowColor     := ButtonHalfShadowColor          onDevice:device].
-        buttonEnteredBgColor      := ButtonEnteredBackgroundColor   onDevice:device.
-
-        (rightArrowShadow := RightArrowShadowForm) notNil ifTrue:[
-            rightArrowShadow := rightArrowShadow onDevice:device
-        ]
+	fgColor                   := DefaultForegroundColor         onDevice:device.
+	activeBgColor             := DefaultHilightBackgroundColor  onDevice:device.
+	activeFgColor             := DefaultHilightForegroundColor  onDevice:device.
+	disabledFgColor           := DefaultDisabledForegroundColor onDevice:device.
+	rightArrow                := RightArrowForm                 onDevice:device.
+	selectionFrameBrightColor := SelectionFrameBrightColor      onDevice:device.
+	selectionFrameDarkColor   := SelectionFrameDarkColor        onDevice:device.
+	buttonLightColor          := ButtonLightColor               onDevice:device.
+	buttonShadowColor         := ButtonShadowColor              onDevice:device.
+	ButtonHalfLightColor notNil ifTrue: [
+	    buttonHalfLightColor      := ButtonHalfLightColor           onDevice:device].
+	ButtonHalfShadowColor notNil ifTrue: [
+	    buttonHalfShadowColor     := ButtonHalfShadowColor          onDevice:device].
+	buttonEnteredBgColor      := ButtonEnteredBackgroundColor   onDevice:device.
+
+	(rightArrowShadow := RightArrowShadowForm) notNil ifTrue:[
+	    rightArrowShadow := rightArrowShadow onDevice:device
+	]
     ] ifFalse:[
-        fgColor                   := superMenu foregroundColor.
-        activeBgColor             := superMenu activeBackgroundColor.
-        activeFgColor             := superMenu activeForegroundColor.
-        disabledFgColor           := superMenu disabledForegroundColor.
-        rightArrow                := superMenu rightArrow.
-        rightArrowShadow          := superMenu rightArrowShadow.
-        selectionFrameBrightColor := superMenu selectionFrameBrightColor.
-        selectionFrameDarkColor   := superMenu selectionFrameDarkColor.
-        buttonLightColor          := superMenu buttonLightColor.
-        buttonShadowColor         := superMenu buttonShadowColor.
-        buttonHalfLightColor      := superMenu buttonHalfLightColor.
-        buttonHalfShadowColor     := superMenu buttonHalfShadowColor.
-        buttonEnteredBgColor      := superMenu buttonEnteredBackgroundColor.
+	fgColor                   := superMenu foregroundColor.
+	activeBgColor             := superMenu activeBackgroundColor.
+	activeFgColor             := superMenu activeForegroundColor.
+	disabledFgColor           := superMenu disabledForegroundColor.
+	rightArrow                := superMenu rightArrow.
+	rightArrowShadow          := superMenu rightArrowShadow.
+	selectionFrameBrightColor := superMenu selectionFrameBrightColor.
+	selectionFrameDarkColor   := superMenu selectionFrameDarkColor.
+	buttonLightColor          := superMenu buttonLightColor.
+	buttonShadowColor         := superMenu buttonShadowColor.
+	buttonHalfLightColor      := superMenu buttonHalfLightColor.
+	buttonHalfShadowColor     := superMenu buttonHalfShadowColor.
+	buttonEnteredBgColor      := superMenu buttonEnteredBackgroundColor.
     ].
 
     "Modified: / 20.8.1998 / 15:51:17 / cg"
@@ -2628,6 +2628,8 @@
 
     super initStyle.
 
+    self viewBackground:DefaultBackgroundColor.
+
     onLevel   := DefaultHilightLevel.
     offLevel  := DefaultLevel.
     itemSpace := DefaultItemSpace.
@@ -2640,8 +2642,10 @@
 "/    style == #st80 ifTrue:[
 "/        self level:0
 "/    ] ifFalse:[
-        self level:1.
+	self level:1.
 "/    ].
+
+    "Modified: / 5.9.1998 / 18:16:57 / cg"
 !
 
 initialize
@@ -2680,16 +2684,16 @@
     anItemList := InitialSelectionQuerySignal raise.
 
     self isPopUpView ifTrue:[
-        self grabMouseAndKeyboard
+	self grabMouseAndKeyboard
     ] ifFalse:[
 "/        styleSheet is3D ifTrue:[self borderWidth:0].
-        super viewBackground:(self backgroundColor).
+	super viewBackground:(self backgroundColor).
     ].
     self do:[:el| el updateIndicators ].
 
     anItemList size > 0 ifTrue:[
-        self redrawX:0 y:0 width:10000 height:10000.
-        self openMenusFromItems:anItemList.
+	self redrawX:0 y:0 width:10000 height:10000.
+	self openMenusFromItems:anItemList.
     ].
 
     "Modified: / 2.2.1998 / 09:27:21 / stefan"
@@ -2701,18 +2705,18 @@
     "
 
     self isPopUpView ifTrue:[
-        "Because of #saveUnder of ShadowView the order of realize is significant:
-         shadowView must be realized before self"
-        self hiddenOnRealize:true.
-        super realize.
-        self resize.
-        shadowView notNil ifTrue:[
-            shadowView realize.
-        ].
-        super map.
-        self raise.
+	"Because of #saveUnder of ShadowView the order of realize is significant:
+	 shadowView must be realized before self"
+	self hiddenOnRealize:true.
+	super realize.
+	self resize.
+	shadowView notNil ifTrue:[
+	    shadowView realize.
+	].
+	super map.
+	self raise.
     ] ifFalse:[
-        super realize.
+	super realize.
     ]
 !
 
@@ -2739,9 +2743,9 @@
     "/
     (superMenu notNil and:[superMenu shown and:[superMenu isPopUpView 
      or:[superMenu sensor anyButtonPressed]]]) ifTrue:[
-        superMenu grabMouseAndKeyboard
+	superMenu grabMouseAndKeyboard
     ] ifFalse:[
-        self ungrabMouseAndKeyboard.
+	self ungrabMouseAndKeyboard.
     ].
     super unmap.
     shadowView notNil ifTrue:[shadowView unmap].
@@ -2780,7 +2784,7 @@
     top := self.
 
     [ top superMenu notNil ] whileTrue:[
-        top := top superMenu
+	top := top superMenu
     ].
   ^ top
 
@@ -2797,8 +2801,8 @@
     string := 'Menu:'.
 
     self do:[:anItem|
-        label  := anItem label ? ''.
-        string := string ,' ', label printString.
+	label  := anItem label ? ''.
+	string := string ,' ', label printString.
     ].
     ^ string
 
@@ -2811,12 +2815,12 @@
     |appl|
 
     superMenu notNil ifTrue:[
-        ^ superMenu application
+	^ superMenu application
     ].
     (appl := super application) isNil ifTrue:[
-        windowGroup notNil ifTrue:[
-            appl := windowGroup mainGroup topViews first application
-        ]
+	windowGroup notNil ifTrue:[
+	    appl := windowGroup mainGroup topViews first application
+	]
     ].
   ^ appl
 !
@@ -2835,10 +2839,10 @@
      current stored value, true is returned otherwise false
     "
     (self menuAdornmentAt:aSymbol) == something ifTrue:[
-        ^ false
+	^ false
     ].
     adornment isNil ifTrue:[
-        adornment := DefaultAdornment copy
+	adornment := DefaultAdornment copy
     ].
     adornment at:aSymbol put:something.
   ^ true
@@ -2848,13 +2852,13 @@
     "on each item perform selector with an argument derived from aList
     "
     aList isCollection ifTrue:[
-        items size >= aList size ifTrue:[
-            aList keysAndValuesDo:[:anIndex :anArg|
-                (items at:anIndex) perform:aSelector with:anArg
-            ]
-        ]
+	items size >= aList size ifTrue:[
+	    aList keysAndValuesDo:[:anIndex :anArg|
+		(items at:anIndex) perform:aSelector with:anArg
+	    ]
+	]
     ] ifFalse:[
-        self do:[:anItem| anItem perform:aSelector with:aList ]
+	self do:[:anItem| anItem perform:aSelector with:aList ]
     ]
 
 
@@ -2866,16 +2870,16 @@
     |item|
 
     (anItemList isNil or:[anItemList isEmpty]) ifTrue:[
-        ^ self
+	^ self
     ].
     item := anItemList removeLast.
 
     item enabled ifFalse:[
-        ^ self
+	^ self
     ].
 
     InitialSelectionQuerySignal answer:anItemList do:[
-        self selection:item
+	self selection:item
     ]
 !
 
@@ -2887,19 +2891,19 @@
     |seq|
 
     self do:[:anItem|
-        anItem isEnabled ifTrue:[
-            anItem shortcutKey = aKey ifTrue:[
-                seq := OrderedCollection new.
-            ] ifFalse:[
-                anItem hasSubmenu ifTrue:[
-                    seq := anItem submenu selectItemsForShortcutKey:aKey
-                ]
-            ].
-            seq notNil ifTrue:[
-                seq add:anItem.
-              ^ seq
-            ]
-        ]
+	anItem isEnabled ifTrue:[
+	    anItem shortcutKey = aKey ifTrue:[
+		seq := OrderedCollection new.
+	    ] ifFalse:[
+		anItem hasSubmenu ifTrue:[
+		    seq := anItem submenu selectItemsForShortcutKey:aKey
+		]
+	    ].
+	    seq notNil ifTrue:[
+		seq add:anItem.
+	      ^ seq
+	    ]
+	]
     ].
   ^ nil
         
@@ -2909,7 +2913,7 @@
     "translate a point into a views point; in case of no view nil is returned
     "
     aView notNil ifTrue:[
-        aView == self ifTrue:[^ aPoint].
+	aView == self ifTrue:[^ aPoint].
       ^ device translatePoint:aPoint from:(self id) to:(aView id)
     ].
   ^ nil
@@ -2951,7 +2955,7 @@
     top := self topMenu.
 
     top activeMenu == self ifTrue:[
-        top activeMenu:nil
+	top activeMenu:nil
     ]
 
     "Created: / 27.2.1998 / 17:41:17 / cg"
@@ -2983,9 +2987,9 @@
     menu := self.
 
     [ (menu := menu superMenu) notNil ] whileTrue:[
-        (menu containsPoint:(self translatePoint:(x@y) to:menu)) ifTrue:[
-            ^ menu
-        ]
+	(menu containsPoint:(self translatePoint:(x@y) to:menu)) ifTrue:[
+	    ^ menu
+	]
     ].
   ^ nil
 ! !
@@ -3026,13 +3030,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
 
@@ -3093,9 +3097,9 @@
     |item|
 
     enabled ifTrue:[
-        (item := self itemAt:something) notNil ifTrue:[
-            ^ item canSelect
-        ]
+	(item := self itemAt:something) notNil ifTrue:[
+	    ^ item canSelect
+	]
     ].
   ^ false
 !
@@ -3114,21 +3118,21 @@
     |item newSel hlp|
 
     selection isNumber ifTrue:[
-        newSel := self itemAt:anItemOrNil
+	newSel := self itemAt:anItemOrNil
     ] ifFalse:[
-        (anItemOrNil notNil and:[anItemOrNil canSelect]) ifTrue:[
-            newSel := anItemOrNil
-        ]
+	(anItemOrNil notNil and:[anItemOrNil canSelect]) ifTrue:[
+	    newSel := anItemOrNil
+	]
     ].
 
     selection == newSel ifTrue:[^ self].
 
     (item := selection) notNil ifTrue:[
-        selection := nil.
-        item selected:false.
+	selection := nil.
+	item selected:false.
     ].
     newSel notNil ifTrue:[
-        selection := newSel.
+	selection := newSel.
 
 "/ cg: thats rubbish - it will show help for my first item,
 "/ but not the selected one ...
@@ -3136,7 +3140,7 @@
 "/            hlp := ActiveHelp currentHelpListener.
 "/            hlp initiateHelpFor:self atX:1 y:1 now:true.
 "/        ].
-        selection selected:true.
+	selection selected:true.
     ].
 
     "Modified: / 2.2.1998 / 10:13:46 / stefan"
@@ -3149,7 +3153,7 @@
     |item|
 
     (item := self selection) notNil ifTrue:[
-        ^ self findFirst:[:el| el == item ]
+	^ self findFirst:[:el| el == item ]
     ].
     ^ 0
 
@@ -3223,8 +3227,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'MenuPanel::Item checkOffIcon'
-        ifAbsentPut:[(Depth2Image new) width: 15; height: 15; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@AUP@@E@AP@DO?Y@D_?>(AO??;AO???LS???3D???<1O???LS???3A_??3@Z??<0A+?00@C@C0@@O?@@') ; colorMapFromArray:#[0 0 0 85 85 85 170 170 170 255 255 255]; mask:((Depth1Image new) width: 15; height: 15; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A<@_<C?8_?1??O?:??+?>/?:??)?=G?4O< HL@_@') ; yourself); yourself]!
+	constantNamed:#'MenuPanel::Item checkOffIcon'
+	ifAbsentPut:[(Depth2Image new) width: 15; height: 15; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@AUP@@E@AP@DO?Y@D_?>(AO??;AO???LS???3D???<1O???LS???3A_??3@Z??<0A+?00@C@C0@@O?@@') ; colorMapFromArray:#[0 0 0 85 85 85 170 170 170 255 255 255]; mask:((Depth1Image new) width: 15; height: 15; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A<@_<C?8_?1??O?:??+?>/?:??)?=G?4O< HL@_@') ; yourself); yourself]!
 
 checkOnIcon
     "This resource specification was automatically generated
@@ -3241,8 +3245,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'MenuPanel::Item checkOnIcon'
-        ifAbsentPut:[(Depth2Image new) width: 15; height: 15; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@AUP@@E@AP@DO?Y@D]@^(AL@@;AM@@GLS@@@3D0@@L1L@@CLSP@A3A\@@3@Z4A<0A+?00@C@C0@@O?@@') ; colorMapFromArray:#[0 0 0 85 85 85 170 170 170 255 255 255]; mask:((Depth1Image new) width: 15; height: 15; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A<@_<C?8_?1??O?:??+?>/?:??)?=G?4O< HL@_@') ; yourself); yourself]!
+	constantNamed:#'MenuPanel::Item checkOnIcon'
+	ifAbsentPut:[(Depth2Image new) width: 15; height: 15; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@AUP@@E@AP@DO?Y@D]@^(AL@@;AM@@GLS@@@3D0@@L1L@@CLSP@A3A\@@3@Z4A<0A+?00@C@C0@@O?@@') ; colorMapFromArray:#[0 0 0 85 85 85 170 170 170 255 255 255]; mask:((Depth1Image new) width: 15; height: 15; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'A<@_<C?8_?1??O?:??+?>/?:??)?=G?4O< HL@_@') ; yourself); yourself]!
 
 checkedImage
     "This resource specification was automatically generated
@@ -3259,8 +3263,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'MenuPanel::Item checkedImage'
-        ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'*****X@@@@FEUUUQ!!UUTDXUUVAFEUUBQ!!UU TXPUP%FDAXEQ!!0DITXW@AUFE\BUQ!!U0UTXUUUUF@@@@AUUUUUP@a') ; colorMapFromArray:#[0 0 0 255 255 255 127 127 127 170 170 170]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????_?=??7??_?=??7??_?=??7??_?=??7??X@A??<b') ; yourself); yourself]!
+	constantNamed:#'MenuPanel::Item checkedImage'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'*****X@@@@FEUUUQ!!UUTDXUUVAFEUUBQ!!UU TXPUP%FDAXEQ!!0DITXW@AUFE\BUQ!!U0UTXUUUUF@@@@AUUUUUP@a') ; colorMapFromArray:#[0 0 0 255 255 255 127 127 127 170 170 170]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????_?=??7??_?=??7??_?=??7??_?=??7??X@A??<b') ; yourself); yourself]!
 
 uncheckedImage
     "This resource specification was automatically generated
@@ -3277,8 +3281,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'MenuPanel::Item uncheckedImage'
-        ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUUUUG????10@@@L\@@@CG@@@@10@@@L\@@@CG@@@@10@@@L\@@@CG@@@@10@@@L\@@@CG@@@@1????<@@@@@@@a') ; colorMapFromArray:#[255 255 255 127 127 127 170 170 170 0 0 0]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????_?=??7??_?=??7??_?=??7??_?=??7??X@A??<b') ; yourself); yourself]! !
+	constantNamed:#'MenuPanel::Item uncheckedImage'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUUUUG????10@@@L\@@@CG@@@@10@@@L\@@@CG@@@@10@@@L\@@@CG@@@@10@@@L\@@@CG@@@@1????<@@@@@@@a') ; colorMapFromArray:#[255 255 255 127 127 127 170 170 170 0 0 0]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????_?=??7??_?=??7??_?=??7??_?=??7??X@A??<b') ; yourself); yourself]! !
 
 !MenuPanel::Item class methodsFor:'instance creation'!
 
@@ -3316,14 +3320,14 @@
     |arg|
 
     self hasIndication ifTrue:[    
-        arg := self indicationValue not.
-        self indicationValue:arg.
+	arg := self indicationValue not.
+	self indicationValue:arg.
     ] ifFalse:[
-        self hasChoice ifTrue:[
-            arg := self choiceValue.
-            self choice value:arg.
-            arg := true.
-        ]
+	self hasChoice ifTrue:[
+	    arg := self choiceValue.
+	    self choice value:arg.
+	    arg := true.
+	]
     ].
     ^ arg
 
@@ -3336,7 +3340,7 @@
     "returns my accessCharacter or nil
     "
     accessCharacterPosition isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
   ^ (rawLabel string) at:accessCharacterPosition ifAbsent:nil
 !
@@ -3351,8 +3355,8 @@
     "set the access character position or nil
     "
     accessCharacterPosition ~~ anIndex ifTrue:[
-        accessCharacterPosition := anIndex.
-        self updateRawLabel.
+	accessCharacterPosition := anIndex.
+	self updateRawLabel.
     ].
 !
 
@@ -3375,7 +3379,7 @@
     "sets the argument
     "
     self argument ~~ anArgument ifTrue:[
-        self adornment argument:anArgument.
+	self adornment argument:anArgument.
     ]
 !
 
@@ -3402,19 +3406,19 @@
     label := aLabel value.
 
     (label isString and:[(s := label size) > 1]) ifTrue:[
-        i := 1.
-
-        [((i := label indexOf:$& startingAt:i) ~~ 0 
-        and:[i < s])] whileTrue:[
-            rest := label copyFrom:(i+1).
-
-            i == 1 ifTrue:[label := rest]
-                  ifFalse:[label := (label copyFrom:1 to:(i-1)), rest].
-
-            (label at:i) == $& ifTrue:[i := i + 1]
-                              ifFalse:[accessCharacterPosition := i].
-            s := s - 1.
-        ]
+	i := 1.
+
+	[((i := label indexOf:$& startingAt:i) ~~ 0 
+	and:[i < s])] whileTrue:[
+	    rest := label copyFrom:(i+1).
+
+	    i == 1 ifTrue:[label := rest]
+		  ifFalse:[label := (label copyFrom:1 to:(i-1)), rest].
+
+	    (label at:i) == $& ifTrue:[i := i + 1]
+			      ifFalse:[accessCharacterPosition := i].
+	    s := s - 1.
+	]
     ].
 
     self updateRawLabel
@@ -3459,8 +3463,8 @@
      no submenu exists evaluate the action assigned to the item (accept).
     "
     self shortcutKey ~~ aKey ifTrue:[
-        self adornment shortcutKey:aKey.
-        self redraw.
+	self adornment shortcutKey:aKey.
+	self redraw.
     ].
 !
 
@@ -3476,9 +3480,9 @@
      at the moment only #right is implemented
     "
     (startGroup isNil or:[startGroup == #right]) ifTrue:[
-        startGroup := aSymbol
+	startGroup := aSymbol
     ] ifFalse:[
-        self warn:('not supported group: ', aSymbol printString ).
+	self warn:('not supported group: ', aSymbol printString ).
     ]
 
 !
@@ -3497,20 +3501,20 @@
 
     (aSubMenu notNil 
      and:[(aSubMenu isView or:[aSubMenu isKindOf:Menu]) not]) ifTrue:[
-        ^ self submenuChannel:aSubMenu
+	^ self submenuChannel:aSubMenu
     ].
 
     (subMenu := aSubMenu) notNil ifTrue:[
-        aSubMenu class == Menu ifTrue:[
-            subMenu := MenuPanel new.
-            menuPanel notNil ifTrue:[
-                subMenu receiver:menuPanel receiver.
-            ].
-            subMenu menu:aSubMenu
-        ].
-        (subMenu notNil and:[subMenu isView]) ifTrue:[
-            subMenu superMenu:menuPanel
-        ]
+	aSubMenu class == Menu ifTrue:[
+	    subMenu := MenuPanel new.
+	    menuPanel notNil ifTrue:[
+		subMenu receiver:menuPanel receiver.
+	    ].
+	    subMenu menu:aSubMenu
+	].
+	(subMenu notNil and:[subMenu isView]) ifTrue:[
+	    subMenu superMenu:menuPanel
+	]
     ].
 
     "Modified: / 10.8.1998 / 13:26:28 / cg"
@@ -3520,7 +3524,7 @@
     "returns my textLabel or nil if none text
     "
     (rawLabel respondsTo:#string) ifTrue:[
-        ^ rawLabel string
+	^ rawLabel string
     ].
   ^ nil
 !
@@ -3564,18 +3568,18 @@
     old == something ifTrue:[^ self].
 
     (self isKindOfValueHolder:old) ifTrue:[
-        old removeDependent:self
+	old removeDependent:self
     ].
 
     new := something.
     new isSymbol ifTrue:[
-        new := self aspectAt:new.
-        new isNil ifTrue:[
-            new := something
-        ]
+	new := self aspectAt:new.
+	new isNil ifTrue:[
+	    new := something
+	]
     ].
     (self isKindOfValueHolder:new) ifTrue:[
-        new addDependent:self
+	new addDependent:self
     ].
     self adornment choice:new.
     self updateRawLabel.
@@ -3610,19 +3614,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.
+
+	    (self isKindOfValueHolder:state) ifTrue:[
+		enableChannel := state.
+		enableChannel addDependent:self.
+		state := enableChannel value.
+	    ] ifFalse:[
+		state := state value
+	    ]
+	] ifFalse:[
+	    state := enableChannel value
+	].
       ^ state ~~ false
     ].
     ^ false
@@ -3634,32 +3638,32 @@
     |oldState newState|
 
     enableChannel isNil ifTrue:[
-        oldState := true
+	oldState := true
     ] ifFalse:[
-        oldState := enableChannel value.
-        (self isKindOfValueHolder:enableChannel) ifTrue:[
-            enableChannel removeDependent:self
-        ]
+	oldState := enableChannel value.
+	(self isKindOfValueHolder:enableChannel) ifTrue:[
+	    enableChannel removeDependent:self
+	]
     ].
     enableChannel := something.
 
     enableChannel isNil ifTrue:[
-        menuPanel shown ifFalse:[^ self].
-        newState := true
+	menuPanel shown ifFalse:[^ self].
+	newState := true
     ] ifFalse:[
-        (self isKindOfValueHolder:enableChannel) ifTrue:[
-            enableChannel addDependent:self
-        ] ifFalse:[
-            enableChannel isSymbol ifTrue:[^ self]
-        ].
-        menuPanel shown ifFalse:[^ self].
-        newState := enableChannel value.
+	(self isKindOfValueHolder:enableChannel) ifTrue:[
+	    enableChannel addDependent:self
+	] ifFalse:[
+	    enableChannel isSymbol ifTrue:[^ self]
+	].
+	menuPanel shown ifFalse:[^ self].
+	newState := enableChannel value.
     ].
 
     newState ~~ oldState ifTrue:[
-        (rawLabel notNil and:[menuPanel canDrawItem]) ifTrue:[
-            self drawLabel
-        ]
+	(rawLabel notNil and:[menuPanel canDrawItem]) ifTrue:[
+	    self drawLabel
+	]
     ]
 
     "Modified: / 27.10.1997 / 16:13:42 / cg"
@@ -3681,11 +3685,11 @@
     old == something ifTrue:[^ self].
 
     (self isKindOfValueHolder:old) ifTrue:[
-        old removeDependent:self
+	old removeDependent:self
     ].
 
     (self isKindOfValueHolder:something) ifTrue:[
-        something addDependent:self
+	something addDependent:self
     ].
     self adornment indication:something.
     self updateRawLabel.
@@ -3703,7 +3707,7 @@
     isButton := anBoolean.
 
     layout notNil ifTrue:[
-        self redrawAsButton
+	self redrawAsButton
     ]
 
 
@@ -3714,28 +3718,28 @@
     |appl recv subm|
 
     submenuChannel notNil ifTrue:[
-        submenuChannel isSymbol ifFalse:[
-            subm := submenuChannel
-        ] ifTrue:[
-            appl := menuPanel application.
-
-            (subm := self findSubMenuIn:appl) isNil ifTrue:[
-                (recv := menuPanel receiver) ~~ appl ifTrue:[
-                    subm := self findSubMenuIn:recv
-                ]
-            ]
-        ].
-
-        (subm := subm value) isArray ifTrue:[
-            subm := Menu new fromLiteralArrayEncoding:subm.
-            "/ cg: linked menus also may contain translations ...
-            subm notNil ifTrue:[
-                appl notNil ifTrue:[
-                    subm findGuiResourcesIn:appl.
-                ]                
-            ].
-        ].
-        self submenu:subm.
+	submenuChannel isSymbol ifFalse:[
+	    subm := submenuChannel
+	] ifTrue:[
+	    appl := menuPanel application.
+
+	    (subm := self findSubMenuIn:appl) isNil ifTrue:[
+		(recv := menuPanel receiver) ~~ appl ifTrue:[
+		    subm := self findSubMenuIn:recv
+		]
+	    ]
+	].
+
+	(subm := subm value) isArray ifTrue:[
+	    subm := Menu new fromLiteralArrayEncoding:subm.
+	    "/ cg: linked menus also may contain translations ...
+	    subm notNil ifTrue:[
+		appl notNil ifTrue:[
+		    subm findGuiResourcesIn:appl.
+		]                
+	    ].
+	].
+	self submenu:subm.
     ].
 
     ^ subMenu
@@ -3761,7 +3765,7 @@
     "gets height
     "
     layout isNil ifTrue:[
-        ^ self preferredExtent y
+	^ self preferredExtent y
     ].
     ^ layout height
 !
@@ -3796,7 +3800,7 @@
     "
 
     layout isNil ifTrue:[
-        ^ self preferredExtent x
+	^ self preferredExtent x
     ].
     ^ layout width
 ! !
@@ -3811,19 +3815,19 @@
     appl := menuPanel receiver.
 
     (appl isKindOf:ValueModel) ifTrue:[
-        ^ appl value:aKey
+	^ appl value:aKey
     ].
 
     (appl notNil or:[(appl := menuPanel application) notNil]) ifTrue:[
-        Object messageNotUnderstoodSignal handle:[:ex|
-            ex parameter selector == aKey ifFalse:[
-                ex reject
-            ].
-        ] do:[
-            (appl isKindOf:ApplicationModel) 
-                ifTrue:[value := appl aspectFor:aKey]
-                ifFalse:[value := appl perform:aKey]
-        ]
+	Object messageNotUnderstoodSignal handle:[:ex|
+	    ex parameter selector == aKey ifFalse:[
+		ex reject
+	    ].
+	] do:[
+	    (appl isKindOf:ApplicationModel) 
+		ifTrue:[value := appl aspectFor:aKey]
+		ifFalse:[value := appl perform:aKey]
+	]
     ].
     ^ value
 
@@ -3838,16 +3842,16 @@
     |indicator|
 
     isButton ifFalse:[
-        indicator := self choiceForm.
-
-        indicator = rawLabel icon ifTrue:[
-            ^ self
-        ].
-        rawLabel icon:indicator.
-
-        disabledRawLabel notNil ifTrue:[
-            disabledRawLabel icon:indicator
-        ]
+	indicator := self choiceForm.
+
+	indicator = rawLabel icon ifTrue:[
+	    ^ self
+	].
+	rawLabel icon:indicator.
+
+	disabledRawLabel notNil ifTrue:[
+	    disabledRawLabel icon:indicator
+	]
     ].
     self redraw
 
@@ -3859,7 +3863,7 @@
     "enabled state of menu changed to aState
     "
     rawLabel notNil ifTrue:[
-        self drawLabel
+	self drawLabel
     ].
 
 !
@@ -3870,16 +3874,16 @@
     |indicator|
 
     isButton ifFalse:[
-        indicator := self indicatorForm.
-
-        indicator = rawLabel icon ifTrue:[
-            ^ self
-        ].
-        rawLabel icon:indicator.
-
-        disabledRawLabel notNil ifTrue:[
-            disabledRawLabel icon:indicator
-        ]
+	indicator := self indicatorForm.
+
+	indicator = rawLabel icon ifTrue:[
+	    ^ self
+	].
+	rawLabel icon:indicator.
+
+	disabledRawLabel notNil ifTrue:[
+	    disabledRawLabel icon:indicator
+	]
     ].
     self redraw
 
@@ -3890,22 +3894,22 @@
     |indicator|
 
     changedObject == self indication ifTrue:[
-        ^ self indicationChanged
+	^ self indicationChanged
     ].
 
     changedObject == self choice ifTrue:[
-        ^ self choiceChanged
+	^ self choiceChanged
     ].
 
     changedObject == enableChannel ifTrue:[
-        (rawLabel notNil and:[menuPanel canDrawItem]) ifTrue:[
-            self drawLabel
-        ].
-        ^ self
+	(rawLabel notNil and:[menuPanel canDrawItem]) ifTrue:[
+	    self drawLabel
+	].
+	^ self
     ].
 
     changedObject == isVisible ifTrue:[
-        ^ menuPanel mustRearrange
+	^ menuPanel mustRearrange
     ].
 
     super update:something with:aParameter from:changedObject
@@ -3924,7 +3928,7 @@
 "/                ^ self
 "/            ]
 "/        ].
-        self indicationChanged
+	self indicationChanged
     ]
 
     "Modified: / 14.8.1998 / 15:19:38 / cg"
@@ -3941,16 +3945,16 @@
     item  := MenuItem labeled:(label printString).
 
     label isImage ifTrue:[
-        rcv := ResourceRetriever new.
-        rcv className:#MenuEditor.
-        rcv selector:#iconUnknown.
-        item labelImage:rcv.
+	rcv := ResourceRetriever new.
+	rcv className:#MenuEditor.
+	rcv selector:#iconUnknown.
+	item labelImage:rcv.
     ].
 
     item activeHelpKey:activeHelpKey.
 
     enableChannel notNil ifTrue:[
-        item enabled:(enableChannel value)
+	item enabled:(enableChannel value)
     ].
 
     item accessCharacterPosition:(self accessCharacterPosition).
@@ -3966,11 +3970,11 @@
     item isButton:isButton.
 
     submenuChannel isSymbol ifTrue:[
-        item submenuChannel:submenuChannel
+	item submenuChannel:submenuChannel
     ] ifFalse:[
-        self submenu notNil ifTrue:[
-            item submenu:(self submenu asMenu)
-        ]
+	self submenu notNil ifTrue:[
+	    item submenu:(self submenu asMenu)
+	]
     ].
   ^ item
 
@@ -3983,35 +3987,35 @@
     |var lbl|
 
     menuPanel disabledRedrawDo:[
-        label := nil.
-        activeHelpKey := aMenuItem activeHelpKey.
-        self enabled:(aMenuItem enabled).
-        self nameKey:(aMenuItem nameKey).
-        self indication:(aMenuItem indication).
-        self choice:(aMenuItem choice).
-        self choiceValue:(aMenuItem choiceValue).
-        self isButton:(aMenuItem isButton).
-        self startGroup:(aMenuItem startGroup).
-        self isVisible:(aMenuItem isVisible).
-
-        (var := aMenuItem accessCharacterPosition) notNil ifTrue:[
-            self accessCharacterPosition:var.
-        ].
-
-        (lbl := aMenuItem labelImage value) isNil ifTrue:[
-            lbl := aMenuItem rawLabel. "/ avoid translating &'s twice
-        ].
-        self label:lbl.
-
-        self shortcutKey:(aMenuItem shortcutKeyCharacter).
-
-        (var := aMenuItem argument) notNil ifTrue:[
-            self argument:var.
-        ].
-
-        submenuChannel := aMenuItem submenuChannel.
-        self submenu:(aMenuItem submenu).
-        self value:(aMenuItem value).
+	label := nil.
+	activeHelpKey := aMenuItem activeHelpKey.
+	self enabled:(aMenuItem enabled).
+	self nameKey:(aMenuItem nameKey).
+	self indication:(aMenuItem indication).
+	self choice:(aMenuItem choice).
+	self choiceValue:(aMenuItem choiceValue).
+	self isButton:(aMenuItem isButton).
+	self startGroup:(aMenuItem startGroup).
+	self isVisible:(aMenuItem isVisible).
+
+	(var := aMenuItem accessCharacterPosition) notNil ifTrue:[
+	    self accessCharacterPosition:var.
+	].
+
+	(lbl := aMenuItem labelImage value) isNil ifTrue:[
+	    lbl := aMenuItem rawLabel. "/ avoid translating &'s twice
+	].
+	self label:lbl.
+
+	self shortcutKey:(aMenuItem shortcutKeyCharacter).
+
+	(var := aMenuItem argument) notNil ifTrue:[
+	    self argument:var.
+	].
+
+	submenuChannel := aMenuItem submenuChannel.
+	self submenu:(aMenuItem submenu).
+	self value:(aMenuItem value).
     ]
 
     "Modified: / 22.8.1998 / 15:34:16 / cg"
@@ -4037,14 +4041,14 @@
     isSelected := self drawSelected.
 
     self enabled ifTrue:[
-        fg := isSelected ifTrue:[self activeForegroundColor]
-                        ifFalse:[menuPanel foregroundColor].
+	fg := isSelected ifTrue:[self activeForegroundColor]
+			ifFalse:[menuPanel foregroundColor].
     ] ifFalse:[
-        fg := menuPanel disabledForegroundColor.
-
-        (img := disabledRawLabel) isNil ifTrue:[
-            img := self disabledRawLabel
-        ]
+	fg := menuPanel disabledForegroundColor.
+
+	(img := disabledRawLabel) isNil ifTrue:[
+	    img := self disabledRawLabel
+	]
     ].
     menuPanel paint:fg.
 
@@ -4052,27 +4056,27 @@
     y := t + ((h - (img heightOn:menuPanel)) // 2).
 
     (self textLabel) notNil ifTrue:[
-        y := y + asc.
+	y := y + asc.
     ].
 
     isButton ifTrue:[   
-        (isSelected or:[self indicationValue == true]) ifTrue:
-        [   
-            img displayOn:menuPanel x:(l + hrzInset) + 1 y: y + 1.
-            buttonLevel := menuPanel buttonActiveLevel.
-        ] ifFalse:[   
-            img displayOn:menuPanel x:(l + hrzInset) y:y.
-            self isEntered ifTrue:[
-                buttonLevel := menuPanel buttonEnteredLevel
-            ] ifFalse:[
-                buttonLevel := menuPanel buttonPassiveLevel
-            ]
-        ].
-        menuPanel 
-            drawButtonEdgesInLayout:layout 
-            withLevel:buttonLevel
-            selected:isSelected.
-        ^ self
+	(isSelected or:[self indicationValue == true]) ifTrue:
+	[   
+	    img displayOn:menuPanel x:(l + hrzInset) + 1 y: y + 1.
+	    buttonLevel := menuPanel buttonActiveLevel.
+	] ifFalse:[   
+	    img displayOn:menuPanel x:(l + hrzInset) y:y.
+	    self isEntered ifTrue:[
+		buttonLevel := menuPanel buttonEnteredLevel
+	    ] ifFalse:[
+		buttonLevel := menuPanel buttonPassiveLevel
+	    ]
+	].
+	menuPanel 
+	    drawButtonEdgesInLayout:layout 
+	    withLevel:buttonLevel
+	    selected:isSelected.
+	^ self
     ].
 
 "/ label = 'Sort By Name' ifTrue:[self halt.].
@@ -4082,42 +4086,42 @@
     "/ DRAW SHORTCUT KEY
 
     MenuView showAcceleratorKeys == true ifTrue:[
-        menuPanel isVerticalLayout ifTrue:[ "/ only for vertical menus ...
-            (scKey:= self shortcutKeyAsString) notNil ifTrue:[
-                (x := menuPanel shortKeyInset) == 0 ifTrue:[
-                    x := hrzInset + LabelRightOffset + (img widthOn:menuPanel)
-                ].
-                x := l + x.
-                y := t + ((h - (scKey heightOn:menuPanel)) // 2).
-                y := y + asc.
-                scKey displayOn:menuPanel x:x y:y. 
-            ].
-        ].
+	menuPanel isVerticalLayout ifTrue:[ "/ only for vertical menus ...
+	    (scKey:= self shortcutKeyAsString) notNil ifTrue:[
+		(x := menuPanel shortKeyInset) == 0 ifTrue:[
+		    x := hrzInset + LabelRightOffset + (img widthOn:menuPanel)
+		].
+		x := l + x.
+		y := t + ((h - (scKey heightOn:menuPanel)) // 2).
+		y := y + asc.
+		scKey displayOn:menuPanel x:x y:y. 
+	    ].
+	].
     ].
 
     "/ DRAW SUBMENU INDICATION
 
     (menuPanel isVerticalLayout and:[self submenu notNil]) ifTrue:[
-        arrow := menuPanel rightArrow.
-        x := layout right - arrow width - hrzInset.
-        y := t + (h - arrow height // 2).
-
-        (menuPanel styleSheet is3D not
-        or:[(img := menuPanel rightArrowShadow) isNil]) ifTrue:[
-            ^ menuPanel displayForm:arrow x:x y:y
-        ].
-        cLa := menuPanel shadowColor.
-        cLb := menuPanel lightColor.
-
-        isSelected ifFalse:[
-            fg  := cLa.
-            cLa := cLb.
-            cLb := fg
-        ].
-        menuPanel paint:cLa.
-        menuPanel displayForm:arrow x:x y:y.
-        menuPanel paint:cLb.
-        menuPanel displayForm:img x:x y:y. 
+	arrow := menuPanel rightArrow.
+	x := layout right - arrow width - hrzInset.
+	y := t + (h - arrow height // 2).
+
+	(menuPanel styleSheet is3D not
+	or:[(img := menuPanel rightArrowShadow) isNil]) ifTrue:[
+	    ^ menuPanel displayForm:arrow x:x y:y
+	].
+	cLa := menuPanel shadowColor.
+	cLb := menuPanel lightColor.
+
+	isSelected ifFalse:[
+	    fg  := cLa.
+	    cLa := cLb.
+	    cLb := fg
+	].
+	menuPanel paint:cLa.
+	menuPanel displayForm:arrow x:x y:y.
+	menuPanel paint:cLb.
+	menuPanel displayForm:img x:x y:y. 
     ]
 
     "Modified: / 22.8.1998 / 18:32:28 / cg"
@@ -4130,10 +4134,10 @@
     |holder|
 
     self isSelected ifTrue:[
-        ^ true
+	^ true
     ].
     isButton ifTrue:[
-        ^ ((holder := self choice) notNil and:[holder value = self choiceValue])
+	^ ((holder := self choice) notNil and:[holder value = self choiceValue])
     ].
     ^ false
 !
@@ -4155,7 +4159,7 @@
     |
 
     (self isVisible and:[menuPanel canDrawItem]) ifFalse:[
-        ^ self
+	^ self
     ].
 
     isSelected := self drawSelected.
@@ -4163,13 +4167,13 @@
     hrzInset   := self horizontalInset.
 
     isSelected ifFalse:[
-        (isButton and:[isEntered]) ifTrue:[
-            paint := self buttonEnteredBackgroundColor
-        ] ifFalse:[
-            paint := self backgroundColor
-        ]
+	(isButton and:[isEntered]) ifTrue:[
+	    paint := self buttonEnteredBackgroundColor
+	] ifFalse:[
+	    paint := self backgroundColor
+	]
     ] ifTrue:[
-        paint := self activeBackgroundColor
+	paint := self activeBackgroundColor
     ].
     l := layout left.
     t := layout top.
@@ -4178,20 +4182,20 @@
     h := layout height.
     w := layout width.
     (ownBgCol := self backgroundColorFromLabel) isNil ifTrue:[
-        menuPanel paint:paint.
-        menuPanel fillRectangle:layout.
+	menuPanel paint:paint.
+	menuPanel fillRectangle:layout.
     ] ifFalse:[
-        self hasIndication ifFalse:[
-            menuPanel paint:ownBgCol.
-            menuPanel fillRectangle:layout.
-        ] ifTrue:[
-            menuPanel paint:paint.
-            x := (rawLabel icon width) + hrzInset + 4.
-
-            menuPanel fillRectangleX:l y:t width:x height:h.
-            menuPanel paint:ownBgCol.
-            menuPanel fillRectangleX:(l + x) y:t width:(w - x) height:h.
-            ownBgCol := nil.
+	self hasIndication ifFalse:[
+	    menuPanel paint:ownBgCol.
+	    menuPanel fillRectangle:layout.
+	] ifTrue:[
+	    menuPanel paint:paint.
+	    x := (rawLabel icon width) + hrzInset + 4.
+
+	    menuPanel fillRectangleX:l y:t width:x height:h.
+	    menuPanel paint:ownBgCol.
+	    menuPanel fillRectangleX:(l + x) y:t width:(w - x) height:h.
+	    ownBgCol := nil.
        ].
     ].
     lgCol       := menuPanel lightColor.
@@ -4200,111 +4204,111 @@
     type        := self separatorType.
 
     type notNil ifTrue:[
-        type == #blankLine ifTrue:[
-            ^ self
-        ].
-        "/ draw separator
-        menuPanel paint:shCol.
-
-        menuPanel verticalLayout ifTrue:[
-            l := l + hrzInset.
-            r := r - hrzInset.
-            y := t - 1 + (h // 2).
-
-            type == #doubleLine ifTrue:[y := y - 2].
-
-            menuPanel displayLineFromX:l y:y toX:r y:y.
-            menuPanel paint:lgCol.
-            y := y + 1.
-            menuPanel displayLineFromX:l y:y toX:r y:y.
-
-            type == #doubleLine ifTrue:[
-                y := y + 3.
-                menuPanel paint:shCol.
-                menuPanel displayLineFromX:l y:y toX:r y:y.
-                menuPanel paint:lgCol.
-                y := y + 1.
-                menuPanel displayLineFromX:l y:y toX:r y:y.
-            ].
-        ] ifFalse:[
-            x := l - 1 + (w // 2).
-
-            type == #doubleLine ifTrue:[x := x - 2].
-
-            menuPanel displayLineFromX:x y:t toX:x y:b.
-            menuPanel paint:lgCol.
-            x := x + 1.
-            menuPanel displayLineFromX:x y:t toX:x y:b.
-
-            type == #doubleLine ifTrue:[
-                x := x + 3.
-                menuPanel paint:shCol.
-                menuPanel displayLineFromX:x y:t toX:x y:b.
-                menuPanel paint:lgCol.
-                x := x + 1.
-                menuPanel displayLineFromX:x y:t toX:x y:b.
-            ]
-        ].
-        ^ self
+	type == #blankLine ifTrue:[
+	    ^ self
+	].
+	"/ draw separator
+	menuPanel paint:shCol.
+
+	menuPanel verticalLayout ifTrue:[
+	    l := l + hrzInset.
+	    r := r - hrzInset.
+	    y := t - 1 + (h // 2).
+
+	    type == #doubleLine ifTrue:[y := y - 2].
+
+	    menuPanel displayLineFromX:l y:y toX:r y:y.
+	    menuPanel paint:lgCol.
+	    y := y + 1.
+	    menuPanel displayLineFromX:l y:y toX:r y:y.
+
+	    type == #doubleLine ifTrue:[
+		y := y + 3.
+		menuPanel paint:shCol.
+		menuPanel displayLineFromX:l y:y toX:r y:y.
+		menuPanel paint:lgCol.
+		y := y + 1.
+		menuPanel displayLineFromX:l y:y toX:r y:y.
+	    ].
+	] ifFalse:[
+	    x := l - 1 + (w // 2).
+
+	    type == #doubleLine ifTrue:[x := x - 2].
+
+	    menuPanel displayLineFromX:x y:t toX:x y:b.
+	    menuPanel paint:lgCol.
+	    x := x + 1.
+	    menuPanel displayLineFromX:x y:t toX:x y:b.
+
+	    type == #doubleLine ifTrue:[
+		x := x + 3.
+		menuPanel paint:shCol.
+		menuPanel displayLineFromX:x y:t toX:x y:b.
+		menuPanel paint:lgCol.
+		x := x + 1.
+		menuPanel displayLineFromX:x y:t toX:x y:b.
+	    ]
+	].
+	^ self
     ].
 
     isButton ifTrue:[
-        ^ self drawLabel
+	^ self drawLabel
     ].
 
     showItemSep ifTrue:[
-        |col index item lfSep rtSep|
-        col := menuPanel paint.
-
-        index := menuPanel indexOfItem:self.
-        item  := menuPanel itemAtIndex:(index - 1).
-        lfSep := item notNil and:[item isButton not].
-        item  := menuPanel itemAtIndex:(index + 1).
-        rtSep := item notNil and:[item isButton not].
-
-        menuPanel paint:lgCol.
-
-        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:shCol.
-
-            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:shCol.
-
-            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.
-            ] 
-        ]
+	|col index item lfSep rtSep|
+	col := menuPanel paint.
+
+	index := menuPanel indexOfItem:self.
+	item  := menuPanel itemAtIndex:(index - 1).
+	lfSep := item notNil and:[item isButton not].
+	item  := menuPanel itemAtIndex:(index + 1).
+	rtSep := item notNil and:[item isButton not].
+
+	menuPanel paint:lgCol.
+
+	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:shCol.
+
+	    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:shCol.
+
+	    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.
+	    ] 
+	]
     ].
 
     self drawLabel.  
 
     (ownBgCol notNil and:[isSelected]) ifTrue:[
-        ownBgCol brightness > 0.5 ifTrue:[menuPanel paint: menuPanel selectionFrameDarkColor]
-                                 ifFalse:[menuPanel paint: menuPanel selectionFrameBrightColor].
-
-        menuPanel displayRectangleX:(l + 1) y:(t + 1) width:(w - 2) height:(h - 2).
-        menuPanel displayRectangleX:(l + 2) y:(t + 2) width:(w - 4) height:(h - 4).  
+	ownBgCol brightness > 0.5 ifTrue:[menuPanel paint: menuPanel selectionFrameDarkColor]
+				 ifFalse:[menuPanel paint: menuPanel selectionFrameBrightColor].
+
+	menuPanel displayRectangleX:(l + 1) y:(t + 1) width:(w - 2) height:(h - 2).
+	menuPanel displayRectangleX:(l + 2) y:(t + 2) width:(w - 4) height:(h - 4).  
     ].
 
     menuPanel drawEdgesForX:l y:t width:w height:h isSelected:isSelected isEntered:isEntered.
@@ -4322,20 +4326,20 @@
     self submenu:nil.
 
     (enableChannel notNil and:[self isKindOfValueHolder:enableChannel]) ifTrue:[
-        enableChannel removeDependent:self
+	enableChannel removeDependent:self
     ].
 
     (isVisible notNil and:[self isKindOfValueHolder:isVisible]) ifTrue:[
-        isVisible removeDependent:self
+	isVisible removeDependent:self
     ].
 
     channel := self indication.
     (channel notNil and:[self isKindOfValueHolder:channel]) ifTrue:[
-        channel removeDependent:self
+	channel removeDependent:self
     ].
     channel := self choice.
     (channel notNil and:[self isKindOfValueHolder:channel]) ifTrue:[
-        channel removeDependent:self
+	channel removeDependent:self
     ].
 
     menuPanel := nil.
@@ -4356,29 +4360,29 @@
     "returns the label used if the item is disabled
     "
     disabledRawLabel isNil ifTrue:[
-        (     rawImage notNil
-         and:[(rawImage respondsTo:#colorMap)
-         and:[rawImage colorMap notNil]]
-        ) ifFalse:[
-            disabledRawLabel := rawLabel.
-        ] ifTrue:[
-            disabledRawLabel := menuPanel lightenedImageOnDevice:rawImage.
-
-            rawLabel class == LabelAndIcon ifTrue:[
-                (isButton
-                  or:[((self indication notNil or:[self choice notNil])
-                 and:[label class == LabelAndIcon])]
-                ) ifTrue:[
-                    disabledRawLabel := LabelAndIcon form:(rawLabel icon)
-                                                    image:disabledRawLabel
-                                                   string:(rawLabel string)
-                ] ifFalse:[
-                    disabledRawLabel := LabelAndIcon form:disabledRawLabel
-                                                    image:(rawLabel image)
-                                                   string:(rawLabel string)
-                ]
-            ]
-        ]
+	(     rawImage notNil
+	 and:[(rawImage respondsTo:#colorMap)
+	 and:[rawImage colorMap notNil]]
+	) ifFalse:[
+	    disabledRawLabel := rawLabel.
+	] ifTrue:[
+	    disabledRawLabel := menuPanel lightenedImageOnDevice:rawImage.
+
+	    rawLabel class == LabelAndIcon ifTrue:[
+		(isButton
+		  or:[((self indication notNil or:[self choice notNil])
+		 and:[label class == LabelAndIcon])]
+		) ifTrue:[
+		    disabledRawLabel := LabelAndIcon form:(rawLabel icon)
+						    image:disabledRawLabel
+						   string:(rawLabel string)
+		] ifFalse:[
+		    disabledRawLabel := LabelAndIcon form:disabledRawLabel
+						    image:(rawLabel image)
+						   string:(rawLabel string)
+		]
+	    ]
+	]
     ].
     ^ disabledRawLabel
 !
@@ -4389,20 +4393,20 @@
     |icon|
 
     rawImage notNil ifTrue:[
-        rawLabel isImage ifTrue:[
-            rawLabel := menuPanel imageOnDevice:rawImage
-        ] ifFalse:[
-            rawLabel class == LabelAndIcon ifTrue:[
-                (icon := rawLabel image) notNil ifTrue:[
-                    rawLabel image:(menuPanel imageOnDevice:icon)
-                ].
-                (icon := rawLabel icon) notNil ifTrue:[
-                    (self indication isNil and:[self choice isNil]) ifTrue:[
-                        rawLabel icon:(menuPanel imageOnDevice:icon)
-                    ]
-                ]
-            ]
-        ]
+	rawLabel isImage ifTrue:[
+	    rawLabel := menuPanel imageOnDevice:rawImage
+	] ifFalse:[
+	    rawLabel class == LabelAndIcon ifTrue:[
+		(icon := rawLabel image) notNil ifTrue:[
+		    rawLabel image:(menuPanel imageOnDevice:icon)
+		].
+		(icon := rawLabel icon) notNil ifTrue:[
+		    (self indication isNil and:[self choice isNil]) ifTrue:[
+			rawLabel icon:(menuPanel imageOnDevice:icon)
+		    ]
+		]
+	    ]
+	]
     ].
 !
 
@@ -4412,75 +4416,75 @@
     |char size form|
 
     label isNil ifTrue:[        "/ not yet initialized
-        ^ self
+	^ self
     ].
 
     (form := self indicatorForm) isNil ifTrue:[
-        form := self choiceForm
+	form := self choiceForm
     ].
     rawImage         := nil.
     disabledRawLabel := nil.
     rawLabel         := label value.
 
     rawLabel isString ifTrue:[
-        rawLabel isText ifFalse:[
-            rawLabel := rawLabel withoutSeparators
-        ].        
-
-        form isNil ifTrue:[                             "/ check for separator
-            rawLabel isEmpty ifTrue:[
-                  rawLabel := nil.
-                ^ self
-            ].
-
-            rawLabel size == 1 ifTrue:[
-                char := rawLabel first.
-
-                (char == $- or:[char == $=]) ifTrue:[   "/ other line separators
-                    label := String new:1.
-                    label at:1 put:char.
-                    rawLabel := nil.
-                  ^ self
-                ]
-            ]
-        ].
-        rawLabel isEmpty ifTrue:[
-            rawLabel := label value
-        ].
-        size := self accessCharacterPosition.
-
-        (size notNil and:[size <= rawLabel size]) ifTrue:[
-            rawLabel isText ifFalse:[
-                rawLabel := Text string:rawLabel
-            ].
-            rawLabel emphasisAt:size add:#underline
-        ]
+	rawLabel isText ifFalse:[
+	    rawLabel := rawLabel withoutSeparators
+	].        
+
+	form isNil ifTrue:[                             "/ check for separator
+	    rawLabel isEmpty ifTrue:[
+		  rawLabel := nil.
+		^ self
+	    ].
+
+	    rawLabel size == 1 ifTrue:[
+		char := rawLabel first.
+
+		(char == $- or:[char == $=]) ifTrue:[   "/ other line separators
+		    label := String new:1.
+		    label at:1 put:char.
+		    rawLabel := nil.
+		  ^ self
+		]
+	    ]
+	].
+	rawLabel isEmpty ifTrue:[
+	    rawLabel := label value
+	].
+	size := self accessCharacterPosition.
+
+	(size notNil and:[size <= rawLabel size]) ifTrue:[
+	    rawLabel isText ifFalse:[
+		rawLabel := Text string:rawLabel
+	    ].
+	    rawLabel emphasisAt:size add:#underline
+	]
     ].
     rawLabel isImage ifTrue:[
-        rawImage := rawLabel.
-
-        form notNil ifTrue:[
-            isButton ifTrue:[form := nil].
-            rawLabel := LabelAndIcon form:form image:rawImage.
-        ]
+	rawImage := rawLabel.
+
+	form notNil ifTrue:[
+	    isButton ifTrue:[form := nil].
+	    rawLabel := LabelAndIcon form:form image:rawImage.
+	]
     ] ifFalse:[
-        rawLabel class == LabelAndIcon ifTrue:[
-            rawImage := rawLabel icon.
-
-            (form notNil and:[isButton not]) ifTrue:[
-                rawLabel image:rawImage.
-                rawLabel icon:form
-            ]                
-        ] ifFalse:[
-            rawImage := nil.
-            rawLabel isNil ifTrue:[rawLabel := ''].
-
-            (form notNil and:[isButton not]) ifTrue:[
-                rawLabel := LabelAndIcon icon:form string:rawLabel.
-            ] ifFalse:[
-                disabledRawLabel := rawLabel.
-            ]
-        ].
+	rawLabel class == LabelAndIcon ifTrue:[
+	    rawImage := rawLabel icon.
+
+	    (form notNil and:[isButton not]) ifTrue:[
+		rawLabel image:rawImage.
+		rawLabel icon:form
+	    ]                
+	] ifFalse:[
+	    rawImage := nil.
+	    rawLabel isNil ifTrue:[rawLabel := ''].
+
+	    (form notNil and:[isButton not]) ifTrue:[
+		rawLabel := LabelAndIcon icon:form string:rawLabel.
+	    ] ifFalse:[
+		disabledRawLabel := rawLabel.
+	    ]
+	].
     ].
     menuPanel shown ifTrue:[ self fetchImages ].
     menuPanel mustRearrange
@@ -4508,7 +4512,7 @@
      is created
     "
     adornment isNil ifTrue:[
-        adornment := Adornment new
+	adornment := Adornment new
     ].
   ^ adornment
 !
@@ -4533,15 +4537,15 @@
     run := run first.
 
     run size == 0 ifTrue:[
-        (run value isColor and:[run key == #backgroundColor]) ifTrue:[
-            ^ run value
-        ]
+	(run value isColor and:[run key == #backgroundColor]) ifTrue:[
+	    ^ run value
+	]
     ] ifFalse:[
-        run do:[:r|
-            (r value isColor and:[r key == #backgroundColor]) ifTrue:[
-                ^ r value
-            ]
-        ]
+	run do:[:r|
+	    (r value isColor and:[r key == #backgroundColor]) ifTrue:[
+		^ r value
+	    ]
+	]
     ].
   ^ nil
 !
@@ -4565,7 +4569,7 @@
     (holder := self choice) isNil ifTrue:[^ nil].
 
     holder value = self choiceValue ifTrue:[
-        ^ self class checkOnIcon
+	^ self class checkOnIcon
     ].
     ^ self class checkOffIcon
 !
@@ -4581,57 +4585,57 @@
     subm := nil.
 
     aRecv notNil ifTrue:[
-        submenuChannel last ~~ $: ifTrue:[
-            Object messageNotUnderstoodSignal handle:[:ex|
-                |selector|
-
-                ((selector := ex parameter selector) == submenuChannel
-                or:[selector == #aspectFor:]) ifFalse:[
-                    ex reject
-                ].
-            ] do:[
-                subm := aRecv aspectFor:submenuChannel
-            ].
-            subm isNil ifTrue:[
-                Object messageNotUnderstoodSignal handle:[:ex| 
-                    ex parameter selector == submenuChannel ifFalse:[
-                        ex reject
-                    ].
-            ] do:[
-                    subm := aRecv perform:submenuChannel
-                ]
-            ].
-            subm isNil ifTrue:[
-                Object messageNotUnderstoodSignal handle:[:ex| 
-                    ex parameter selector == submenuChannel ifFalse:[
-                        ex reject
-                    ].
-                ] do:[
-                    subm := aRecv class perform:submenuChannel
-                ]
-            ]
-        ] ifFalse:[
-            (argument := self argument) notNil ifTrue:[
-                sel := submenuChannel asSymbol.
-                Object messageNotUnderstoodSignal handle:[:ex| 
-                    ex parameter selector == sel ifFalse:[
-                        ex reject
-                    ].
-                ] do:[
-                    subm := aRecv perform:sel with:argument
-                ].
-
-                subm isNil ifTrue:[
-                    Object messageNotUnderstoodSignal handle:[:ex| 
-                        ex parameter selector == sel ifFalse:[
-                            ex reject
-                        ].
-                    ] do:[
-                        subm := aRecv class perform:sel with:argument
-                    ]
-                ]
-            ]
-        ]
+	submenuChannel last ~~ $: ifTrue:[
+	    Object messageNotUnderstoodSignal handle:[:ex|
+		|selector|
+
+		((selector := ex parameter selector) == submenuChannel
+		or:[selector == #aspectFor:]) ifFalse:[
+		    ex reject
+		].
+	    ] do:[
+		subm := aRecv aspectFor:submenuChannel
+	    ].
+	    subm isNil ifTrue:[
+		Object messageNotUnderstoodSignal handle:[:ex| 
+		    ex parameter selector == submenuChannel ifFalse:[
+			ex reject
+		    ].
+	    ] do:[
+		    subm := aRecv perform:submenuChannel
+		]
+	    ].
+	    subm isNil ifTrue:[
+		Object messageNotUnderstoodSignal handle:[:ex| 
+		    ex parameter selector == submenuChannel ifFalse:[
+			ex reject
+		    ].
+		] do:[
+		    subm := aRecv class perform:submenuChannel
+		]
+	    ]
+	] ifFalse:[
+	    (argument := self argument) notNil ifTrue:[
+		sel := submenuChannel asSymbol.
+		Object messageNotUnderstoodSignal handle:[:ex| 
+		    ex parameter selector == sel ifFalse:[
+			ex reject
+		    ].
+		] do:[
+		    subm := aRecv perform:sel with:argument
+		].
+
+		subm isNil ifTrue:[
+		    Object messageNotUnderstoodSignal handle:[:ex| 
+			ex parameter selector == sel ifFalse:[
+			    ex reject
+			].
+		    ] do:[
+			subm := aRecv class perform:sel with:argument
+		    ]
+		]
+	    ]
+	]
     ].
     ^ subm
 
@@ -4644,40 +4648,40 @@
     |indication numArgs sel recv|
 
     (indication := self indication) isNil ifTrue:[
-        ^ nil                                           "/ has no indication
+	^ nil                                           "/ has no indication
     ].
 
     indication isSymbol ifTrue:[
-        (numArgs := indication numArgs) ~~ 0 ifTrue:[
-            numArgs == 2 ifTrue:[
-                recv := menuPanel receiver.
-
-                (recv isKindOf:ValueModel) ifFalse:[
-                    (recv notNil or:[(recv := menuPanel application) notNil]) ifTrue:[
-                        sel := indication copyFrom:1 to:(indication indexOf:$:).
-                        indication := nil.
-                        sel := sel asSymbol.
-
-                        Object messageNotUnderstoodSignal handle:[:ex| 
-                            ex parameter selector == sel ifFalse:[
+	(numArgs := indication numArgs) ~~ 0 ifTrue:[
+	    numArgs == 2 ifTrue:[
+		recv := menuPanel receiver.
+
+		(recv isKindOf:ValueModel) ifFalse:[
+		    (recv notNil or:[(recv := menuPanel application) notNil]) ifTrue:[
+			sel := indication copyFrom:1 to:(indication indexOf:$:).
+			indication := nil.
+			sel := sel asSymbol.
+
+			Object messageNotUnderstoodSignal handle:[:ex| 
+			    ex parameter selector == sel ifFalse:[
 "/                                Transcript showCR:'no indication for: ' , sel.
-                                ex reject
-                            ].
-                        ] do:[
-                            indication := recv perform:sel with:self argument
-                        ]
-                    ].
-                ].
-                ^ indication value == true
-            ].
-            indication := (indication copyWithoutLast:1) asSymbol
-        ].
-        indication := self aspectAt:indication.
-
-        (self isKindOfValueHolder:indication) ifTrue:[
-            self adornment indication:indication.
-            indication addDependent:self.
-        ]
+				ex reject
+			    ].
+			] do:[
+			    indication := recv perform:sel with:self argument
+			]
+		    ].
+		].
+		^ indication value == true
+	    ].
+	    indication := (indication copyWithoutLast:1) asSymbol
+	].
+	indication := self aspectAt:indication.
+
+	(self isKindOfValueHolder:indication) ifTrue:[
+	    self adornment indication:indication.
+	    indication addDependent:self.
+	]
     ].
     ^ indication value == true
 
@@ -4690,35 +4694,35 @@
     |numArgs indication recv|
 
     (indication := self indication) isNil ifTrue:[
-        ^ self                                          "/ has no indication
+	^ self                                          "/ has no indication
     ].
 
     indication isSymbol ifFalse:[
-        (self isKindOfValueHolder:indication) ifTrue:[  "/ is value holder
-            indication value:aValue
-        ].
-        ^ self
+	(self isKindOfValueHolder:indication) ifTrue:[  "/ is value holder
+	    indication value:aValue
+	].
+	^ self
     ].
     recv := menuPanel receiver.
 
     (recv isKindOf:ValueModel) ifTrue:[
-        recv value:indication value:aValue.
+	recv value:indication value:aValue.
     ] ifFalse:[
-        (      (numArgs := indication numArgs) ~~ 0
-          and:[recv notNil or:[(recv := menuPanel application) notNil]]
-        ) ifTrue:[
-            Object messageNotUnderstoodSignal handle:[:ex| 
-                (ex parameter selector ~~ indication) ifTrue:[
-                    ex reject
-                ]
-            ] do:[
-                numArgs == 1 ifTrue:[
-                    recv perform:indication with:aValue
-                ] ifFalse:[
-                    recv perform:indication with:(self argument ? self) with:aValue
-                ]
-            ]
-        ]
+	(      (numArgs := indication numArgs) ~~ 0
+	  and:[recv notNil or:[(recv := menuPanel application) notNil]]
+	) ifTrue:[
+	    Object messageNotUnderstoodSignal handle:[:ex| 
+		(ex parameter selector ~~ indication) ifTrue:[
+		    ex reject
+		]
+	    ] do:[
+		numArgs == 1 ifTrue:[
+		    recv perform:indication with:aValue
+		] ifFalse:[
+		    recv perform:indication with:(self argument ? self) with:aValue
+		]
+	    ]
+	]
     ].
 
     "Modified: / 28.7.1998 / 20:47:08 / cg"
@@ -4730,7 +4734,7 @@
     |value|
 
     (value := self indicationValue) isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
   ^ value ifTrue:[IndicatorOn] ifFalse:[IndicatorOff]
 
@@ -4751,17 +4755,17 @@
     |c lbl|
 
     rawLabel isNil ifFalse:[
-        ^ nil
+	^ nil
     ].
 
     (lbl := label value) isNil ifTrue:[
-        ^ #singleLine
+	^ #singleLine
     ].
 
     lbl size == 1 ifTrue:[
-        c := lbl first.
-        c == $- ifTrue:[^ #singleLine].
-        c == $= ifTrue:[^ #doubleLine].
+	c := lbl first.
+	c == $- ifTrue:[^ #singleLine].
+	c == $= ifTrue:[^ #doubleLine].
     ].
   ^ #blankLine
 ! !
@@ -4774,9 +4778,9 @@
     |holder|
 
     (self isVisible and:[self enabled and:[rawLabel notNil]]) ifTrue:[
-        ((holder := self choice) isNil or:[holder value ~= self choiceValue]) ifTrue:[
-            ^ true
-        ].
+	((holder := self choice) isNil or:[holder value ~= self choiceValue]) ifTrue:[
+	    ^ true
+	].
     ].
     ^ false
 !
@@ -4785,11 +4789,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]]]
-          )
+	^ (     (x >= layout left)
+	    and:[x <  layout right
+	    and:[y >  layout top
+	    and:[y <= layout bottom]]]
+	  )
     ].
     ^ false
 !
@@ -4843,15 +4847,15 @@
     |state|
 
     isVisible isSymbol ifTrue:[
-        state := self aspectAt:isVisible.
-
-        (self isKindOfValueHolder:state) ifTrue:[
-            isVisible := state.
-            isVisible addDependent:self.
-            state := isVisible value.
-        ]
+	state := self aspectAt:isVisible.
+
+	(self isKindOfValueHolder:state) ifTrue:[
+	    isVisible := state.
+	    isVisible addDependent:self.
+	    state := isVisible value.
+	]
     ] ifFalse:[
-        state := isVisible value
+	state := isVisible value
     ].
   ^ state ~~ false
 
@@ -4863,29 +4867,29 @@
     |oldState newState|
 
     isVisible isNil ifTrue:[
-        oldState := true
+	oldState := true
     ] ifFalse:[
-        oldState := isVisible value.
-        (self isKindOfValueHolder:isVisible) ifTrue:[
-            isVisible removeDependent:self
-        ]
+	oldState := isVisible value.
+	(self isKindOfValueHolder:isVisible) 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.
+	(self isKindOfValueHolder:isVisible) ifTrue:[
+	    isVisible addDependent:self
+	] ifFalse:[
+	    isVisible isSymbol ifTrue:[^ self]
+	].
+	menuPanel shown ifFalse:[^ self].
+	newState := isVisible value.
     ].
 
     newState ~~ oldState ifTrue:[
-        menuPanel mustRearrange
+	menuPanel mustRearrange
     ]
 !
 
@@ -4902,31 +4906,31 @@
     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 or:[submenuChannel notNil]]) ifTrue:[
-            x := x + menuPanel subMenuIndicationWidth.
-
-            s notNil ifTrue:[x := x + ShortcutKeyOffset]
-                    ifFalse:[x := x + LabelRightOffset]
-        ].
+	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 or:[submenuChannel notNil]]) 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
-        ].
+	sepSize := (self class separatorSize:(self separatorType)).
+	isVertical ifFalse:[
+	    x := x max:sepSize.
+	    y := y + (menuPanel font height)
+	] ifTrue:[
+	    y := y max:sepSize
+	].
     ].
 
     ^ (x @ y)
@@ -4947,34 +4951,34 @@
     |nm key prefix|
 
     (key := self shortcutKey) isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
 
     key isCharacter ifTrue:[
-        nm := key asString
+	nm := key asString
     ] ifFalse:[
-        "/ this is somewhat complicated: we have the symbolic key at hand,
-        "/ but want to show the untranslated (inverse keyBoardMapped) key & modifier
-        "/ Ask the devices keyboardMap for the backtranslation.
-
-        nm := menuPanel device keyboardMap keyAtValue:key ifAbsent:key.
-        "/
-        "/ some modifier-key combination ?
-        "/
-        (nm startsWith:#Cmd) ifTrue:[
-            prefix := #Cmd.
-        ] ifFalse:[(nm startsWith:#Alt) ifTrue:[
-            prefix := #Alt.
-        ] ifFalse:[(nm startsWith:#Meta) ifTrue:[
-            prefix := #Meta.
-        ] ifFalse:[(nm startsWith:#Ctrl) ifTrue:[
-            prefix := #Ctrl.
-        ]]]].
-        prefix notNil ifTrue:[
-            nm := (self shortcutKeyPrefixFor:prefix), (nm copyFrom:(prefix size + 1))
-        ] ifFalse:[
-            nm := nm asString
-        ]
+	"/ this is somewhat complicated: we have the symbolic key at hand,
+	"/ but want to show the untranslated (inverse keyBoardMapped) key & modifier
+	"/ Ask the devices keyboardMap for the backtranslation.
+
+	nm := menuPanel device keyboardMap keyAtValue:key ifAbsent:key.
+	"/
+	"/ some modifier-key combination ?
+	"/
+	(nm startsWith:#Cmd) ifTrue:[
+	    prefix := #Cmd.
+	] ifFalse:[(nm startsWith:#Alt) ifTrue:[
+	    prefix := #Alt.
+	] ifFalse:[(nm startsWith:#Meta) ifTrue:[
+	    prefix := #Meta.
+	] ifFalse:[(nm startsWith:#Ctrl) ifTrue:[
+	    prefix := #Ctrl.
+	]]]].
+	prefix notNil ifTrue:[
+	    nm := (self shortcutKeyPrefixFor:prefix), (nm copyFrom:(prefix size + 1))
+	] ifFalse:[
+	    nm := nm asString
+	]
     ].
     ^ nm
 
@@ -4988,7 +4992,7 @@
 
     m := menuPanel device modifierKeyTopFor:aModifier.
     m notNil ifTrue:[
-        ^ m , '-'
+	^ m , '-'
     ].
     ^ aModifier , '-'.
 
@@ -5004,9 +5008,9 @@
 
     subMenu := self submenu.
     subMenu realized ifFalse:[
-        (id := subMenu id) notNil ifTrue:[
-            menuPanel device unmapWindow:id
-        ]
+	(id := subMenu id) notNil ifTrue:[
+	    menuPanel device unmapWindow:id
+	]
     ] ifTrue:[
        subMenu hide
     ].
@@ -5031,14 +5035,14 @@
     windowGrp := menuPanel topMenu windowGroup.
     subMenu   := self setupSubmenu.
     subMenu isNil ifTrue:[
-        ^ self
+	^ self
     ].
     subMenu font:(menuPanel topMenu font).
     subMenu becomesActiveMenu.
 
     windowGrp notNil ifTrue:[
-        subMenu windowGroup:windowGrp.
-        windowGrp addTopView:subMenu.
+	subMenu windowGroup:windowGrp.
+	windowGrp addTopView:subMenu.
     ].
     subMenu fixSize.
     subMenu origin:aPoint.
@@ -5046,9 +5050,9 @@
     top := menuPanel topMenu.
 
     subMenu realized ifFalse:[
-        subMenu realize. 
+	subMenu realize. 
     ] ifTrue:[
-        top device mapWindow:subMenu id.
+	top device mapWindow:subMenu id.
     ].
     subMenu makeFullyVisible.
 
@@ -5069,24 +5073,24 @@
     subMenu := self submenu.
 
     aState ifFalse:[
-        self redraw.
-        subMenu notNil ifTrue:[
-            self hideSubmenu
-        ].
+	self redraw.
+	subMenu notNil ifTrue:[
+	    self hideSubmenu
+	].
       ^ self
     ].
     menuPanel shown ifFalse:[^ self].  
     (self hasIndication not or: [isButton not]) ifTrue: [self redraw].
 
     subMenu isNil ifTrue:[
-        menuPanel isPopUpView ifTrue:[
-            menuPanel grabMouseAndKeyboard.
-        ].
-        ^ self.
+	menuPanel isPopUpView ifTrue:[
+	    menuPanel grabMouseAndKeyboard.
+	].
+	^ self.
     ].
 
     menuPanel verticalLayout ifTrue:[p := (layout right - 4) @ (layout top)]
-                            ifFalse:[p := (layout left)  @ (layout bottom)].
+			    ifFalse:[p := (layout left)  @ (layout bottom)].
 
     d := menuPanel device.
     p := d translatePoint:p from:(menuPanel id) to:(d rootWindowId).
@@ -5181,6 +5185,6 @@
 !MenuPanel class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/MenuPanel.st,v 1.124 1998-09-02 13:42:50 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/MenuPanel.st,v 1.125 1998-09-08 10:17:48 cg Exp $'
 ! !
 MenuPanel initialize!