MenuPanel.st
author Claus Gittinger <cg@exept.de>
Fri, 11 Sep 1998 14:04:52 +0200
changeset 1130 fb79ef4aeec8
parent 1124 4a7fec62a572
child 1137 7df0b776e47a
permissions -rw-r--r--
style changes

"
 COPYRIGHT (c) 1997 by eXept Software AG
	      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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


SimpleView subclass:#MenuPanel
	instanceVariableNames:'adornment shadowView mapTime mustRearrange superMenu
		shortKeyInset selection items groupSizes receiver enableChannel
		menuHolder enabled onLevel offLevel fgColor activeFgColor
		lastActiveMenu activeBgColor disabledFgColor groupDividerSize
		itemSpace fitFirstPanel rightArrow rightArrowShadow
		selectionFrameBrightColor selectionFrameDarkColor
		buttonLightColor buttonShadowColor buttonHalfLightColor
		buttonHalfShadowColor lastButtonSelected enteredItem
		buttonEnteredBgColor'
	classVariableNames:'InitialSelectionQuerySignal DefaultAdornment
		DefaultGroupDividerSize DefaultHilightLevel DefaultLevel
		DefaultItemSpace DefaultButtonItemSpace DefaultForegroundColor
		DefaultBackgroundColor DefaultHilightForegroundColor
		DefaultHilightBackgroundColor DefaultDisabledForegroundColor
		DefaultFitFirstPanel RightArrowForm RightArrowShadowForm
		SelectionFrameBrightColor SelectionFrameDarkColor
		ButtonActiveLevel ButtonPassiveLevel ButtonActiveBackgroundColor
		ButtonPassiveBackgroundColor ButtonLightColor ButtonShadowColor
		ButtonHalfLightColor ButtonHalfShadowColor ButtonEdgeStyle Images
		LigthenedImages ButtonEnteredBackgroundColor ButtonEnteredLevel'
	poolDictionaries:''
	category:'Views-Menus'
!

Object subclass:#Item
	instanceVariableNames:'layout menuPanel subMenu adornment rawLabel disabledRawLabel
		enableChannel nameKey accessCharacterPosition value label
		rawImage activeHelpKey submenuChannel startGroup isButton
		isVisible'
	classVariableNames:'HorizontalInset VerticalInset HorizontalButtonInset
		VerticalButtonInset LabelRightOffset ShortcutKeyOffset
		IndicatorOn IndicatorOff'
	poolDictionaries:''
	privateIn:MenuPanel
!

Object subclass:#Adornment
	instanceVariableNames:'indication accessCharacterPosition shortcutKey argument choice
		choiceValue'
	classVariableNames:''
	poolDictionaries:''
	privateIn:MenuPanel::Item
!

!MenuPanel class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG
	      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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

!

documentation
"
    a menu panel used for both pull-down-menus and pop-up-menus.

    not yet finished MenuPanel class - this will eventually replace
    most of the MenuView and PopUpMenu stuff.
    (and hopefully be ST-80 compatible ...)

    To create a menu, there exists a MenuEditor which will generate
    a menu specification.


    [author:]
	Claus Atzkern

    [see also:]
	Menu
	MenuItem
	MenuEditor
"

!

examples

"
    start as PullDownMenu
										[exBegin]
    |top subView mview desc s1 s2 s3 img lbs labels|

    top := StandardSystemView new.

    mview := MenuPanel in:top.

    labels := #( 'foo' 'bar' 'baz' 'test' 'claus' ).
    mview level:2.
    mview verticalLayout:false.
    img := Image fromFile:'bitmaps/SBrowser.xbm'.
    lbs := Array with:'foo' with:'bar' with:img with:'baz' with:'test' with:'ludwig'.
    mview labels:lbs.
    mview shortcutKeyAt:2 put:#Cut.
    mview accessCharacterPositionAt:1 put:1.
    mview accessCharacterPositionAt:2 put:2.

    mview enabledAt:5 put:false.
    mview groupSizes:#( 2 2 ).
    s1 := MenuPanel labels:labels.
    s1 accessCharacterPositionAt:1 put:1.
    s1 accessCharacterPositionAt:2 put:2.
    s1 groupSizes:#( 2 2 ).
    s2 := MenuPanel labels:#( '1' nil '2' '-' '3' '=' '4' ' ' '5' ).
    s3 := MenuPanel labels:lbs.

    s1 subMenuAt:2 put:s2.
    s1 subMenuAt:3 put:(MenuPanel labels:lbs).
    s2 subMenuAt:3 put:s3.
    s3 subMenuAt:3 put:(MenuPanel labels:labels).
    s3 shortcutKeyAt:3 put:$q.

    mview subMenuAt:1 put:s1.
    mview subMenuAt:4 put:(MenuPanel labels:lbs).
    (mview subMenuAt:4) shortcutKeyAt:3 put:#Copy.
    s1 shortcutKeyAt:1 put:#Copy.
    s1 shortcutKeyAt:3 put:#Paste.

    mview subMenuAt:2 put:(MenuPanel labels:labels).
    top extent:(mview preferredExtent).
    top open.
										[exEnd]


    start as PopUpMenu
										[exBegin]
    |subView mview desc s1 s2 s3 img lbs labels|

    mview := MenuPanel new.
    labels := #( 'foo' 'bar' 'baz' ).
    mview level:2.

    img := Image fromFile:'bitmaps/SBrowser.xbm'.
    lbs := Array with:'foo' with:'bar' with:img with:'baz' with:'test'.
    mview labels:lbs.

    s1 := MenuPanel labels:labels.
    s2 := MenuPanel labels:#( '1' nil '2' '-' '3' '=' '4' ' ' '5' ).
    s3 := MenuPanel labels:lbs.
    s1 subMenuAt:2 put:s2.
    s1 subMenuAt:3 put:(MenuPanel labels:lbs).
    s2 subMenuAt:3 put:s3.
    s3 subMenuAt:3 put:(MenuPanel labels:labels).
    s3 shortcutKeyAt:3 put:$q.

    mview subMenuAt:1 put:s1.
    mview subMenuAt:4 put:(MenuPanel labels:lbs).
    (mview subMenuAt:4) shortcutKeyAt:3 put:#Copy.
    s1 shortcutKeyAt:1 put:#Copy.
    s1 shortcutKeyAt:3 put:#Paste.

    mview subMenuAt:2 put:(MenuPanel labels:labels).
    mview startUp
										[exEnd]


    start from menu spec
										[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 verticalLayout:false.
    Transcript showCR:(menu startUp).
										[exEnd]

"

! !

!MenuPanel class methodsFor:'instance creation'!

fromSpec:aSpec
    ^ self fromSpec:aSpec receiver:nil
!

fromSpec:aSpec receiver:aReceiver
    |menu|

    aSpec notNil ifTrue:[
	menu := Menu new.
	menu fromLiteralArrayEncoding:aSpec.
    ].
  ^ self menu:menu receiver:aReceiver
!

labels:labels
    ^ self labels:labels nameKeys:nil receiver:nil
!

labels:labels nameKeys:nameKeys
    ^ self labels:labels nameKeys:nameKeys receiver:nil
!

labels:labels nameKeys:nameKeys receiver:aReceiver
    |mview|

    mview := self menu:nil receiver:aReceiver.
    mview labels:labels.
    mview nameKeys:nameKeys.
  ^ mview

!

labels:labels receiver:aReceiver
    ^ self labels:labels nameKeys:nil receiver:aReceiver
!

menu:aMenu
    ^ self menu:aMenu receiver:nil
!

menu:aMenu receiver:aReceiver
    |mview|

    mview := self new.
    mview menu:aMenu.

"/ a menu itself may contain a receiver
"/ thus we do not overwrite the receiver

    aReceiver notNil ifTrue:[
	mview receiver:aReceiver
    ].
  ^ mview

! !

!MenuPanel class methodsFor:'class initialization'!

initialize
    "
    DefaultAdornment := nil.
    self initialize
    "

    InitialSelectionQuerySignal isNil ifTrue:[
	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
    ].

    "Modified: / 15.1.1998 / 23:08:31 / stefan"
!

preSnapshot
    "remove all resources
    "
    Images := nil.
    LigthenedImages := nil.

! !

!MenuPanel class methodsFor:'defaults'!

updateStyleCache

    |menuStyle style font|

    MenuView updateStyleCache.        

    menuStyle := MenuView styleSheet.
    menuStyle isNil ifTrue:[
        "make sure that style sheet is present"
        MenuView updateStyleCache.        
        menuStyle := MenuView styleSheet.
    ].
    style := menuStyle name.


    DefaultForegroundColor := menuStyle colorAt:'pullDownMenu.foregroundColor'.

    DefaultForegroundColor isNil ifTrue:[
        DefaultForegroundColor := menuStyle colorAt:'menu.foregroundColor'
                                            default:Color black.
    ].

    (style == #motif or:[style == #iris]) ifTrue:[
        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
        ].
    ].

    DefaultDisabledForegroundColor := menuStyle colorAt:'menu.disabledForegroundColor'.
    DefaultDisabledForegroundColor isNil ifTrue:[
        DefaultDisabledForegroundColor := menuStyle colorAt:'button.disabledForegroundColor'
                                                    default:Color darkGray.
    ].

    style == #motif ifTrue:[
        DefaultHilightBackgroundColor := DefaultBackgroundColor
    ] ifFalse:[
        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.
    DefaultItemSpace        := menuStyle at:'menu.itemSpace' default:0.
    DefaultButtonItemSpace  := menuStyle at:'menu.buttonItemSpace' default:0.
    DefaultFitFirstPanel    := menuStyle at:'menu.fitFirstPanel' default:true.

    MenuView updateStyleCache.
    DefaultFont := MenuView defaultFont.
"/    font := menuStyle fontAt:'pullDownMenu.font'.
"/    font isNil ifTrue:[font := menuStyle fontAt:'menu.font'].
"/    DefaultFont := font.

    RightArrowForm := SelectionInListView rightArrowFormOn:Display.

    (style ~~ #os2 and:[style ~~ #win95]) ifTrue:[
        RightArrowShadowForm := SelectionInListView rightArrowShadowFormOn:Display.
    ] ifFalse:[
        RightArrowShadowForm := nil
    ].

    SelectionFrameBrightColor    := Color white.
    SelectionFrameDarkColor      := Color black.

    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]).
    ].
    ButtonPassiveLevel           :=  menuStyle at:'menu.buttonPassiveLevel'.
    ButtonPassiveLevel isNil ifTrue:[
        ButtonPassiveLevel       :=  menuStyle at:'button.passiveLevel' default:(menuStyle is3D ifTrue:[2] ifFalse:[0]).
    ].
    ButtonActiveBackgroundColor  :=  menuStyle at:'button.activeBackgroundColor' default: DefaultBackgroundColor.
    ButtonPassiveBackgroundColor := (menuStyle at:'button.backgroundColor') ? (menuStyle at:'viewBackground') ? DefaultBackgroundColor.
    ButtonLightColor             := (menuStyle at:'button.lightColor') ? Color white.
    ButtonShadowColor            := menuStyle at:'button.shadowColor' default:(style == #next ifTrue:[Color black] ifFalse:[Color gray]).
    ButtonHalfLightColor         :=  menuStyle at:'button.halfLightColor'.
    ButtonHalfShadowColor        :=  menuStyle at:'button.halfShadowColor'.
    ButtonEdgeStyle              :=  menuStyle at:'button.edgeStyle'.

    ButtonEnteredBackgroundColor := menuStyle colorAt:'menu.buttonEnteredBackgroundColor'.
    ButtonEnteredBackgroundColor isNil ifTrue:[
        ButtonEnteredBackgroundColor := menuStyle colorAt:'button.enteredBackgroundColor'
                                                  default:ButtonPassiveBackgroundColor.
    ].
    ButtonEnteredLevel := menuStyle at:'menu.buttonEnteredLevel' default:ButtonPassiveLevel.

    Item updateStyleCache

    "
     self updateStyleCache
    "

    "Modified: / 10.9.1998 / 21:40:32 / cg"
! !

!MenuPanel class methodsFor:'image registration'!

image:anImage onDevice:aDevice
"
Images := nil
"
    |deviceImages image|

    Images isNil ifTrue:[ Images := IdentityDictionary new ].

    (deviceImages := Images at:aDevice ifAbsent:nil) isNil ifTrue:[
	Images at:aDevice put:(deviceImages := Dictionary new)
    ].

    (image := deviceImages at:anImage ifAbsent:nil) notNil ifTrue:[
	^ image
    ].

    image := anImage copy onDevice:aDevice.
    image clearMaskedPixels.
    deviceImages at:anImage put:image.
    ^ image

    "Modified: / 27.2.1998 / 17:41:37 / cg"
!

lightenedImage:anImage onDevice:aDevice
"
LigthenedImages := nil
"
    |deviceImages image|

    LigthenedImages isNil ifTrue:[ LigthenedImages := IdentityDictionary new ].

    (deviceImages := LigthenedImages at:aDevice ifAbsent:nil) isNil ifTrue:[
	LigthenedImages at:aDevice put:(deviceImages := Dictionary new)
    ].

    (image := deviceImages at:anImage ifAbsent:nil) notNil ifTrue:[
	^ image
    ].

    ((anImage respondsTo:#colorMap) and:[anImage colorMap notNil]) ifTrue:[
	image := anImage copy lightened onDevice:aDevice.
	image clearMaskedPixels.
    ] ifFalse:[
	image := self image:anImage onDevice:aDevice
    ].
    deviceImages at:anImage put:image.
    ^ image


! !

!MenuPanel class methodsFor:'private'!

subMenu:aSubMenu
    "create a submenu; can be redifined in derived classes
    "
  ^ (self new) menu:aSubMenu.

    "Modified: / 8.8.1998 / 02:13:11 / cg"
! !

!MenuPanel methodsFor:'accept'!

accept
    "accept current selected item
    "
    ^ self accept:(self selection)
!

accept:anItem
    "this is the topMenu: accept item
    "
    |value item tgState itemIdx recv|

    self superMenu notNil ifTrue:[
	^ 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.
    ].

    self isPopUpView ifFalse:[
	self do:[:el| el updateIndicators].
	self windowGroup processExposeEvents.
    ] ifTrue:[
	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.
    ].

  ^ item.

    "Modified: / 14.8.1998 / 16:10:02 / cg"
!

accept:anItem index:anIndex toggle:aState receiver:aReceiver
    "accept an item
    "
    |value argument numArgs isKindOfValueModel|

    anItem isNil ifTrue:[
	self menuAdornmentAt:#hasPerformed put:true.
      ^ nil
    ].

    self menuAdornmentAt:#hasPerformed put:(aReceiver isKindOf:ValueModel).

    (value := anItem value) isNil ifTrue:[
	^ anIndex
    ].

    (argument := anItem argument) isNil ifTrue:[
	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.
      ^ anIndex
    ].

    aReceiver isNil ifTrue:[
	^ value
    ].
    isKindOfValueModel := aReceiver isKindOf:ValueModel.

    (numArgs := value numArgs) == 0 ifTrue:[
	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]
	]
    ].
    self menuAdornmentAt:#hasPerformed put:true.
  ^ value
