PullDownMenu.st
author claus
Fri, 12 May 1995 20:25:18 +0200
changeset 127 462396b08e30
parent 119 59758ff5b841
child 128 06a050529335
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      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:#PullDownMenu
       instanceVariableNames:'menus titles selectors activeMenuNumber
			      showSeparatingLines topMargin
			      fgColor bgColor activeFgColor activeBgColor
			      onLevel offLevel edgeStyle
			      keepMenu toggleKeep'
       classVariableNames:'DefaultFont
			   DefaultViewBackground 
			   DefaultForegroundColor 
			   DefaultBackgroundColor
			   DefaultHilightForegroundColor 
			   DefaultHilightBackgroundColor
			   DefaultLevel DefaultHilightLevel
			   DefaultShadowColor DefaultLightColor 
			   DefaultEdgeStyle DefaultKeepMenu DefaultToggleKeep'
       poolDictionaries:''
       category:'Views-Menus'
!

PullDownMenu comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	     All Rights Reserved

$Header: /cvs/stx/stx/libwidg/PullDownMenu.st,v 1.17 1995-05-03 00:37:05 claus Exp $
'!

!PullDownMenu class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      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.
"
!

version
"
$Header: /cvs/stx/stx/libwidg/PullDownMenu.st,v 1.17 1995-05-03 00:37:05 claus Exp $
"
!