!

lastItemAccepted
    "returns last item selected or nil
    "
  ^ self topMenu menuAdornmentAt:#item
!

lastValueAccepted
    "returns last value accepted or nil
    "
    ^ (self lastItemAccepted) value
"/    |top|
"/
"/    top := self topMenu.
"/
"/    (top menuAdornmentAt:#hasPerformed) == true ifTrue:[
"/        ^ self topMenu menuAdornmentAt:#value.
"/    ].
"/  ^ nil

    "Modified: / 18.6.1998 / 23:37:09 / cg"
! !

!MenuPanel methodsFor:'accessing'!

accessCharacterPositionAt:stringOrNumber
    "get the access character position for a textLabel
    "
  ^ self itemAt:stringOrNumber do:[:el| el accessCharacterPosition ]
!

accessCharacterPositionAt:stringOrNumber put:anIndexOrNil
    "get the access character position for a textLabel
    "
    self itemAt:stringOrNumber do:[:el| el accessCharacterPosition:anIndexOrNil ]
!

accessCharacterPositions
    "returns a collection of accessCharacterPosition's or nil
    "
    ^ self collect:[:anItem| anItem accessCharacterPosition ]

!

accessCharacterPositions:something
    "define accessCharacterPosition's for each item
    "
    self onEachPerform:#accessCharacterPosition: withArgList:something
!

args
    "returns a collection of argument's or nil
    "
    ^ self collect:[:anItem| anItem argument ]
!

args:something
    "define arguments for each item
    "
    self onEachPerform:#argument: withArgList:something
!

argsAt:stringOrNumber
    "gets the argument of an item or nil
    "
  ^ self itemAt:stringOrNumber do:[:el| el argument ]
!

argsAt:stringOrNumber put:anArgument
    "sets the argument of an item
    "
    self itemAt:stringOrNumber do:[:el| el argument:anArgument ]
!

enteredItem
    "return the item over which the mouse pointer is located;
     nil if the mouse is not over any item"

    ^ enteredItem

    "Created: / 20.8.1998 / 13:12:34 / cg"
!

groupSizes
    "gets collection of group sizes
    "
  ^ groupSizes
!

groupSizes:aGroupSizes
    "sets collection of group sizes
    "
    aGroupSizes = groupSizes ifFalse:[
	groupSizes := aGroupSizes copy.
	self mustRearrange.
    ].
!

labelAt:stringOrNumber
    "gets the label of an item or nil
    "
  ^ self itemAt:stringOrNumber do:[:el| el label ]
!

labelAt:stringOrNumber put:aLabel
    "sets the label of an item
    "
    self itemAt:stringOrNumber do:[:el| el label:aLabel ]
!

labels
    "returns a collection of labels's or nil
    "
    ^ self collect:[:anItem| anItem label ]

!

labels:labels
    "define labels for each item
    "
    self disabledRedrawDo:[
	self removeAll.

	labels notNil ifTrue:[
	    labels do:[:aLabel|(self createAtIndex:nil) label:aLabel]
	]
    ]
!

nameKeyAt:stringOrNumber
    "gets the nameKey of an item or nil
    "
  ^ self itemAt:stringOrNumber do:[:el| el nameKey ]
!

nameKeyAt:stringOrNumber put:aNameKey
    "sets the nameKey of an item
    "
    self itemAt:stringOrNumber do:[:el| el nameKey:aNameKey ]
!

nameKeys
    "returns a collection of nameKeys's or nil
    "
    ^ self collect:[:anItem| anItem nameKey ]
!

nameKeys:something
    "define nameKeys for each item
    "
    self onEachPerform:#nameKey: withArgList:something
!

numberOfItems
    "gets number of items
    "
    ^ items size
!

receiver
    "get the menu-receiver. Thats the one who gets the messages ( both from myself and
     from all submenus no specific receiver is defined ).
    "
    (receiver isNil and:[superMenu notNil]) ifTrue:[
	^ superMenu receiver
    ].
  ^ receiver
!

receiver:anObject 
    "set the menu-receiver. Thats the one who gets the messages ( both from myself and
     from all submenus no specific receiver is defined ).
    "
    receiver := anObject
!

shortcutKeyAt:stringOrNumber
    "gets the shortCutKey of an item or nil
    "
  ^ self itemAt:stringOrNumber do:[:el| el shortcutKey ]
!

shortcutKeyAt:stringOrNumber put:aKey
    "sets the shortCutKey of an item
    "
    self itemAt:stringOrNumber do:[:el| el shortcutKey:aKey ]
!

shortcutKeys
    "returns a collection of shortcutKey's or nil
    "
    ^ self collect:[:anItem| anItem shortcutKey ]

!

shortcutKeys:something
    "define shortcutKey's for each item
    "
    self onEachPerform:#shortcutKey: withArgList:something
!

valueAt:stringOrNumber
    "gets value of an item; a block, valueHolder, ...
    "
  ^ self itemAt:stringOrNumber do:[:el| el value ]

!

valueAt:stringOrNumber put:someThing
    "sets value of an item; a block, valueHolder, ...
    "
    self itemAt:stringOrNumber do:[:el| el value:someThing ]


!

values:something
    "define values for each item
    "
    self onEachPerform:#value: withArgList:something
! !

!MenuPanel methodsFor:'accessing behavior'!

disable
    "disable the menu
    "
    self enabled:false
!

disableAll
    "disable all items; not the menu in case of enabled
    "
    self do:[:anItem| anItem enabled:false]
!

disableAll:collectionOfIndicesOrNames
    "disable an collection of items
    "
    collectionOfIndicesOrNames do:[:entry| self enabledAt:entry put:false ].

!

enable
    "enable the menu
    "
    self enabled:true
!

enableAll
    "enable all items; not the menu in case of disabled
    "
    self do:[:anItem| anItem enabled:true]
!

enableAll:collectionOfIndicesOrNames
    "enable an collection of items
    "
    collectionOfIndicesOrNames do:[:entry| self enabledAt:entry put:true ].

!

enabled
    "returns enabled state
    "
    ^ enabled
!

enabled:aState
    "change enabled state of menu
    "
    |state|

    state := aState ? true.

    self enabled == state ifTrue:[
	^ self
    ].
    enabled := state.

    self canDrawItem ifTrue:[
	self do:[:anItem| anItem enabledStateOfMenuChangedTo:enabled]
    ].
!

enabledAt:stringOrNumber
    "gets the enabled state of an item or false
    "
  ^ self itemAt:stringOrNumber do:[:el| el enabled ] ifAbsent:false
!

enabledAt:stringOrNumber put:aState
    "sets the enabled state of an item
    "
    self itemAt:stringOrNumber do:[:el| el enabled:aState ]
!

isEnabled:stringOrNumber
    "gets the enabled state of an item or false
    "
    ^ self enabledAt:stringOrNumber
! !

!MenuPanel methodsFor:'accessing channels'!

enableChannel
    "gets a enable channel or nil
    "
    ^ enableChannel
!

enableChannel:aValueHolder
    "set my enableChannel
    "
    enableChannel notNil ifTrue:[
	enableChannel removeDependent:self
    ].

    (enableChannel := aValueHolder) notNil ifTrue:[
	enableChannel addDependent:self.
    ].
    self enabled:(enableChannel value).
!

menuHolder
    "gets a menu holder or nil
    "
    ^ menuHolder
!

menuHolder:aValueHolder
    "set my menuHolder
    "
    menuHolder notNil ifTrue:[
	menuHolder removeDependent:self
    ].

    (menuHolder := aValueHolder) notNil ifTrue:[
	menuHolder addDependent:self.
    ].
    self menu:(menuHolder value)
! !

!MenuPanel methodsFor:'accessing color & font'!

activeBackgroundColor
    "get the background drawing color used to highlight selection
    "
    ^ activeBgColor
!

activeBackgroundColor:aColor
    "set the background drawing color used to highlight selection. You should not 
     use this method; instead leave the value as defined in the styleSheet.
    "
    activeBgColor ~~ aColor ifTrue:[
	activeBgColor := aColor on:device.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ]

    "Modified: / 6.6.1998 / 19:49:46 / cg"
!

activeForegroundColor
    "get the foreground color used to highlight selections
    "
    ^ activeFgColor
!

activeForegroundColor:aColor
    "set the foreground color used to highlight selections; You should not
     use this method; instead leave the value as defined in the styleSheet.
    "
    activeFgColor ~~ aColor ifTrue:[
	activeFgColor := aColor on:device.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ]

    "Modified: / 6.6.1998 / 19:50:01 / cg"
!

backgroundColor
    "return the background color
    "
    ^ super viewBackground
!

backgroundColor:aColor
    "set the background drawing color. You should not use this method;
     instead leave the value as defined in the styleSheet.
    "
    super viewBackground ~~ aColor ifTrue:[
	super viewBackground:aColor.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ]

    "Modified: / 6.6.1998 / 19:50:06 / cg"
!

buttonActiveBackgroundColor
    "get the background drawing color used to highlight button selection
    "
    ^ButtonActiveBackgroundColor
!

buttonEdgeStyle
    "get the button edge style
    "
    ^ButtonEdgeStyle
!

buttonEnteredBackgroundColor
    "get the background drawing color used to highlight entered button items
    "
    ^ buttonEnteredBgColor

    "Created: / 20.8.1998 / 13:53:37 / cg"
!

buttonEnteredLevel
    "get the 3D-level used to highlight entered button items
    "
    ^ ButtonEnteredLevel

    "Created: / 20.8.1998 / 13:53:46 / cg"
    "Modified: / 20.8.1998 / 15:49:32 / cg"
!

buttonHalfLightColor
    "get the background drawing color used to half light button frame
    "
    ^buttonHalfLightColor
!

buttonHalfShadowColor
    "get the background drawing color used to half shadow button frame
    "
    ^buttonHalfShadowColor
!

buttonLightColor
    "get the background drawing color used to light button frame
    "
    ^buttonLightColor
!

buttonPassiveBackgroundColor
    "get the background drawing color used for button
    "
    ^ButtonPassiveBackgroundColor
!

buttonShadowColor
    "get the background drawing color used to shadow button frame
    "
    ^buttonShadowColor
!

disabledForegroundColor
    "return the foreground color used by disabled items
    "
  ^ disabledFgColor

!

disabledForegroundColor:aColor
    "set the foregroundColor drawing color used by disabled items. You should not
     use this method; instead leave the value as defined in the styleSheet.
    "
    disabledFgColor ~~ aColor ifTrue:[
	disabledFgColor := aColor on:device.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ].

    "Modified: / 6.6.1998 / 19:50:17 / cg"
!

font:aFont
    "set the font
    "
    (aFont notNil and:[aFont ~= font]) ifTrue:[
	super font:(aFont on:device).

	superMenu notNil ifTrue:[
	    self extent:(self preferredExtent)
	].
	self mustRearrange.
    ]
!

foregroundColor
    "return the passive foreground color
    "
  ^ fgColor


!

foregroundColor:aColor
    "set the foregroundColor drawing color. You should not use this method;
     instead leave the value as defined in the styleSheet.
    "
    fgColor ~~ aColor ifTrue:[
	fgColor := aColor on:device.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ]

    "Modified: / 6.6.1998 / 19:50:46 / cg"
!

lightColor
    "get the lightColor
    "
    ^ lightColor


!

lightColor:aColor
    "set the light drawing color. You should not use this method;
     instead leave the value as defined in the styleSheet.
    "
    lightColor ~~ aColor ifTrue:[
	super lightColor:aColor.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ]

    "Modified: / 6.6.1998 / 19:50:39 / cg"
!

selectionFrameBrightColor
    "get the selection frame bright color
    "
    ^selectionFrameBrightColor
!

selectionFrameDarkColor
    "get the selection frame dark color
    "
    ^selectionFrameDarkColor
!

shadowColor
    "get the shadowColor
    "
    ^ shadowColor


!

shadowColor:aColor
    "set the shadow drawing color. You should not use this method;
     instead leave the value as defined in the styleSheet.
    "
    shadowColor ~~ aColor ifTrue:[
	super shadowColor:aColor.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ]

    "Modified: / 6.6.1998 / 19:50:32 / cg"
! !

!MenuPanel methodsFor:'accessing dimensions'!

height
    "default height
    "
    |item|

    (explicitExtent ~~ true) ifTrue:[
	(item := self itemAt:1) notNil ifTrue:[
	    self rearrangeItems.
	  ^ item height
	].
	^ 4 + (font height + (font descent * 2)).
    ].
    ^ super height
!

preferredExtent
    "compute and returns my preferred extent
    "
    |x y hasMenu shCtKey space hrzInset|

    self numberOfItems == 0 ifTrue:[
	^ 32 @ 32
    ].
    space := (items size + 1) * itemSpace.

    self isFitPanel ifTrue:[
	x := 0
    ] ifFalse:[
	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.
    ] 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.
    ].
    ^ (x @ y) + (margin + margin)

    "Modified: / 24.8.1998 / 19:16:02 / cg"
!

shortKeyInset
    "left inset of shortcutKey
    "
  ^ shortKeyInset
!

subMenuIndicationWidth
    ^ RightArrowForm width
! !

!MenuPanel methodsFor:'accessing items'!

itemAt:stringOrNumber
    "returns item assigned to an index, nameKey, textLabel or value if symbol.
     If no item match nil is returned.
    "
    |idx|

    idx := self indexOf:stringOrNumber.
    (idx > 0 and:[idx <= items size]) ifTrue:[ ^ items at:idx ].
  ^ nil

!

itemAt:stringOrNumber do:aOneArgBlock
    "evaluate teh block for an item and return the result from the block. In case that  
     the item not exists nil is returned
    "
    ^ self itemAt:stringOrNumber do:aOneArgBlock ifAbsent:nil
!

itemAt:stringOrNumber do:aOneArgBlock ifAbsent:exceptionBlock
    "evaluate teh block for an item and return the result from the block. In case that  
     the item not exists the result of the exception block is returned (no arguments).
    "
    |item|

    item := self itemAt:stringOrNumber.
    item notNil ifTrue:[ ^ aOneArgBlock value:item ].
  ^ exceptionBlock value
!

itemAtIndex:anIndex
    "returns item at an index or nil
    "
    ^ items notNil ifTrue:[items at:anIndex ifAbsent:nil] ifFalse:[nil]
! !

!MenuPanel methodsFor:'accessing look'!

buttonActiveLevel
    "get the button active level
    "
    ^ButtonActiveLevel

!

buttonPassiveLevel
    "get the button passive level
    "
    ^ButtonPassiveLevel

!

fitFirstPanel
    "gets true if the first panel in the menu hierarchy must be fit 
     to the extent of its superView
    "
    ^ fitFirstPanel
!

fitFirstPanel:aState
    "sets true if the first panel in the menu hierarchy must be fit 
     to the extent of its superView
    "
    (fitFirstPanel == aState or:[self isPopUpView]) ifFalse:[
	fitFirstPanel := aState.
	self mustRearrange
    ]
!

groupDividerSize
    "get the size of the group dividers
    "
  ^ groupDividerSize

!

groupDividerSize:aSize
    "set the size of the group dividers. You should not use this
     method; instead leave the value as defined in the styleSheet.
    "
    aSize ~~ groupDividerSize ifTrue:[
	groupDividerSize := aSize.
	self mustRearrange.
    ].

!

itemSpace
    "get the space space between to items
    "
  ^ itemSpace

!

itemSpace:aSize
    "set the horizontal space between to items. You should not use this
     method; instead leave the value as defined in the styleSheet.
    "
    aSize ~~ itemSpace ifTrue:[
	itemSpace := aSize.
	self mustRearrange
    ].

!

level:anInt
    super level:anInt.
    mustRearrange := true
!

rightArrow
    ^ rightArrow
!

rightArrowShadow
    ^ rightArrowShadow
!

showGroupDivider
    "get the enabled flag for showing groupDiveders
    "
  ^ self menuAdornmentAt:#showGroupDivider
!

showGroupDivider:aState
    "set the enabled flag for showing groupDiveders
    "
    (self menuAdornmentAt:#showGroupDivider put:aState) ifTrue:[
	self mustRearrange.
    ]
!

showSeparatingLines
    "gets true if drawing of separating lines is enabled.
    "
  ^ self menuAdornmentAt:#showSeparatingLines
!

showSeparatingLines:aState
    "turn on/off drawing of separating lines.
    "
    (self menuAdornmentAt:#showSeparatingLines put:aState) ifTrue:[
	self mustRearrange
    ]
!

verticalLayout
    "get the layout: or vertical( true ) or horizontal( false )
    "
  ^ self menuAdornmentAt:#verticalLayout
!

verticalLayout:aState
    "set the layout: or vertical( true ) or horizontal( false )
    "
    (self menuAdornmentAt:#verticalLayout put:aState) ifTrue:[        
	self mustRearrange
    ]
! !

!MenuPanel methodsFor:'accessing submenu'!

subMenuAt:stringOrNumber
    "gets the submenu of an item or nil
    "
  ^ self itemAt:stringOrNumber do:[:el| el submenu ]
!

subMenuAt:stringOrNumber put:aSubMenu
    "sets the submenu of an item
    "
    self itemAt:stringOrNumber do:[:el| el submenu:aSubMenu ]

!

subMenuShown
    "return the currently visible submenu - or nil if there is none
    "
    |item|

    (item := self selection) notNil ifTrue:[
	^ item submenu
    ].
  ^ nil
! !

!MenuPanel methodsFor:'activation'!

hide
    "hide the view, leave its modal event loop
    "

    self selection:nil.
    self unmap.


!

show
    "realize the view at its last position
    "
  ^ self showAt:(self origin) resizing:true

!

showAt:aPoint
    "realize the view at aPoint
    "
  ^ self showAt:aPoint resizing:true


!

showAt:aPoint resizing:aBoolean
    "realize the view at aPoint; return nil if no item was selected,
     or if I have already performed.
     Return the items value, otherwise.
     Notice, that this is returned back to the one who started this
     menu (i.e. the view or controller), which will perform the action
     if a non-nil is returned.
    "
    self rearrangeItems.

    aBoolean ifTrue:[
	self fixSize.
    ].
    self origin:aPoint.
    self makeFullyVisible.
    self openModal:[true]. "realize     "

    "/ if I have already performed,
    "/ return nil - to avoid items triggering twice.

    (self topMenu menuAdornmentAt:#hasPerformed) == true ifTrue:[
	^ nil
    ].
    ^ self lastValueAccepted

    "Modified: / 8.7.1998 / 20:06:35 / cg"
!

showAtPointer
    "realize the view at the current pointer position
    "
  ^ self showAt:(device pointerPosition) resizing:true


!

showCenteredIn:aView
    "make myself visible at the screen center.
    "
    |top|

    top := aView topView.
    top raise.
  ^ self showAt:(top origin + (aView originRelativeTo:top) + (aView extent // 2) - (self extent // 2))


!

startUp
    "realize the menu at the current pointer position
    "
    ^ self showAtPointer
!

startUpAt:aPoint
    "realize the menu at aPoint
    "
    ^ self showAt:aPoint

    "Created: / 21.5.1998 / 14:15:57 / cg"
! !

!MenuPanel methodsFor:'active help'!

helpText
    |appl item key|

    (item := self selection) notNil ifTrue:[
	(key := item activeHelpKey) notNil ifTrue:[
	    (appl := self application) notNil ifTrue:[
		^ appl helpTextForKey:key.
	    ].
	]
    ].
    ^ nil.

    "Modified: / 31.7.1998 / 03:15:17 / cg"
!

helpTextAt:aPoint
    |menu point item key appl|

    menu := self superMenuAtX:aPoint x y:aPoint y.

    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.
	    ].
	]
    ].
"/    'nil item' printCR.
    ^ nil.

    "Modified: / 31.7.1998 / 03:15:07 / cg"
! !

!MenuPanel methodsFor:'adding & removing'!

createAtIndex:anIndexOrNil
    "create an item and add this item to the index. In case of nil the item
     is added to the end. If the index is not valid nil is returned otherwise
     the new created item.
    "
    |max item|

    max := (items size) + 1.

    anIndexOrNil notNil ifTrue:[
	(anIndexOrNil < 1 or:[anIndexOrNil > max]) ifTrue:[
	    ^ nil
	]
    ].
    items isNil ifTrue:[
	items := OrderedCollection new
    ].
    item := Item in:self.

    (anIndexOrNil isNil or:[anIndexOrNil == max]) ifTrue:[
	items add:item
    ] ifFalse:[
	items add:item beforeIndex:anIndexOrNil
    ].
    ^ item