documentation
"
    PullDown menu provides the top (always visible) part of these menus. 
    It controls display of its menus, which become visible when one of the 
    PullDownMenus entries is pressed.

    Instance variables:

      menus                   <aCollection>   the sub menus
      titles                  <aCollection>   the strings in the menu
      activeMenuNumber        <Number>        the index of the currently active menu
      showSeparatingLines     <Boolean>       show separating lines between my menu-strings
      topMargin               <Number>        number of pixels at top
      fgColor                 <Color>         color to draw passive menu-titles
      bgColor                 <Color>         color to draw passive menu-titles
      activeFgColor           <Color>         color to draw activated menu-titles
      activeBgColor           <Color>         color to draw activated menu-titles
      onLevel                 <Integer>       level of entry-buttons when pressed
      offLevel                <Integer>       level of entry-buttons when released
      keepmenu                <Boolean>       if on, pulled menu stays on click,
					      till clicked again (motif & windows behavior)


    StyleSheet values:

      pullDownMenuViewBackground              view background Color for the menu bar
					      default: menuViewBackground

      pullDownMenuForegroundColor             foreground drawing color for the menu bar
					      default: menuForegroundColor

      pullDownMenuBackgroundColor             background drawing color for the menu bar
					      default: menuBackgroundColor

      pullDownMenuHilightForegroundColor      active foreground drawing color for the menu bar
					      default: menuHilightForegroundColor

      pullDownMenuHilightBackgroundColor      active background drawing color for the menu bar
					      default: menuHilightBackgroundColor

      pullDownMenuHilightLevel                level (3D only) when active
					      default: menuHilightLevel

      pullDownMenuEdgeStyle                   edge style (nil or #soft)

      pullDownMenuKeepMenu                    if true, pulled menu stays open until button
					      is pressed again (motif behavior)
					      if false, menu closes on release (default)

      pullDownMenuToggleKeep                  if true, pulled menu closes when an entry is pressed
					      again. Otherwise, only press outside outside of
					      the entry hides it.
					      default is false

      pullDownMenuLevel                       level (3D only)

      pullDownMenuFont                        font to use for the menu bar
					      default: menuFont
"
!

examples 
"
    |top menu|

    top := StandardSystemView new.
    menu := PullDownMenu origin:0.0@0.0 corner:1.0@30 in:top.
    menu labels:#('foo' 'bar').
    menu selectors:#(foo bar).
    menu at:#foo
	 putLabels:#('foo1' 'foo2' 'foo3')
	 selectors:#(foo1 foo2 foo3)
	 receiver:nil.
    menu at:#bar 
	 putLabels:#('bar1' 'bar2' 'bar3')
	 selectors:#(bar1 bar2 bar3)
	 receiver:nil.
    top open



    'empty entries are possible ...'

    |top menu|

    top := StandardSystemView new.
    menu := PullDownMenu origin:0.0@0.0 corner:1.0@30 in:top.
    menu labels:#('foo' 'bar').
    menu selectors:#(foo bar).
    menu at:#foo
	 putLabels:#('foo1' 'foo2' 'foo3')
	 selectors:#(foo1 foo2 foo3)
	 receiver:nil.
    top open



    '... for example as separators'

    |top menu|

    top := StandardSystemView new.
    menu := PullDownMenu origin:0.0@0.0 corner:1.0@30 in:top.
    menu labels:#('foo' '    ' 'bar' ' baz' '    ' 'moreFoo' 'moreBar' 'moreBaz').
    menu selectors:#(foo nil bar baz nil moreFoo moreBar moreBaz).
    menu showSeparatingLines:true.
    menu at:#foo
	 putLabels:#('foo1' 'foo2' 'foo3')
	 selectors:#(foo1 foo2 foo3)
	 receiver:nil.
    menu at:#bar 
	 putLabels:#('bar1' 'bar2' 'bar3')
	 selectors:#(bar1 bar2 bar3)
	 receiver:nil.
    menu at:#baz 
	 putLabels:#('baz1' 'baz2' 'baz3')
	 selectors:#(baz1 baz2 baz3)
	 receiver:nil.
    top open




    'use menus default height'

    |top menu|

    top := StandardSystemView new.
    menu := PullDownMenu in:top.
    menu origin:0.0@0.0 corner:1.0@(menu height).
    menu labels:#('foo' 'bar').
    menu selectors:#(foo bar).
    menu at:#foo
	 putLabels:#('foo1' 'foo2' 'foo3')
	 selectors:#(foo1 foo2 foo3)
	 receiver:nil.
    top open




    'although you can change the font, colors etc (as shown below)
     you should NOT do it - since if you do so, the styleSheet settings
     are ineffective (which users wont like probably)
     BTW: The styleSheet entries for below are pullDownMenuForegroundColor,
	  pullDownMenuBackgroundColor and pullDownMenuFont'

    |top menu|

    top := StandardSystemView new.
    menu := PullDownMenu in:top.
    menu font:(Font family:'courier' size:20).
    menu foregroundColor:Color red.
    menu backgroundColor:Color yellow.
    menu viewBackground:Color yellow.
    menu showSeparatingLines:true.

    menu origin:0.0@0.0 corner:1.0@(menu height).
    menu labels:#('foo' 'bar').
    menu selectors:#(foo bar).
    menu at:#foo
	 putLabels:#('foo1' 'foo2' 'foo3')
	 selectors:#(foo1 foo2 foo3)
	 receiver:nil.
    (menu menuAt:#foo) font:(Font family:'courier' size:36).
    top open



    'you can use icons, too ...'

    |labels top menu|

    top := StandardSystemView new.
    menu := PullDownMenu in:top.
    menu origin:0.0@0.0 corner:1.0@(menu height).
    labels := Array with:(Image fromFile:'SmalltalkX.xbm')
		    with:'foo'
		    with:'bar'.
    menu labels:labels.
    menu selectors:#(about foo bar).
    menu at:#about 
	 putLabels:#('about PullDownMenus')
	 selectors:#(aboutMenus)
	 receiver:nil.
    menu at:#foo
	 putLabels:#('foo1' 'foo2' 'foo3')
	 selectors:#(foo1 foo2 foo3)
	 receiver:nil.
    top open
"
! !

!PullDownMenu class methodsFor:'defaults'!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables"

    DefaultViewBackground := StyleSheet colorAt:'pullDownMenuViewBackground'.
    DefaultViewBackground isNil ifTrue:[
	DefaultViewBackground := StyleSheet colorAt:'menuViewBackground'.
    ].
    DefaultForegroundColor := StyleSheet colorAt:'pullDownMenuForegroundColor'.
    DefaultForegroundColor isNil ifTrue:[
	DefaultForegroundColor := StyleSheet colorAt:'menuForegroundColor'.
    ].
    DefaultBackgroundColor := StyleSheet colorAt:'pullDownMenuBackgroundColor'.
    DefaultBackgroundColor isNil ifTrue:[
	DefaultViewBackground notNil ifTrue:[
	    DefaultBackgroundColor := DefaultViewBackground
	] ifFalse:[
	    DefaultBackgroundColor := StyleSheet colorAt:'menuBackgroundColor'.
	]
    ].
    DefaultHilightForegroundColor := StyleSheet colorAt:'pullDownMenuHilightForegroundColor'.
    DefaultHilightForegroundColor isNil ifTrue:[
	DefaultHilightForegroundColor := StyleSheet colorAt:'menuHilightForegroundColor'.
    ].
    DefaultHilightBackgroundColor := StyleSheet colorAt:'pullDownMenuHilightBackgroundColor'.
    DefaultHilightBackgroundColor isNil ifTrue:[
	DefaultHilightBackgroundColor := StyleSheet colorAt:'menuHilightBackgroundColor'.
    ].
    DefaultHilightLevel := StyleSheet at:'pullDownMenuHilightLevel'.
    DefaultHilightLevel isNil ifTrue:[
	DefaultHilightLevel := StyleSheet at:'menuHilightLevel' default:0.
    ].
    DefaultEdgeStyle := StyleSheet at:'pullDownMenuEdgeStyle'.
    DefaultKeepMenu := StyleSheet at:'pullDownMenuKeepMenu' default:false.
    DefaultToggleKeep := StyleSheet at:'pullDownMenuToggleKeep' default:false.
    DefaultLevel := StyleSheet at:'pullDownMenuLevel' default:1.
    DefaultFont := StyleSheet fontAt:'pullDownMenuFont'.
    DefaultFont isNil ifTrue:[
	DefaultFont := StyleSheet fontAt:'menuFont'.
    ].

    "
     PullDownMenu updateStyleCache
    "
! !

!PullDownMenu class methodsFor:'instance creation'!

labels:titleArray
    "create and return a new PullDownMenu"

    ^ self new labels:titleArray
! !

!PullDownMenu methodsFor:'initialize / release'!

initialize
    super initialize.

    font := font on:device.
    self origin:(0.0 @ 0.0)
	 extent:(1.0 @ (font height + (font descent * 2)  + topMargin)).
!

initStyle
    super initStyle.

    showSeparatingLines := false.
    DefaultViewBackground notNil ifTrue:[
	viewBackground := DefaultViewBackground on:device
    ].

    DefaultFont notNil ifTrue:[
	font := DefaultFont on:device
    ].
    DefaultForegroundColor notNil ifTrue:[
	fgColor := DefaultForegroundColor
    ] ifFalse:[
	fgColor := Black.
    ].
    DefaultBackgroundColor notNil ifTrue:[
	bgColor := DefaultBackgroundColor
    ] ifFalse:[
	bgColor := viewBackground.
    ].
    onLevel := DefaultHilightLevel.
    offLevel := DefaultLevel.

    self is3D ifTrue:[
	device hasColors ifTrue:[
	    activeFgColor := Color name:'yellow'
	] ifFalse:[
	    activeFgColor := White
	].
	device hasGreyscales ifTrue:[
	    activeBgColor := bgColor.
	] ifFalse:[
	    activeBgColor := fgColor.
	].
	topMargin := 2.

	((StyleSheet name == #iris) or:[StyleSheet name == #motif]) ifTrue:[
	    self level:2.
	    onLevel := 2.
	    offLevel := 0.
	    activeFgColor := fgColor
	]
    ] ifFalse:[
	activeFgColor := bgColor.
	activeBgColor := fgColor.
	topMargin := 0
    ].

    edgeStyle := DefaultEdgeStyle.
    keepMenu := DefaultKeepMenu.
    toggleKeep := DefaultToggleKeep.

    DefaultHilightForegroundColor notNil ifTrue:[
	activeFgColor := DefaultHilightForegroundColor
    ].
    DefaultHilightBackgroundColor notNil ifTrue:[
	activeBgColor := DefaultHilightBackgroundColor
    ].
    DefaultShadowColor notNil ifTrue:[
	shadowColor := DefaultShadowColor on:device
    ].
    DefaultLightColor notNil ifTrue:[
	lightColor := DefaultLightColor on:device
    ].

    bgColor := bgColor on:device.
    fgColor := fgColor on:device.
    activeBgColor := activeBgColor on:device.
    activeFgColor := activeFgColor on:device.
!

recreate
    "if saved with an active menu, hide it"

    activeMenuNumber notNil ifTrue:[
	(menus at:activeMenuNumber) unrealize.
	activeMenuNumber := nil.
    ].
    super recreate.
    self setMenuOrigins
!

create
    super create.
    self setMenuOrigins
!

destroy
    "
     have to destroy the menus manually here,
     since they are no real subviews of myself
    "
    menus notNil ifTrue:[
	menus do:[:m |
	    m notNil ifTrue:[m destroy]
	].
	menus := nil
    ].
    activeMenuNumber := nil.
    super destroy.
! !

!PullDownMenu methodsFor:'accessing'!

showSeparatingLines:aBoolean
    "turn on/off drawing of separating lines"

    showSeparatingLines := aBoolean.
    shown ifTrue:[
	self redraw
    ]
!

numberOfTitles:n
    "setup blank title-space to be filled in later"

    menus := Array new:n.
    titles := Array new:n
!

labels:titleArray
    "define the menu-titles (group-headers)"

    |numberOfLabels|

    numberOfLabels := titleArray size.
    menus := Array new:numberOfLabels.
    titles := Array new:numberOfLabels.

    titleArray keysAndValuesDo:[:index :entry |
	|e|

	entry isImage ifTrue:[
	    e := entry on:device
	] ifFalse:[
	    e := entry printString
	].
	titles at:index put:e
    ].
    shown ifTrue:[
	self clear.
	self redraw
    ]
!

labels
    "return the menu-titles (group-headers)"

    ^ titles
!

selectors:selectorArray
    "define the menu-selectors. These are used as accesskey only
     in menuAt: accesses. This makes PullDownMenu accesss
     somewhat more compatible to PopUpMenus."

    selectors := selectorArray.
!

font:aFont
    "adjust menu-origins when font changes"

    super font:(aFont on:device).
    self height:(font height + (font descent * 2)).
    shown ifTrue:[
	self setMenuOrigins
    ]
!

foregroundColor:aColor
    fgColor := aColor on:device
!

backgroundColor:aColor
    bgColor := aColor on:device
!

menuAt:string
    "return the menu with the title; return nil if not found"

    |index|

    index := self indexOf:string.
    (index == 0) ifTrue:[^ nil].
    ^ menus at:index
!

at:aString putMenu:aMenu
    "set the menu under the title, aString"

    |index|

    index := self indexOf:aString.
    (index == 0) ifTrue:[^ nil].

"/ not needed:
"/    aMenu origin:((left + (self titleLenUpTo:index)) 
"/                  @
"/                  (height + aMenu borderWidth)).
    aMenu hidden:true.
    menus at:index put:aMenu.
    aMenu masterView:self.
!

at:aString putLabels:labels selectors:selectors args:args receiver:anObject
    "create and set the menu under the title, aString"

    |menuView|

    menuView := MenuView labels:labels
		      selectors:selectors
			   args:args
		       receiver:anObject
			    for:self.
    self at:aString putMenu:menuView
!

at:aString putLabels:labels selector:selector args:args receiver:anObject
    "create and set the menu under the title, aString"

    |menuView|

    menuView := MenuView labels:labels
		       selector:selector
			   args:args
		       receiver:anObject
			    for:self.
    self at:aString putMenu:menuView
!

at:aString putLabels:labels selectors:selectors receiver:anObject
    "create and set the menu under the title, aString"

    |menuView|

    menuView := MenuView labels:labels
		      selectors:selectors
		       receiver:anObject
			    for:self.
    self at:aString putMenu:menuView
! !

!PullDownMenu methodsFor:'private'!

titleLenUpTo:index
    "answer len (in pixels) of all title-strings up-to 
     (but excluding) title-index. Used to compute x-position when drawing
     individual entries."

    |len "{ Class: SmallInteger }" 
     wSpace wSep|

    (index <= 1) ifTrue:[^ 0].
    wSpace := (font widthOf:' ').
    showSeparatingLines ifTrue:[
	self is3D ifTrue:[
	    wSep := 2
	] ifFalse:[
	    wSep := 1
	]
    ] ifFalse:[
	wSep := 0
    ].

    len := 0.
    titles from:1 to:(index - 1) do:[:entry |
	|thisLength|

	entry isString ifTrue:[
	    thisLength := (font widthOf:entry).
	] ifFalse:[
	    thisLength := entry width
	].
	len := len + thisLength + wSpace + wSep + wSpace.
    ].
    ^ len
!

indexOf:stringOrNumber
    "return the index of the menu with title; return 0 if not found.
     stringOrNumber may be a number, a selector from the selectorArray
     or a string from the title array."

    |idx|

    stringOrNumber isNumber ifTrue:[
	^ stringOrNumber
    ].
    selectors notNil ifTrue:[
	idx := selectors indexOf:stringOrNumber.
	idx ~~ 0 ifTrue:[^ idx].
    ].
    ^ titles indexOf:stringOrNumber
!

setMenuOrigins
    "adjust origins of menus when font changes"

    (font device == device) ifTrue:[
	menus keysAndValuesDo:[:index :aMenu |
	    aMenu notNil ifTrue:[
		aMenu origin:((left + (self titleLenUpTo:index)) 
			      @
			      (height + aMenu borderWidth))
	    ].
	]
    ]
!

titleIndexForX:x
    "given a click x-position, return index in title or nil"

    |xstart "{ Class: SmallInteger }"
     xend   "{ Class: SmallInteger }" 
     wSpace wSep|

    wSpace := (font widthOf:' ') * 2. 
    showSeparatingLines ifTrue:[
	self is3D ifTrue:[
	    wSep := 2
	] ifFalse:[
	    wSep := 1
	]
    ] ifFalse:[
	wSep := 0
    ].
    xstart := 0.
    1 to:(titles size) do:[:index |
	|entry thisLength|

	entry := titles at:index.
	entry isString ifTrue:[
	    thisLength := font widthOf:entry.
	] ifFalse:[
	    thisLength := entry width
	].
	xend := xstart + thisLength + wSpace + wSep.
	(x between:xstart and:xend) ifTrue:[^ index].
	xstart := xend
    ].
    ^ nil
! !

!PullDownMenu methodsFor:'hiding/showing menus'!

hideActiveMenuRelease:aBoolean
    "hide currently active menu - release grab if aBoolean is true
     and a grab was set (keepMenu)"

    activeMenuNumber notNil ifTrue:[
	(menus at:activeMenuNumber) unrealize.
	self unHighlightActiveTitle.
	activeMenuNumber := nil
    ].
    aBoolean ifTrue:[
	device ungrabPointer. 
	self cursor:Cursor normal
    ].
!

hideActiveMenu
    "hide currently active menu - release grab if there is any grab (keepMenu)"

    ^ self hideActiveMenuRelease:true
!

pullMenu:aNumber
    "activate a menu, return it or nil"

    |subMenu|

    activeMenuNumber notNil ifTrue:[self hideActiveMenuRelease:false].
    subMenu := menus at:aNumber.
    subMenu notNil ifTrue:[
	activeMenuNumber := aNumber.
	self highlightActiveTitle.
	subMenu deselect.
	subMenu create.
	subMenu saveUnder:true.
	subMenu superMenu:self.
	subMenu raise show
    ].
    ^ subMenu
!

regainControl
    keepMenu ifTrue:[
	device grabPointerInView:self.
	self cursor:Cursor upRightArrow
    ]
! !

!PullDownMenu methodsFor:'drawing '!

redraw
    |string
     x     "{ Class: SmallInteger }"
     y     "{ Class: SmallInteger }"
     index "{ Class: SmallInteger }" 
     wSpace|

    shown ifFalse: [ ^ self ].
    titles isNil ifTrue:[^ self].

    wSpace := (font widthOf:' ').
    x := 0.
    y := height "- 1".
    index := 1.
    titles do:[:title |
	self drawTitle:title x:x selected:(index == activeMenuNumber).

	title isString ifTrue:[
	    x := x + (font widthOf:title).
	] ifFalse:[
	    x := x + title width
	].
	x := x + wSpace + wSpace.
	showSeparatingLines ifTrue:[
	    self is3D ifTrue:[
		self paint:shadowColor.
		self displayLineFromX:x y:0 toX:x y:y.
		x := x + 1.
		self paint:lightColor.
	    ] ifFalse:[
		self paint:fgColor.
	    ].
	    self displayLineFromX:x y:0 toX:x y:y.
	    x := x + 1
	].
	index := index + 1
    ]
!

drawTitle:stringOrImage x:x0 selected:selected
    |y w x wSpace|

    wSpace := font widthOf:' '.
    x := x0.
    stringOrImage isString ifTrue:[
	y := ((height - (font height)) // 2) + (font ascent) "+ topMargin".
	w := font widthOf:stringOrImage.
    ] ifFalse:[
	y := ((height - stringOrImage height) // 2) max:0.
	w := stringOrImage width
    ].
    w := w + (wSpace * 2).

    selected ifTrue:[
	self paint:activeBgColor
    ] ifFalse:[
	self paint:bgColor
    ].
    self fillRectangleX:x y:0 width:w height:height.

    self is3D ifTrue:[
	self drawEdgesForX:x y:0
		     width:w
		    height:height
		     level:(selected ifTrue:[onLevel] ifFalse:[offLevel])
    ].
    selected ifTrue:[
	self paint:activeFgColor
    ] ifFalse:[
	self paint:fgColor
    ].
    x := x + wSpace.
    stringOrImage isString ifTrue:[
	self displayString:stringOrImage x:x y:y
    ] ifFalse:[
	self displayForm:stringOrImage x:x y:y
    ]
!

highlightActiveTitle
    |x|
    activeMenuNumber notNil ifTrue:[
	x := self titleLenUpTo:activeMenuNumber.
	self drawTitle:(titles at:activeMenuNumber) x:x selected:true
    ]
!

unHighlightActiveTitle
    |x|
    activeMenuNumber notNil ifTrue:[
	x := self titleLenUpTo:activeMenuNumber.
	self drawTitle:(titles at:activeMenuNumber) x:x selected:false
    ]
! !

!PullDownMenu methodsFor:'submenu notifications'!

showActive
    "sent by a submenu to tell me that it started to perform
     its menu action"
!

showPassive
    "sent by a submenu to tell me that it finished its menu-action."

    self hideActiveMenu
!

submenuTriggered 
    "sent by a sub-submenu to tell me that it finished its menu-action."

    self showPassive
! !

!PullDownMenu methodsFor:'event handling'!

keyPress:key x:x y:y
    |index m|

    "
     handle CursorLeft/Right for non-mouse operation
     (once it has the explicit focus)
    "
    ((key == #CursorRight) or:[key == #CursorLeft]) ifTrue:[
	activeMenuNumber isNil ifTrue:[
	    index := (key == #CursorRight) ifTrue:[1] ifFalse:[menus size].
	] ifFalse:[
	    (key == #CursorRight) ifTrue:[
		index := activeMenuNumber+1
	    ] ifFalse:[
		index := activeMenuNumber-1
	    ].
	    index == 0 ifTrue:[index := menus size]
	    ifFalse:[
		index > menus size ifTrue:[index := 1]
	    ]
	].
	m := self pullMenu:index.
	^ self
    ].

    activeMenuNumber isNil ifTrue:[^self].

    "
     pass it on to the active menu
    "
    m := menus at:activeMenuNumber.
    m keyPress:key x:0 y:0.
    ^ self
!

buttonPress:button x:x y:y
    |titleIndex activeMenu activeLeft activeTop m|

    device ungrabPointer.

    (y between:0 and:height) ifTrue:[
	titleIndex := self titleIndexForX:x.
    ].

    "
     now, titleIndex is non-nil if pressed within myself
    "
    (titleIndex notNil and:[titleIndex ~~ activeMenuNumber]) ifTrue:[
	m := self pullMenu:titleIndex.
	(keepMenu and:[m notNil]) ifTrue:[
	    device grabPointerInView:self.
	    self cursor:Cursor upRightArrow
	]
    ] ifFalse:[
	(keepMenu and:[toggleKeep not]) ifTrue:[
	    titleIndex == activeMenuNumber ifTrue:[
		"same pressed again ... stay"
		device grabPointerInView:self.
		^ self
	    ].
	    "moving around below"
	    activeMenuNumber isNil ifTrue:[^self].
	    activeMenu := menus at:activeMenuNumber.
	    activeLeft := activeMenu left.
	    (x between:activeLeft and:(activeMenu right)) ifTrue:[
		activeTop := activeMenu top.
		(y between:activeTop and:(activeMenu bottom)) ifTrue:[
		    "moving around in menu"
		    activeMenu buttonPress:button
					 x:(x - activeLeft)
					 y:(y - activeTop).
		    ^ self
		]
	    ].
	].
	self hideActiveMenu
    ]
!

buttonMotion:button x:x y:y
    |titleIndex activeMenu activeLeft activeTop|

    activeMenuNumber notNil ifTrue:[
	activeMenu := menus at:activeMenuNumber.
    ].

    (y < height) ifTrue:[
	"moving around in title line"
	activeMenu notNil ifTrue:[
	    activeMenu selection:nil
	].
	titleIndex := self titleIndexForX:x.
	titleIndex notNil ifTrue:[
	    (titleIndex ~~ activeMenuNumber) ifTrue:[
		self pullMenu:titleIndex
	    ]
	]
    ] ifFalse:[
	"moving around below"
	activeMenu isNil ifTrue:[^self].
	activeLeft := activeMenu left.
	(x between:activeLeft and:(activeMenu right)) ifTrue:[
	    activeTop := activeMenu top.
	    (y between:activeTop and:(activeMenu bottom)) ifTrue:[
		"moving around in menu"
		activeMenu buttonMotion:button
				      x:(x - activeLeft)
				      y:(y - activeTop).
		^ self
	    ]
	].
	"moved outside menu"
	activeMenu selection:nil
    ]
!

buttonRelease:button x:x y:y
    |activeMenu activeLeft activeTop hideMenu|

    hideMenu := false.
    (y >= height) ifTrue:[
	"release below title-line"
	activeMenuNumber isNil ifTrue:[^self].
	activeMenu := menus at:activeMenuNumber.
	activeLeft := activeMenu left.
	"
	 released in a submenu ?
	"
	(x between:activeLeft and:(activeMenu right)) ifTrue:[
	    activeTop := activeMenu top.
	    (y between:activeTop and:(activeMenu bottom)) ifTrue:[
		"release in menu"
		self hideActiveMenu.   
		activeMenu buttonRelease:button
				       x:(x - activeLeft)
				       y:(y - activeTop).
		^ self
	    ]
	].
	hideMenu := true.
    ] ifFalse:[
	y < 0 ifTrue:[
	    hideMenu := true
	] ifFalse:[
	    keepMenu ifFalse:[   
		hideMenu := true
	    ]
	]
    ].                  
    hideMenu ifTrue:[
       self hideActiveMenu.
    ]
! !