!

remove:stringOrNumber
    "remove the first item which is assigned to stringOrNumber;
     if found, remove and return it
    "
    |item|

    (item := self itemAt:stringOrNumber) notNil ifTrue:[
	items remove:item.
	item  destroy.
	items isEmpty ifTrue:[items := nil].
	self mustRearrange.
    ].
  ^ item
!

removeAll
    "remove all items and submenus
    "
    self disabledRedrawDo:[
	self selection:nil.
	groupSizes := nil.
	self do:[:el| el destroy ].
	items := nil
    ].
! !

!MenuPanel methodsFor:'change & update'!

update:something with:aParameter from:changedObject

    changedObject == menuHolder    ifTrue:[^ self menu:(menuHolder value)].
    changedObject == enableChannel ifTrue:[^ self enabled:(enableChannel value)].

    super update:something with:aParameter from:changedObject
! !

!MenuPanel methodsFor:'converting'!

asMenu
    "convert contents to menu
    "
    |menu|

    menu := Menu new.
    menu groupSizes:groupSizes.
    self do:[:anItem| menu addItem:(anItem asMenuItem) ].
  ^ menu
!

fromSpec:aMenuSpec
    "build from spec
    "
    |menu|

    menu := Menu new.
    menu fromLiteralArrayEncoding:aMenuSpec.
    self menu:menu

!

menu:aMenu
    "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).
	]
    ]

    "Modified: / 8.8.1998 / 02:05:04 / cg"
! !

!MenuPanel methodsFor:'drawing'!

disabledRedrawDo:aBlock
    "evaluate a block without redrawing within the block; after processing
     of the block a redraw might be performed
    "
    |state|

    state := mustRearrange.
    mustRearrange := true.
    aBlock value.
    mustRearrange := state.
    self mustRearrange
!

drawButtonEdgesInLayout: layout withLevel: aLevel selected:isSelected
    |shadow|

    styleSheet is3D ifFalse:[
	^ self displayRectangle:layout.
    ].

    shadow := buttonShadowColor.
    isSelected ifTrue:[
	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

    "Created: / 20.8.1998 / 15:43:38 / cg"
    "Modified: / 20.8.1998 / 19:09:05 / cg"
!

drawEdgesForX:x y:y width:w height:height isSelected:selectedBool isEntered:enteredBool
    |level|

    level := selectedBool 
		ifTrue:[onLevel] 
		ifFalse:[offLevel].

    level ~~ 0 ifTrue:[
	self drawEdgesForX:x y:y width:w height:height level:level
    ].

    "Modified: / 20.8.1998 / 15:43:11 / cg"
!

mustRearrange
    "force rearrange (i.e. set the rearrange flag)
    "
    mustRearrange == true ifFalse:[
	mustRearrange := true.
	shown ifTrue:[
	    self invalidate "/ RepairNow:true
	]
    ]

    "Modified: / 6.6.1998 / 19:51:07 / cg"
!

rearrangeGroups
    |layout
     dltX  "{ Class:SmallInteger }"
     start "{ Class:SmallInteger }"
    |

    (self isPopUpView or:[self verticalLayout]) ifTrue:[
	^ self
    ].

    layout := items last layout.

    (dltX := width - margin "- 2" - layout right) <= 0 ifTrue:[
	^ self  "/ no free space
    ].
    start := items findFirst:[:anItem| anItem startGroup == #right ].

    start == 0 ifTrue:[
	^ 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).
	]
    ].
!

rearrangeItems
    "recompute layout of my items
    "
    |expLast e grpDivSz layout isVert
     x  "{ Class:SmallInteger }"
     y  "{ Class:SmallInteger }"
     noItems "{ Class:SmallInteger }"
    |

    mustRearrange ifFalse:[ ^ self ].

"/  fetch font from superMenu
    (superMenu notNil and:[superMenu font ~~ font]) ifTrue:[
	super font:(superMenu font on:device)
    ].
    (noItems := items size) == 0 ifTrue:[
	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 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
    ] ifFalse:[
	e := self computeExtent
    ].

    x := y := margin.

    isVert ifTrue:[y := y + itemSpace]
	  ifFalse:[x := x + itemSpace].

    self keysAndValuesDo:[:anIndex :el| |org corn elPref|
	el isVisible ifTrue:[
	    el isButton ifTrue:[
		org := Point x:(x+DefaultButtonItemSpace) y:(y+DefaultButtonItemSpace).
	    ] ifFalse:[
		org := Point x:x y:y.
	    ].
	    elPref := el preferredExtent.
	    isVert ifTrue:[
		y := y + elPref y.
		corn := (e x - margin @ y).
		el isButton ifTrue:[
		    corn := corn - (DefaultButtonItemSpace @ 0).
		    el layout:(Rectangle origin:org corner:corn).
		    y := y + (2 * DefaultButtonItemSpace).
		] ifFalse:[
		    el layout:(Rectangle origin:org corner:corn).
		].
		y := y + itemSpace.
	    ] ifFalse:[
		x := x + elPref x.
		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)].
	]
    ].
    self rearrangeGroups.
    mustRearrange := false.

    "Modified: / 20.8.1998 / 19:34:41 / cg"
!

redrawX:x y:y width:w height:h
    "redraw a rectangle
    "
    |start end isVrt x1 x2 y1 y2 item layout lnSz hrzInset prevClipArea|

    (shown and:[w ~~ 0]) ifFalse:[^ self].

    self  paint:(self backgroundColor).
    self  clearRectangleX:x y:y width:w height:h.

    isVrt := self verticalLayout.
    end   := items size.

    mustRearrange ifTrue:[
	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
	]
    ].

    (     self hasGroupDividers
     and:[self showGroupDivider
     and:[self isFitPanel not]]
    ) ifTrue:[
	lnSz := groupDividerSize // 2
    ].

    end == 0 ifTrue:[^ self ].

    hrzInset := items first horizontalInset.

    prevClipArea   := clipRect.
    clipRect       := nil.

    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
	]
    ].

    clipRect := nil.
    prevClipArea isNil ifTrue:[device noClipIn:drawableId  gc:gcId]
		      ifFalse:[self clippingRectangle:prevClipArea].



! !

!MenuPanel methodsFor:'enumerting & searching'!

collect:aOneArgBlock
    "evaluate the argument, aOneArgBlock for every item in the menuPanel
     and return a collection of the results
    "
    items notNil ifTrue:[^ items collect:aOneArgBlock ].
  ^ nil

!

do:aOneArgBlock
    "evaluate the argument, aOneArgBlock for every item in the menuPanel.
    "
    items notNil ifTrue:[ items do:aOneArgBlock ].

!

findFirst:aOneArgBlock
    "find the first item, for which evaluation of the argument, aOneArgBlock
     returns true; return its index or 0 if none detected.
    "
    items notNil ifTrue:[ ^ items findFirst:aOneArgBlock ].
  ^ 0

!

findLast:aOneArgBlock
    "find the last item, for which evaluation of the argument, aOneArgBlock
     returns true; return its index or 0 if none detected.
    "
    items notNil ifTrue:[ ^ items findLast:aOneArgBlock ].
  ^ 0

!

indexOf:something
    "returns index of an item assigned to an index, nameKey, textLabel or value if symbol.
     If no item match 0 is returned. No range checks are performed on a number argument
    "
    |i v|

    something isNumber ifTrue:[ ^ something ].
    something isNil    ifTrue:[ ^ 0 ].

    i := self findFirst:[:el|(el nameKey = something) or: [el = something]].

    i ~~ 0 ifTrue:[
	^ i
    ].

    something isSymbol ifTrue:[
	i := self findFirst:[:el|
	    v := el value.
	    v isSymbol and:[v == something]
	].
	i ~~ 0 ifTrue:[
	    ^ i
	]
    ].

    (something respondsTo:#string) ifTrue:[
	v := something string.
      ^ self findFirst:[:el|el textLabel = v].
    ].
  ^ 0
!

indexOfItem:anItem
    "returns the index of the item or 0
    "
    ^ items notNil ifTrue:[items identityIndexOf:anItem] ifFalse:[0]
!

keysAndValuesDo:aTwoArgBlock
    "evaluate the argument, aTwoArgBlock for every item in the menuPanel.
    "
    items notNil ifTrue:[ items keysAndValuesDo:aTwoArgBlock ].

! !

!MenuPanel methodsFor:'event handling'!

buttonMotion:state x:x y:y
    "open or close the corresponding submenus
    "
    |menu point sensor sel|

    (    (sensor := self sensor) notNil
     and:[sensor hasButtonMotionEventFor:nil]
    ) ifTrue:[
	^ self
    ].

    sensor anyButtonPressed ifFalse:[
	"/ 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
    ].

    "/ ok, a button is pressed.
    (buttonEnteredBgColor ~= ButtonPassiveBackgroundColor
    or:[ButtonEnteredLevel ~~ ButtonPassiveLevel]) ifTrue:[
	self itemEntered:nil.
    ].

    lastButtonSelected notNil ifTrue:[
	^ 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
    ].

    menu := self superMenuAtX:x y:y.

    menu isNil ifTrue:[
       ^ self selection:nil
    ].
    point := self translatePoint:(x@y) to:menu.
    menu selection:(menu itemAtX:(point x) y:(point y))

    "Modified: / 22.8.1998 / 12:51:17 / cg"
!

buttonPress:button x:x y:y
    "any button pressed; open or close the corresponding submenus
    "
    |menu point item|

    menu := self superMenuAtX:x y:y.

    menu isNil ifTrue:[
	menu := self topMenu.
    ] ifFalse:[
	point := self translatePoint:(x@y) to:menu.
	item  := menu itemAtX:(point x) y:(point y)
    ].
    menu selection:item
!

buttonRelease:button x:x y:y
    "button release action; accept selection and close all views
    "
    |menu item|

    menu := self topMenu activeMenu.

    (    menu hasSelection
     or:[menu isPopUpView not
     or:[(OperatingSystem millisecondTimeDeltaBetween:(Time millisecondClockValue)
				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
	]
    ].

    "Modified: / 27.2.1998 / 17:41:23 / cg"
!

cursorPressed:aKey
    "handle a cursor key
    "
    |next submenu item
     n     "{ Class:SmallInteger }"
     idx   "{ Class:SmallInteger }"
     first "{ Class:SmallInteger }"
    |
    (self hasSelection not and:[superMenu notNil]) ifTrue:[
	^ superMenu cursorPressed:aKey
    ].

    self verticalLayout ifTrue:[
	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].        
    ].

    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
	].
      ^ self
    ].
    first := self findFirst:[:el| el canSelect ].
    first == 0 ifTrue:[^ self].

    idx := self selectionIndex.
    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.
            
	    idx < 1 ifTrue:[ idx := self findLast:[:el| el canSelect ] ]
	]
    ].
    self selectionIndex:idx
!

itemEntered:anItem
    |prevEnteredItem|

    anItem == enteredItem ifTrue:[^ self].

    prevEnteredItem := enteredItem.
    enteredItem := anItem.

    prevEnteredItem notNil ifTrue:[
	prevEnteredItem redraw
    ].
    enteredItem notNil ifTrue:[
	enteredItem redraw
    ].

    "Created: / 20.8.1998 / 13:18:23 / cg"
    "Modified: / 20.8.1998 / 14:03:55 / cg"
!

keyPress:key x:x y:y
    "any key is pressed
    "
    |listOfItems item menu idx cIdx upperKey lowerKey rawKey|

    menu := self.

    [ menu shown ] whileFalse:[
	(menu := superMenu) isNil ifTrue:[^ self]
    ].

    key == #Return ifTrue:[
	^ menu accept
    ].

    (     key == #CursorDown or:[key == #CursorUp
      or:[key == #CursorLeft or:[key == #CursorRight]]]
    ) ifTrue:[
	^ menu cursorPressed:key
    ].

    rawKey := device keyboardMap keyAtValue:key ifAbsent:key.

    listOfItems := self selectItemsForShortcutKey:rawKey.
    listOfItems isNil ifTrue:[
	listOfItems := self selectItemsForShortcutKey:key.
    ].
    listOfItems notNil ifTrue:[
	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
	]
    ].

    cIdx := menu selectionIndex.
    cIdx isNil ifTrue:[cIdx := 0].

    upperKey := key asUppercase.
    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
				    ]
				]
			    ]
			]
                        
		    ]
		]
	    ]
	]
    ].
    (item := menu itemAt:idx) isNil ifTrue:[
	menu hasSelection ifFalse:[
	    (menu := menu superMenu) isNil ifTrue:[
		^ super keyPress:key x:x y:y
	    ]
	]
    ].
    menu selection:item.

    "Modified: / 8.8.1998 / 13:38:36 / cg"
!

pointerLeave:state
    self itemEntered:nil.
    super pointerLeave:state

    "Created: / 20.8.1998 / 14:04:29 / cg"
!

sizeChanged:how
    self isFitPanel ifTrue:[
	self mustRearrange.
    ].
    super sizeChanged:how
! !

!MenuPanel methodsFor:'grabbing'!

forceUngrabMouseAndKeyboard
    "ungrab resources (mouse and keyboard)
    "
    |sensor|

    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
    ].
    device ungrabKeyboard.

    "Modified: / 2.2.1998 / 09:24:48 / stefan"
!

grabMouseAndKeyboard
    "get exclusive access to pointer and keyboard.
     Only used for popUp menus."

    |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
	    ]
	]
    ]

    "Modified: / 2.2.1998 / 23:43:59 / stefan"
!

ungrabMouseAndKeyboard
    "ungrab resources (mouse and keyboard)
    "
    |sensor|

    device activePointerGrab == self ifTrue:[
	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.
    ].

    "Modified: / 2.2.1998 / 10:27:12 / stefan"
! !

!MenuPanel methodsFor:'image registration'!

imageOnDevice:anImage
    "returns image registered on device
    "
    ^ self class image:anImage onDevice:device
!

lightenedImageOnDevice:anImage
    "returns lightened image registered on device
    "
    ^ self class lightenedImage:anImage onDevice:device
! !

!MenuPanel methodsFor:'initialize / release'!

addToCurrentProject
    "ignored here"

    ^self
!

create
    "create the shadow view for a none contained submenu
    "
    |style|

    self isPopUpView ifTrue:[
	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.
	    ].
	]
    ] ifFalse:[
	explicitExtent == true ifTrue:[
	    (self width) == (superView width) ifTrue:[
		self verticalLayout:false
	    ]
	]
    ]

    "Modified: / 28.7.1998 / 02:11:44 / cg"
!

destroy
    "destroy items and shadowView; remove dependencies
    "
    self clearLastActiveMenu.
    self do:[:el|el destroy].

    menuHolder    notNil ifTrue:[menuHolder    removeDependent:self].
    enableChannel notNil ifTrue:[enableChannel removeDependent:self].

    super destroy.
    superMenu := nil.
    items     := nil.
    shadowView notNil ifTrue:[shadowView destroy].

    "Modified: / 27.2.1998 / 17:41:25 / cg"
!

fetchDeviceResources
    "fetch device colors, to avoid reallocation at redraw time"

    |style|

    super fetchDeviceResources.

    style := styleSheet name.

    "/ thats a kludge - will be replaced by values from the styleSheet ...
    "/ (i.e. read menu.buttonActiveLevel & menu.buttonPassiveLevel)

    self isPopUpView ifFalse:[
	(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.
	    ]
	]
    ].

    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
	]
    ] 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.
    ].

    "Modified: / 20.8.1998 / 15:51:17 / cg"
!

initStyle
    "initialize style specific stuff"

    |style|

    super initStyle.

    self viewBackground:DefaultBackgroundColor.

    onLevel   := DefaultHilightLevel.
    offLevel  := DefaultLevel.
    itemSpace := DefaultItemSpace.

    groupDividerSize := DefaultGroupDividerSize.
    fitFirstPanel := DefaultFitFirstPanel.

    style := styleSheet name.

"/    style == #st80 ifTrue:[
"/        self level:0
"/    ] ifFalse:[
	self level:1.
"/    ].

    "Modified: / 5.9.1998 / 18:16:57 / cg"
!

initialize
    "set default configuration
    "
    |style|

    super initialize.

    enabled := true.
"/    self origin:0.0@0.0.
    originChanged  := extentChanged := false.
    explicitExtent := nil.
    shortKeyInset  := 0.
    mustRearrange  := false.
    self borderWidth:0.

    font := MenuView defaultFont.

    "Modified: / 20.8.1998 / 20:09:53 / cg"
!

mapped
    "grab the pointer here, when visible (but not if control has already been lost). 
     If the grab fails, try again and unmap myself if that fails too.
    "
    |anItemList|

    self enableMotionEvents.

    lastButtonSelected := nil.
    self becomesActiveMenu.
    super mapped.
    self do:[:anItem| anItem fetchImages ].

    anItemList := InitialSelectionQuerySignal raise.

    self isPopUpView ifTrue:[
	self grabMouseAndKeyboard
    ] ifFalse:[
"/        styleSheet is3D ifTrue:[self borderWidth:0].
	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.
    ].

    "Modified: / 2.2.1998 / 09:27:21 / stefan"
    "Modified: / 20.8.1998 / 19:17:07 / cg"
!

realize
    "realize menu and shadowView
    "

    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.
    ] ifFalse:[
	super realize.
    ]
!

recreate
    "this is called after a snapin. If the image was saved with an active menu,
     hide the menu
    "
    self selection:nil.
    super recreate.

!

reinitStyle
    "handle style change while being open (win32 only - for now)"

    super reinitStyle.

    self fetchDeviceResources.
    items notNil ifTrue:[
        items do:[:anItem |
            anItem reinitSubmenuStyle
        ]
    ]

    "Created: / 10.9.1998 / 21:37:05 / cg"
    "Modified: / 11.9.1998 / 13:20:57 / cg"
!

unmap
    "unmap view. If we have a popup supermenu, it will get all keyboard and
     mouse events.
    "

    self clearLastActiveMenu.

    "/
    "/ Kludge for X11: after grabbing and ungrabbing other views may get buttonMotionEvents
    "/ when a mouse button is still pressed. To avoid this we grab the mouse for the superview.
    "/ (Move from upperMenuPanel of NewLauncher to lowerMenuPanel)
    "/
    (superMenu notNil and:[superMenu shown and:[superMenu isPopUpView 
     or:[superMenu sensor anyButtonPressed]]]) ifTrue:[
	superMenu grabMouseAndKeyboard
    ] ifFalse:[
	self ungrabMouseAndKeyboard.
    ].
    super unmap.
    shadowView notNil ifTrue:[shadowView unmap].

    "Modified: / 2.2.1998 / 10:27:06 / stefan"
    "Modified: / 27.2.1998 / 17:41:24 / cg"
! !

!MenuPanel methodsFor:'misc'!

raiseDeiconified
    ^ self raise

    "Created: 21.6.1997 / 13:29:12 / cg"
!

superMenu
    "returns supermenu or nil
    "
    ^ superMenu


!

superMenu:aSuperMenu
    "set the supermenu starting from
    "
    superMenu := aSuperMenu.
!

topMenu
    "returns the topMenu; the one having no superMenu
    "
    |top|

    top := self.

    [ top superMenu notNil ] whileTrue:[
	top := top superMenu
    ].
  ^ top


! !

!MenuPanel methodsFor:'printing'!

printString
    "return a printed representation of the menu
    "
    |string label|

    string := 'Menu:'.

    self do:[:anItem|
	label  := anItem label ? ''.
	string := string ,' ', label printString.
    ].
    ^ string

    "Modified: / 27.2.1998 / 17:41:22 / cg"
! !

!MenuPanel methodsFor:'private'!

application
    |appl|

    superMenu notNil ifTrue:[
	^ superMenu application
    ].
    (appl := super application) isNil ifTrue:[
	windowGroup notNil ifTrue:[
	    appl := windowGroup mainGroup topViews first application
	]
    ].
  ^ appl
!

menuAdornmentAt:aSymbol
    "returns a value derived from adornment
    "
    |adm|

    adm := adornment ? DefaultAdornment.
  ^ adm at:aSymbol ifAbsent:nil
!

menuAdornmentAt:aSymbol put:something
    "sets a value for the specific menu; if the value differs to the
     current stored value, true is returned otherwise false
    "
    (self menuAdornmentAt:aSymbol) == something ifTrue:[
	^ false
    ].
    adornment isNil ifTrue:[
	adornment := DefaultAdornment copy
    ].
    adornment at:aSymbol put:something.
  ^ true
!

onEachPerform:aSelector withArgList:aList
    "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
	    ]
	]
    ] ifFalse:[
	self do:[:anItem| anItem perform:aSelector with:aList ]
    ]


!

openMenusFromItems:anItemList
    "open all menus derived from sequence of items
    "
    |item|

    (anItemList isNil or:[anItemList isEmpty]) ifTrue:[
	^ self
    ].
    item := anItemList removeLast.

    item enabled ifFalse:[
	^ self
    ].

    InitialSelectionQuerySignal answer:anItemList do:[
	self selection:item
    ]
!

selectItemsForShortcutKey:aKey
    "get sequence of items up to the item providing the key (inclusive). The
     first entry into the collection is the item providing the key, the last
     entry is the item in the topMenu( reverse )
    "
    |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
	    ]
	]
    ].
  ^ nil
        
!

translatePoint:aPoint to:aView
    "translate a point into a views point; in case of no view nil is returned
    "
    aView notNil ifTrue:[
	aView == self ifTrue:[^ aPoint].
      ^ device translatePoint:aPoint from:(self id) to:(aView id)
    ].
  ^ nil

! !

!MenuPanel methodsFor:'private activation'!

activeMenu
    "returns the current active menu or self (the top menu)
    "
    ^ lastActiveMenu ? self

    "Created: / 27.2.1998 / 17:41:15 / cg"
!

activeMenu:aMenu
    "set the current active menu
    "
    lastActiveMenu := aMenu

    "Created: / 27.2.1998 / 17:41:16 / cg"
!

becomesActiveMenu
    "submenu becomes the active menu
    "
    mapTime := Time millisecondClockValue.
    self topMenu activeMenu:self.

    "Created: / 27.2.1998 / 17:41:23 / cg"
!

clearLastActiveMenu
    "reset the current active menu
    "
    |top|

    top := self topMenu.

    top activeMenu == self ifTrue:[
	top activeMenu:nil
    ]

    "Created: / 27.2.1998 / 17:41:17 / cg"
!

mapTime
    "returns the time when the menu becomes active
    "
    ^ mapTime

    "Modified: / 27.2.1998 / 17:41:18 / cg"
! !

!MenuPanel methodsFor:'private searching'!

itemAtX:x y:y
    "returns item at a point or nil
    "
    self do:[:el| (el containsPointX:x y:y) ifTrue:[^el] ].
  ^ nil
!

superMenuAtX:x y:y
    "returns supermenu at a point or nil
    "
    |menu|

    (self containsPointX:x y:y) ifTrue:[^ self].
    menu := self.

    [ (menu := menu superMenu) notNil ] whileTrue:[
	(menu containsPoint:(self translatePoint:(x@y) to:menu)) ifTrue:[
	    ^ menu
	]
    ].
  ^ nil
! !

!MenuPanel methodsFor:'queries'!

canDrawItem
    "returns true if an item could be drawn otherwise false
    "
    ^ (mustRearrange not and:[shown])
!

containsPoint:aPoint
    "returns true if point is contained by the view
    "
    ^ self containsPointX:(aPoint x) y:(aPoint y)
!

containsPointX:x y:y
    "returns true if point is contained by the view
    "
    ^ (x between:0 and:width) and:[y between:0 and:height]

"/    |ext|
"/
"/    (x >= 0 and:[y >= 0]) ifTrue:[
"/        ext := self computeExtent.
"/      ^ (x < ext x and:[y < ext y])
"/    ].
"/    ^ false

    "Modified: / 29.1.1998 / 16:46:10 / cg"
!

hasGroupDividerAt:anIndex
    "returns true if a divider is defined at an index
    "
    |i|

    groupSizes size ~~ 0 ifTrue:[
	i := 0.

	groupSizes do:[:t|
	    (i := i + t) == anIndex ifTrue:[
		^ true
	    ]
	]
    ].
  ^ false

!

hasGroupDividers
    "returns true if any group divider exists
    "
  ^ (items size ~~ 0 and:[groupSizes size ~~ 0])
!

isEnabled
    "returns enabled state of menu and items
    "
    ^ self enabled
!

isFitPanel
    "returns true if the panel is the first in the menu hierarchy in must
     be fit to the extent of its superView
    "
    ^ self isPopUpView ifTrue:[false] ifFalse:[fitFirstPanel]
!

isPopUpView
    "return true if view is a popup view; without decoration
     and popUp to top immediately
    "
    ^ superView isNil


!

isVerticalLayout
    "returns true if vertical layout otherwise false( horizontal layout )
    "
  ^ self verticalLayout


!

type
    ^ nil.

! !

!MenuPanel methodsFor:'selection'!

hasSelection
    "returns true if a selection exists
    "
    ^ self selection notNil
!

isValidSelection:something
    "returns true if something could be selected
    "
    |item|

    enabled ifTrue:[
	(item := self itemAt:something) notNil ifTrue:[
	    ^ item canSelect
	]
    ].
  ^ false
!

selection
    "returns current selected item or nil
    "
    ^ selection


!

selection:anItemOrNil
    "change selection to an item
    "
    |item newSel hlp|

    selection isNumber ifTrue:[
	newSel := self itemAt:anItemOrNil
    ] ifFalse:[
	(anItemOrNil notNil and:[anItemOrNil canSelect]) ifTrue:[
	    newSel := anItemOrNil
	]
    ].

    selection == newSel ifTrue:[^ self].

    (item := selection) notNil ifTrue:[
	selection := nil.
	item selected:false.
    ].
    newSel notNil ifTrue:[
	selection := newSel.

"/ cg: thats rubbish - it will show help for my first item,
"/ but not the selected one ...
"/        ActiveHelp isActive ifTrue:[
"/            hlp := ActiveHelp currentHelpListener.
"/            hlp initiateHelpFor:self atX:1 y:1 now:true.
"/        ].
	selection selected:true.
    ].

    "Modified: / 2.2.1998 / 10:13:46 / stefan"
    "Modified: / 31.7.1998 / 03:14:18 / cg"
!

selectionIndex
    "returns index of current selection or 0
    "
    |item|

    (item := self selection) notNil ifTrue:[
	^ self findFirst:[:el| el == item ]
    ].
    ^ 0

!

selectionIndex:anIndex
    "set selection at an index
    "
    self selection:(self itemAt:anIndex)
! !

!MenuPanel::Item class methodsFor:'accessing'!

horizontalInset
    ^ HorizontalInset
!

labelRightOffset
    ^ LabelRightOffset
!

shortcutKeyOffset
    ^ ShortcutKeyOffset
!

verticalInset
    ^ VerticalInset
! !

!MenuPanel::Item class methodsFor:'defaults'!

separatorSize:aType
    "returns size of a separator
    "
    aType == #doubleLine ifTrue:[^ 10 ].
    aType == #singleLine ifTrue:[^ 10 ].
  ^ 10
!

updateStyleCache
    "setup defaults
     self updateStyleCache
    "
    HorizontalInset       := 4.
    VerticalInset         := 3.

    HorizontalButtonInset := 3.
    VerticalButtonInset   := 3.

    LabelRightOffset      := 15.
    ShortcutKeyOffset     := 5.

    IndicatorOn  := self checkedImage.
    IndicatorOff := self uncheckedImage.
! !

!MenuPanel::Item class methodsFor:'image specs'!

checkOffIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self checkOffIcon inspect
     ImageEditor openOnClass:self andSelector:#checkOffIcon
    "

    <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]!

checkOnIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self checkOnIcon inspect
     ImageEditor openOnClass:self andSelector:#checkOnIcon
    "

    <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]!

checkedImage
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self checkedImage inspect
     ImageEditor openOnClass:self andSelector:#checkedImage
    "

    <resource: #image>

    ^Icon
        constantNamed:#'MenuPanel::Item checkedImage'
        ifAbsentPut:[(Depth2Image new) width: 14; height: 14; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'****$H@@@MBEUUWP!!UUU4HUUT]BEUTGP!!ETA4HPTA]BD@AWP!!PAU4HUAU]BEUUWP/???4EUUUU@b') ; colorMapFromArray:#[0 0 0 255 255 255 127 127 127 170 170 170]; mask:((Depth1Image new) width: 14; height: 14; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??3??O?<??3??O?<??3??O?<??3??O?<??3??@@a') ; yourself); yourself]

    "Modified: / 6.9.1998 / 22:29:58 / cg"
!

uncheckedImage
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the ImageEditor may not be able to read the specification."

    "
     self uncheckedImage inspect
     ImageEditor openOnClass:self andSelector:#uncheckedImage
    "

    <resource: #image>

    ^Icon
        constantNamed:#'MenuPanel::Item uncheckedImage'
        ifAbsentPut:[(Depth2Image new) width: 14; height: 14; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUUUPG???8A0@@B@\@@@ G@@@HA0@@B@\@@@ G@@@HA0@@B@\@@@ G@@@HA0@@B@Z*** @@@@@@b') ; colorMapFromArray:#[255 255 255 127 127 127 170 170 170 0 0 0]; mask:((Depth1Image new) width: 14; height: 14; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??3??O?<??3??O?<??3??O?<??3??O?<??3??@@a') ; yourself); yourself]

    "Modified: / 6.9.1998 / 22:24:24 / cg"
! !

!MenuPanel::Item class methodsFor:'instance creation'!

in:aSuperMenu
    ^ self in:aSuperMenu label:nil
!

in:aSuperMenu label:aLabel
    |item|

    item := self new in:aSuperMenu.
    item label:aLabel.
  ^ item
!

in:aSuperMenu menuItem:aMenuItem
    |item|

    item := self in:aSuperMenu.
    item menuItem:aMenuItem.
  ^ item.
! !

!MenuPanel::Item methodsFor:'accept'!

canAccept
    "returns true if item is acceptable
    "
  ^ (self enabled and:[self hasSubmenu not])
!

toggleIndication
    "toggle indication or choice
    "
    |arg|

    self hasIndication ifTrue:[    
	arg := self indicationValue not.
	self indicationValue:arg.
    ] ifFalse:[
	self hasChoice ifTrue:[
	    arg := self choiceValue.
	    self choice value:arg.
	    arg := true.
	]
    ].
    ^ arg

    "Modified: / 14.8.1998 / 16:13:37 / cg"
! !

!MenuPanel::Item methodsFor:'accessing'!

accessCharacter
    "returns my accessCharacter or nil
    "
    accessCharacterPosition isNil ifTrue:[
	^ nil
    ].
  ^ (rawLabel string) at:accessCharacterPosition ifAbsent:nil
!

accessCharacterPosition
    "get the access character position or nil
    "
  ^ accessCharacterPosition
!

accessCharacterPosition:anIndex
    "set the access character position or nil
    "
    accessCharacterPosition ~~ anIndex ifTrue:[
	accessCharacterPosition := anIndex.
	self updateRawLabel.
    ].
!

activeHelpKey
    ^ activeHelpKey
!

activeHelpKey:aHelpKey
    activeHelpKey := aHelpKey
!

argument
    "gets the argument
    "
    adornment isNil ifTrue:[^ nil ].
  ^ adornment argument
!

argument:anArgument
    "sets the argument
    "
    self argument ~~ anArgument ifTrue:[
	self adornment argument:anArgument.
    ]
!

compareAccessCharacterWith:aKey
    "returns true if key is my access character
    "
    ^ self accessCharacter == aKey

!

label
    "returns the label
    "
    ^ label
!

label:aLabel
    "set a new label; if the label changed, a redraw is performed;
     handle characters $& (ST-80 compatibility)
    "
    |i rest s|

    accessCharacterPosition := nil.
    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.
	]
    ].

    self updateRawLabel

    "Modified: / 31.7.1998 / 00:52:26 / cg"
!

menuPanel
    "returns my menuPanel
    "
    ^ menuPanel
!

nameKey
    "gets the nameKey
    "
    ^ nameKey
!

nameKey:aNameKey
    "sets the nameKey
    "
    nameKey := aNameKey.
!

rawLabel
    "returns my printable Label
    "
    ^ rawLabel
!

shortcutKey
    "get the key to press to select the submenu from the keyboard or if
     no submenu exists evaluate the action assigned to the item (accept).
    "
    adornment isNil ifTrue:[^ nil ].
  ^ adornment shortcutKey
!

shortcutKey:aKey
    "set the key to press to select the submenu from the keyboard or if
     no submenu exists evaluate the action assigned to the item (accept).
    "
    self shortcutKey ~~ aKey ifTrue:[
	self adornment shortcutKey:aKey.
	self redraw.
    ].
!

startGroup
    "start group #left #right #center ... or nil
     at the moment only #right is implemented
    "
    ^ startGroup
!

startGroup:aSymbol
    "start group #left #right #center ...
     at the moment only #right is implemented
    "
    (startGroup isNil or:[startGroup == #right]) ifTrue:[
	startGroup := aSymbol
    ] ifFalse:[
	self warn:('not supported group: ', aSymbol printString ).
    ]

!

submenu
    "returns my submenu or nil
    "
    subMenu notNil ifTrue:[^ subMenu].
  ^ self setupSubmenu
!

submenu:aSubMenu
    "set a new submenu; an existing submenu will be destroyed. This might lead
     to a redraw if 'hasSubmenu' changed
    "

    (aSubMenu notNil 
     and:[(aSubMenu isView or:[aSubMenu isKindOf:Menu]) not]) ifTrue:[
	^ 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
	]
    ].

    "Modified: / 10.8.1998 / 13:26:28 / cg"
!

textLabel
    "returns my textLabel or nil if none text
    "
    (rawLabel respondsTo:#string) ifTrue:[
	^ rawLabel string
    ].
  ^ nil
!

value
    "gets value
    "
    ^ value
!

value:something
    "could be a value holder, an action or selector
    "
    value := something.
!

value:aValue argument:anArgument
    "set the value and an argument
    "
    self value:aValue.
    self argument:anArgument.
! !

!MenuPanel::Item methodsFor:'accessing behavior'!

choice
    "get choice indication
    "
    adornment isNil ifTrue:[^ nil].
  ^ adornment choice

    "Created: / 14.8.1998 / 14:38:52 / cg"
!

choice:something
    "set choice indication
    "
    |old new|

    old := self choice.
    old == something ifTrue:[^ self].

    (self isKindOfValueHolder:old) ifTrue:[
	old removeDependent:self
    ].

    new := something.
    new isSymbol ifTrue:[
	new := self aspectAt:new.
	new isNil ifTrue:[
	    new := something
	]
    ].
    (self isKindOfValueHolder:new) ifTrue:[
	new addDependent:self
    ].
    self adornment choice:new.
    self updateRawLabel.

    "Created: / 14.8.1998 / 14:39:11 / cg"
    "Modified: / 14.8.1998 / 16:13:19 / cg"
!

choiceValue
    "get choice value
    "
    adornment isNil ifTrue:[^ nil].
  ^ adornment choiceValue

    "Created: / 14.8.1998 / 15:46:33 / cg"
!

choiceValue:something
    "set choice value
    "
    |old|

    self adornment choiceValue:something.
    self updateRawLabel.

    "Created: / 14.8.1998 / 15:46:59 / cg"
!

enabled
    "returns the enabled state
    "
    |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
	].
      ^ state ~~ false
    ].
    ^ false
!

enabled:something
    "change the enabled state; if the state changed, a redraw is performed
    "
    |oldState newState|

    enableChannel isNil ifTrue:[
	oldState := true
    ] ifFalse:[
	oldState := enableChannel value.
	(self isKindOfValueHolder:enableChannel) ifTrue:[
	    enableChannel removeDependent:self
	]
    ].
    enableChannel := something.

    enableChannel isNil ifTrue:[
	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.
    ].

    newState ~~ oldState ifTrue:[
	(rawLabel notNil and:[menuPanel canDrawItem]) ifTrue:[
	    self drawLabel
	]
    ]

    "Modified: / 27.10.1997 / 16:13:42 / cg"
!

indication
    "get on/off indication
    "
    adornment isNil ifTrue:[^ nil].
  ^ adornment indication
!

indication:something
    "set on/off indication
    "
    |old|

    old := self indication.
    old == something ifTrue:[^ self].

    (self isKindOfValueHolder:old) ifTrue:[
	old removeDependent:self
    ].

    (self isKindOfValueHolder:something) ifTrue:[
	something addDependent:self
    ].
    self adornment indication:something.
    self updateRawLabel.
!

isButton
    "returns whether item looks like a Button
    "
    ^ isButton
!

isButton:anBoolean
    "sets whether item looks like a Button
    "
    isButton := anBoolean.

    layout notNil ifTrue:[
	self redrawAsButton
    ]



!

submenuChannel
    "get the submenu channel
    "
  ^ submenuChannel
!

submenuChannel:aSelectorOrNil
    "returns the submenu channel
    "
    submenuChannel := aSelectorOrNil.
! !

!MenuPanel::Item methodsFor:'accessing dimension'!

height
    "gets height
    "
    layout isNil ifTrue:[
	^ self preferredExtent y
    ].
    ^ layout height
!

horizontalInset

    isButton ifTrue: [^menuPanel buttonPassiveLevel + HorizontalButtonInset].
    ^HorizontalInset
!

layout
    "returns my layout ( Rectangle )
    "
    ^ layout
!

layout:aLayout
    "set a new layout ( Rectangle )
    "
    layout := aLayout.
    self redraw.
!

verticalInset

    isButton ifTrue: [^menuPanel buttonPassiveLevel + VerticalButtonInset].
    ^VerticalInset
!

width
    "gets width
    "

    layout isNil ifTrue:[
	^ self preferredExtent x
    ].
    ^ layout width
! !

!MenuPanel::Item methodsFor:'building'!

aspectAt:aKey
    "retursns value assigned to key or nil
    "
    |appl value|

    appl := menuPanel receiver.

    (appl isKindOf:ValueModel) ifTrue:[
	^ 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]
	]
    ].
    ^ value

    "Modified: / 29.7.1998 / 11:59:50 / cg"
! !

!MenuPanel::Item methodsFor:'change & update'!

choiceChanged
    "called when the choice changed
    "
    |indicator|

    isButton ifFalse:[
	indicator := self choiceForm.

	indicator = rawLabel icon ifTrue:[
	    ^ self
	].
	rawLabel icon:indicator.

	disabledRawLabel notNil ifTrue:[
	    disabledRawLabel icon:indicator
	]
    ].
    self redraw

    "Created: / 14.8.1998 / 16:14:59 / cg"
    "Modified: / 14.8.1998 / 17:19:32 / cg"
!

enabledStateOfMenuChangedTo:aState
    "enabled state of menu changed to aState
    "
    rawLabel notNil ifTrue:[
	self drawLabel
    ].

!

indicationChanged
    "called when the indication changed
    "
    |indicator|

    isButton ifFalse:[
	indicator := self indicatorForm.

	indicator = rawLabel icon ifTrue:[
	    ^ self
	].
	rawLabel icon:indicator.

	disabledRawLabel notNil ifTrue:[
	    disabledRawLabel icon:indicator
	]
    ].
    self redraw

    "Modified: / 14.8.1998 / 17:19:38 / cg"
!

update:something with:aParameter from:changedObject
    |indicator|

    changedObject == self indication ifTrue:[
	^ self indicationChanged
    ].

    changedObject == self choice ifTrue:[
	^ self choiceChanged
    ].

    changedObject == enableChannel ifTrue:[
	(rawLabel notNil and:[menuPanel canDrawItem]) ifTrue:[
	    self drawLabel
	].
	^ self
    ].

    changedObject == isVisible ifTrue:[
	^ menuPanel mustRearrange
    ].

    super update:something with:aParameter from:changedObject

    "Modified: / 14.8.1998 / 16:13:41 / cg"
!

updateIndicators
    "update indicators
    "
    |indicator| 

    (indicator := self indication) notNil ifTrue:[
"/        (isButton and:[menuPanel isPopUpView]) ifFalse:[
"/            (self isKindOfValueHolder:indicator) ifTrue:[
"/                ^ self
"/            ]
"/        ].
	self indicationChanged
    ]

    "Modified: / 14.8.1998 / 15:19:38 / cg"
! !

!MenuPanel::Item methodsFor:'converting'!

asMenuItem
    "convert to a MenuItem
    "
    |item label rcv|

    label := self label.
    item  := MenuItem labeled:(label printString).

    label isImage ifTrue:[
	rcv := ResourceRetriever new.
	rcv className:#MenuEditor.
	rcv selector:#iconUnknown.
	item labelImage:rcv.
    ].

    item activeHelpKey:activeHelpKey.

    enableChannel notNil ifTrue:[
	item enabled:(enableChannel value)
    ].

    item accessCharacterPosition:(self accessCharacterPosition).
    item startGroup:(self startGroup).
    item argument:(self argument).
    item nameKey:(self nameKey).
    item shortcutKeyCharacter:(self shortcutKey).
    item value:(value value).
    item indication:(self indication value).
    item choice:(self choice value).
    item choiceValue:(self choiceValue).
    item isVisible:(self isVisible).
    item isButton:isButton.

    submenuChannel isSymbol ifTrue:[
	item submenuChannel:submenuChannel
    ] ifFalse:[
	self submenu notNil ifTrue:[
	    item submenu:(self submenu asMenu)
	]
    ].
  ^ item

    "Modified: / 14.8.1998 / 15:47:21 / cg"
!

menuItem:aMenuItem
    "setup attributes from a MenuItem
    "
    |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).
    ]

    "Modified: / 22.8.1998 / 15:34:16 / cg"
! !

!MenuPanel::Item methodsFor:'drawing'!

drawLabel
    "draw label
    "
    |y x h l t scKey cLb cLa img fg asc arrow hrzInset 
     buttonLevel isSelected clr|

    self isVisible ifFalse:[^ self].

    img := rawLabel.

    asc := menuPanel font ascent.
    h   := layout height.
    l   := layout left.
    t   := layout top.
    hrzInset := self horizontalInset.
    isSelected := self drawSelected.

    self enabled ifTrue:[
        fg := isSelected ifTrue:[self activeForegroundColor]
                        ifFalse:[menuPanel foregroundColor].
    ] ifFalse:[
        fg := menuPanel disabledForegroundColor.

        (img := disabledRawLabel) isNil ifTrue:[
            img := self disabledRawLabel
        ]
    ].
    menuPanel paint:fg.

    "/ t := t + menuPanel level.
    y := t + ((h - (img heightOn:menuPanel)) // 2).

    (self textLabel) notNil ifTrue:[
        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
            ]
        ].
        buttonLevel ~~ 0 ifTrue:[
            menuPanel 
                drawButtonEdgesInLayout:layout 
                withLevel:buttonLevel
                selected:isSelected.
        ].
        ^ self
    ].

"/ label = 'Sort By Name' ifTrue:[self halt.].

    img displayOn:menuPanel x:(l + hrzInset) y:y.

    "/ 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. 
            ].
        ].
    ].

    "/ 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. 
    ]

    "Modified: / 6.9.1998 / 21:48:53 / cg"
!

drawSelected
    "return true if item is selected or if item implements
     a toggle in a radio group which is selected
    "
    |holder|

    self isSelected ifTrue:[
	^ true
    ].
    isButton ifTrue:[
	^ ((holder := self choice) notNil and:[holder value = self choiceValue])
    ].
    ^ false
!

redraw
    "redraw item
    "
    |isSelected ownBgCol showItemSep type paint lgCol shCol
     h  "{ Class:SmallInteger }"
     w  "{ Class:SmallInteger }"
     l  "{ Class:SmallInteger }"
     t  "{ Class:SmallInteger }"
     r  "{ Class:SmallInteger }"
     b  "{ Class:SmallInteger }"
     x  "{ Class:SmallInteger }"
     y  "{ Class:SmallInteger }"
     hrzInset "{ Class:SmallInteger }"
     isEntered
    |

    (self isVisible and:[menuPanel canDrawItem]) ifFalse:[
	^ self
    ].

    isSelected := self drawSelected.
    isEntered := self isEntered.
    hrzInset   := self horizontalInset.

    isSelected ifFalse:[
	(isButton and:[isEntered]) ifTrue:[
	    paint := self buttonEnteredBackgroundColor
	] ifFalse:[
	    paint := self backgroundColor
	]
    ] ifTrue:[
	paint := self activeBackgroundColor
    ].
    l := layout left.
    t := layout top.
    r := layout right.
    b := layout bottom.
    h := layout height.
    w := layout width.
    (ownBgCol := self backgroundColorFromLabel) isNil ifTrue:[
	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.
       ].
    ].
    lgCol       := menuPanel lightColor.
    shCol       := menuPanel shadowColor.
    showItemSep := menuPanel showSeparatingLines.
    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
    ].

    isButton ifTrue:[
	^ 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.
	    ] 
	]
    ].

    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).  
    ].

    menuPanel drawEdgesForX:l y:t width:w height:h isSelected:isSelected isEntered:isEntered.

    "Modified: / 20.8.1998 / 15:11:33 / cg"
! !

!MenuPanel::Item methodsFor:'initialization'!

destroy
    "destroy submenus, remove dependencies
    "
    |channel|

    self submenu:nil.

    (enableChannel notNil and:[self isKindOfValueHolder:enableChannel]) ifTrue:[
	enableChannel removeDependent:self
    ].

    (isVisible notNil and:[self isKindOfValueHolder:isVisible]) ifTrue:[
	isVisible removeDependent:self
    ].

    channel := self indication.
    (channel notNil and:[self isKindOfValueHolder:channel]) ifTrue:[
	channel removeDependent:self
    ].
    channel := self choice.
    (channel notNil and:[self isKindOfValueHolder:channel]) ifTrue:[
	channel removeDependent:self
    ].

    menuPanel := nil.

    "Modified: / 14.8.1998 / 14:37:57 / cg"
!

in:aPanel
    "create item in a menuPanel
    "
    menuPanel := aPanel.
    isButton  := false.
! !

!MenuPanel::Item methodsFor:'label basics'!

disabledRawLabel
    "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)
		]
	    ]
	]
    ].
    ^ disabledRawLabel
!

fetchImages
    "fetch images
    "
    |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)
		    ]
		]
	    ]
	]
    ].
!

updateRawLabel
    "recreate rawLabel
    "
    |char size form|

    label isNil ifTrue:[        "/ not yet initialized
	^ self
    ].

    (form := self indicatorForm) isNil ifTrue:[
	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 isImage ifTrue:[
	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.
	    ]
	].
    ].
    menuPanel shown ifTrue:[ self fetchImages ].
    menuPanel mustRearrange
! !

!MenuPanel::Item methodsFor:'private'!

activeBackgroundColor
    "returns the active background color derived from menuPanel
    "

    isButton ifTrue: [^menuPanel buttonActiveBackgroundColor].
    ^menuPanel activeBackgroundColor
!

activeForegroundColor
    "returns the active foreground color derived from menuPanel
    "

    ^menuPanel activeForegroundColor
!

adornment
    "returns adornment; if not existing yet a new instance
     is created
    "
    adornment isNil ifTrue:[
	adornment := Adornment new
    ].
  ^ adornment
!

backgroundColor
    "returns the background color derived from menuPanel
    "

    isButton ifTrue: [^menuPanel buttonPassiveBackgroundColor].
    ^menuPanel backgroundColor
!

backgroundColorFromLabel
    "returns the background color derived from label or nil
    "
    |run|

    label isText ifFalse:[^ nil ].
    run := label emphasis.
    run size == 0 ifTrue:[^ nil ].

    run := run first.

    run size == 0 ifTrue:[
	(run value isColor and:[run key == #backgroundColor]) ifTrue:[
	    ^ run value
	]
    ] ifFalse:[
	run do:[:r|
	    (r value isColor and:[r key == #backgroundColor]) ifTrue:[
		^ r value
	    ]
	]
    ].
  ^ nil
!

buttonEnteredBackgroundColor
    "returns the background color to use when thhe mouse has entered 
     derived from menuPanel
    "

    isButton ifTrue: [^ menuPanel buttonEnteredBackgroundColor].
    ^ menuPanel backgroundColor

    "Created: / 20.8.1998 / 13:56:10 / cg"
!

choiceForm
    "returns choice form or nil
    "
    |holder|

    (holder := self choice) isNil ifTrue:[^ nil].

    holder value = self choiceValue ifTrue:[
	^ self class checkOnIcon
    ].
    ^ self class checkOffIcon
!

findSubMenuIn:aRecv
    "ask the receiver for a submenu aspect, sending it
     #aspectFor: first; then trying the selector itself.
     Ignore the error if that message is not understood
     (but not other message-not-understoods)"

    |subm argument sel|

    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
		    ]
		]
	    ]
	]
    ].
    ^ subm

    "Modified: / 4.8.1998 / 17:40:09 / cg"
!

indicationValue
    "returns indication value or nil in case of no indication
    "
    |indication numArgs sel recv|

    (indication := self indication) isNil ifTrue:[
	^ 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:[
"/                                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.
	]
    ].
    ^ indication value == true

    "Modified: / 8.8.1998 / 02:15:15 / cg"
!

indicationValue:aValue
    "returns indication value or nil
    "
    |numArgs indication recv|

    (indication := self indication) isNil ifTrue:[
	^ self                                          "/ has no indication
    ].

    indication isSymbol ifFalse:[
	(self isKindOfValueHolder:indication) ifTrue:[  "/ is value holder
	    indication value:aValue
	].
	^ self
    ].
    recv := menuPanel receiver.

    (recv isKindOf:ValueModel) ifTrue:[
	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
		]
	    ]
	]
    ].

    "Modified: / 28.7.1998 / 20:47:08 / cg"
!

indicatorForm
    "returns indication form or nil
    "
    |value|

    (value := self indicationValue) isNil ifTrue:[
	^ nil
    ].
  ^ value ifTrue:[IndicatorOn] ifFalse:[IndicatorOff]

    "Created: / 14.8.1998 / 15:53:53 / cg"
!

isEntered
    "returns true if the mouse pointer is over the item
    "
    ^ menuPanel enteredItem == self

    "Created: / 20.8.1998 / 13:11:50 / cg"
!

reinitSubmenuStyle
    "returns my submenu or nil
    "
    subMenu notNil ifTrue:[
        subMenu reinitStyle
    ].

    "Created: / 10.9.1998 / 21:36:09 / cg"
!

separatorType
    "returns type of separator line or nil
    "
    |c lbl|

    rawLabel isNil ifFalse:[
	^ nil
    ].

    (lbl := label value) isNil ifTrue:[
	^ #singleLine
    ].

    lbl size == 1 ifTrue:[
	c := lbl first.
	c == $- ifTrue:[^ #singleLine].
	c == $= ifTrue:[^ #doubleLine].
    ].
  ^ #blankLine
!

setupSubmenu
    |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.
    ].

    ^ subMenu

    "Modified: / 19.5.1998 / 19:36:56 / cg"
! !

!MenuPanel::Item methodsFor:'queries'!

canSelect
    "returns true if item is selectable
    "
    |holder|

    (self isVisible and:[self enabled and:[rawLabel notNil]]) ifTrue:[
	((holder := self choice) isNil or:[holder value ~= self choiceValue]) ifTrue:[
	    ^ true
	].
    ].
    ^ false
!

containsPointX:x y:y
    "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]]]
	  )
    ].
    ^ false
!

hasChoice
    "returns true if a choice indication (RadioButton) exists
    "
  ^ self choice notNil

    "Created: / 14.8.1998 / 14:38:20 / cg"
!

hasIndication
    "returns true if on/off indication exists
    "
  ^ self indication notNil
!

hasSubmenu
    "returns true if a submenu exists
    "
    ^ self submenu notNil
!

isEnabled
    "returns enabled state
    "
    ^ self enabled
!

isKindOfValueHolder:something
    "returns true if something is kind of vlaue holder
    "
    ^ ((something respondsTo:#value:) and:[something isBlock not])





!

isSeparator
    "returns true if item is a separator
    "
    ^ rawLabel isNil
!

isVisible
    "returns the visibility state
    "
    |state|

    isVisible isSymbol ifTrue:[
	state := self aspectAt:isVisible.

	(self isKindOfValueHolder:state) ifTrue:[
	    isVisible := state.
	    isVisible addDependent:self.
	    state := isVisible value.
	]
    ] ifFalse:[
	state := isVisible value
    ].
  ^ state ~~ false

!

isVisible:something
    "change the state; if the state changed, a redraw is performed
    "
    |oldState newState|

    isVisible isNil ifTrue:[
	oldState := true
    ] ifFalse:[
	oldState := isVisible value.
	(self isKindOfValueHolder:isVisible) ifTrue:[
	    isVisible removeDependent:self
	]
    ].
    isVisible := something.

    isVisible isNil ifTrue:[
	newState := true
    ] ifFalse:[
	(self isKindOfValueHolder:isVisible) ifTrue:[
	    isVisible addDependent:self
	] ifFalse:[
	    isVisible isSymbol ifTrue:[^ self]
	].
	menuPanel shown ifFalse:[^ self].
	newState := isVisible value.
    ].

    newState ~~ oldState ifTrue:[
	menuPanel mustRearrange
    ]
!

preferredExtent
    "compute my preferred extent
    "
    |x y s isVertical sepSize|

    self isVisible ifFalse:[^ (0 @ 0) ].

    x := self horizontalInset * 2.
    y := self verticalInset * 2.

    isVertical := menuPanel verticalLayout.

    self isSeparator ifFalse:[
	x := x + (rawLabel widthOn:menuPanel).
	y := y + (rawLabel heightOn:menuPanel).

	MenuView showAcceleratorKeys == true ifTrue:[
	    isVertical ifTrue:[ "/ only for vertical menus ...
		(s := self shortcutKeyAsString) notNil ifTrue:[
		    x := x + LabelRightOffset + (s widthOn:menuPanel)
		].
	    ].
	].
	(isVertical and:[self hasSubmenu 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
	].
    ].

    ^ (x @ y)

    "Modified: / 8.8.1998 / 01:38:26 / cg"
!

preferredExtentX
    "compute my preferred extent x
    "
    ^ self preferredExtent x

!

shortcutKeyAsString
    "converts shortcutKey to a text object
    "
    |nm key prefix|

    (key := self shortcutKey) isNil ifTrue:[
	^ nil
    ].

    key isCharacter ifTrue:[
	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
	]
    ].
    ^ nm

    "Modified: / 17.7.1998 / 11:56:40 / cg"
!

shortcutKeyPrefixFor:aModifier
    "returns prefix assigned to a modifier
    "
    |m|

    m := menuPanel device modifierKeyTopFor:aModifier.
    m notNil ifTrue:[
	^ m , '-'
    ].
    ^ aModifier , '-'.

    "Modified: / 17.7.1998 / 11:56:46 / cg"
! !

!MenuPanel::Item methodsFor:'selection'!

hideSubmenu
    "hide submenu
    "
    |subMenu id|

    subMenu := self submenu.
    subMenu realized ifFalse:[
	(id := subMenu id) notNil ifTrue:[
	    menuPanel device unmapWindow:id
	]
    ] ifTrue:[
       subMenu hide
    ].

    subMenu windowGroup:nil.
    menuPanel windowGroup removeView:subMenu.

    "Modified: / 14.8.1998 / 17:36:01 / cg"
!

isSelected
    "returns true if item is selected
    "
    ^ menuPanel selection == self
!

openSubmenuAt:aPoint
    "open submenu at a point
    "
    |top windowGrp subMenu|

    windowGrp := menuPanel topMenu windowGroup.
    subMenu   := self setupSubmenu.
    subMenu isNil ifTrue:[
	^ self
    ].
    subMenu font:(menuPanel topMenu font).
    subMenu becomesActiveMenu.

    windowGrp notNil ifTrue:[
	subMenu windowGroup:windowGrp.
	windowGrp addTopView:subMenu.
    ].
    subMenu fixSize.
    subMenu origin:aPoint.
"/    subMenu makeFullyVisible.
    top := menuPanel topMenu.

    subMenu realized ifFalse:[
	subMenu realize. 
    ] ifTrue:[
	top device mapWindow:subMenu id.
    ].
    subMenu makeFullyVisible.


"/    (top styleSheet at:'menu.autoSelectFirst') ifTrue:[
"/        subMenu selectionIndex:1
"/    ]

    "Modified: / 19.5.1998 / 19:37:37 / cg"
!

selected:aState
    "change selection to a state. Dependant on the state open or hide an existing
     submenu and perform a redraw
    "
    |p d subMenu|

    subMenu := self submenu.

    aState ifFalse:[
	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 verticalLayout ifTrue:[p := (layout right - 4) @ (layout top)]
			    ifFalse:[p := (layout left)  @ (layout bottom)].

    d := menuPanel device.
    p := d translatePoint:p from:(menuPanel id) to:(d rootWindowId).
    self openSubmenuAt:p.

    "Modified: / 2.2.1998 / 10:17:41 / stefan"
    "Modified: / 5.8.1998 / 00:15:36 / cg"
! !

!MenuPanel::Item::Adornment methodsFor:'accessing'!

accessCharacterPosition
    "get the index of the access character in the label text or string, or nil if none
    "
    ^ accessCharacterPosition
!

accessCharacterPosition:anIndexOrNil
    "set the index of the access character in the label text or string, or nil if none
    "
    accessCharacterPosition := anIndexOrNil
!

argument
    "ST/X goody; get argunment to a selector or block
    "
  ^ argument
!

argument:anArgumentOrNil
    "ST/X goody; set argunment to a selector or block
    "
    argument := anArgumentOrNil
!

choice
    "get has choice indicator value
    "
  ^ choice

    "Created: / 14.8.1998 / 14:41:31 / cg"
!

choice:something
    "set choice indicator value
    "
    choice := something.

    "Created: / 14.8.1998 / 14:41:39 / cg"
!

choiceValue
    "return the value of the instance variable 'choiceValue' (automatically generated)"

    ^ choiceValue

    "Created: / 14.8.1998 / 15:47:52 / cg"
!

choiceValue:something
    "set the value of the instance variable 'choiceValue' (automatically generated)"

    choiceValue := something.

    "Created: / 14.8.1998 / 15:47:52 / cg"
!

indication
    "get has on/off indicator value
    "
  ^ indication
!

indication:something
    "set has on/off indicator value
    "
    indication := something.
!

shortcutKey
    "get the character that is used as a shortcut key for this item
    "
  ^ shortcutKey
!

shortcutKey:aKeyOrNil
    "set the character that is used as a shortcut key for this item
    "
    shortcutKey := aKeyOrNil
! !

!MenuPanel class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/MenuPanel.st,v 1.127 1998-09-11 12:04:52 cg Exp $'
! !
MenuPanel initialize!