MenuView.st
author Claus Gittinger <cg@exept.de>
Fri, 08 Mar 1996 14:45:20 +0100
changeset 497 072d3b8507fd
parent 495 d993f23ea658
child 508 7b0bffe113a0
permissions -rw-r--r--
checkin from browser

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

SelectionInListView subclass:#MenuView
	instanceVariableNames:'selectors args receiver enableFlags disabledFgColor onOffFlags
		subMenus subMenuShown superMenu checkColor lineLevel lineInset
		masterView hilightStyle needResize hideOnRelease sizeFixed
		shortKeys maxShortKeyStringLen'
	classVariableNames:'DefaultCheckColor DefaultViewBackground DefaultForegroundColor
		DefaultBackgroundColor DefaultDisabledForegroundColor
		DefaultHilightForegroundColor DefaultHilightBackgroundColor
		DefaultHilightLevel DefaultHilightStyle DefaultHilightFrameColor
		DefaultLineLevel DefaultLineInset DefaultShadowColor
		DefaultLightColor ShowAcceleratorKeys'
	poolDictionaries:''
	category:'Views-Menus'
!

!MenuView 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.
"
!

documentation
"
    a menu view used for both pull-down-menus and pop-up-menus (and also,
    for nonModal menus, such as the Launchers click-menu).
    the action to be performed can be defined either as:

    1) action:aBlockWithOneArg
       which defines a block to be called with the line number (1..n)
       of the selected line.

    2) selectors:selectorArray [args: argArray] [receiver:anObject]
       which defines the messages to be sent to the model or
       receiver. Giving an explicit receiver overrides the model.

    It is also possible to define both actionBlock and selectorArray.

    The wellknown popups are created by wrapping a MenuView into an instance of
    PopUpMenu (read the description of popupmenu).

    menu entries starting with '\c' are check-entries.
    menu entries starting with '\b' are checkBox-entries.
    menu entries starting with '\t' are thumbUp/Down-entries.
    menu entries conisting of '-' alone, are separating lines.
    menu entries conisting of '=' alone, are double separating lines.


    StyleSheet defaults:

	menuFont                    font to use for menus

	menuViewBackground          view background (should be same as menuBackgroundColor)
	menuForegroundColor         foreground color
	menuBackgroundColor         background color

	menuShadowColor             shadow color for 3D effects
	menuLightColor              lightColor for 3D effects
	menuHilightForegroundColor  hilighted items foregroundColor
	menuHilightBackgroundColor  hilighted items backgroundColor

	menuHilightFrameColor       frame arounf hilighted items (or nil, if none)
				    defaults to selectionHilightFrameColor
	menuHilightLevel            3D level of selected items
	menuHilightStyle            #openwin or nil (special kludge)
	menuSeparatingLineLevel     3D level of sep. lines
	menuSeparatingLineInset     left/right inset of sep. lines
	menuDisabledForegroundColor foreground color of disabled items
	menuCheckColor              color to use for check marks
	menuFont                    font to use

    other values and some defaults are inherited via SelectionInListViews
    styles (i.e. look for selectionForegroundColor ...)
"
!

examples
"
    See real examples in PopUpMenu & PullDownMenu

    Examples:
        Notice: normally, menuviews are wrapped into either a popup-
        menu or pulldown-menu. But they can also be used stand-alone
        as in:

        |m|
        m := MenuView
                labels:#('foo'
                         'bar'
                         'baz')
                selectors:#(
                            #foo
                            #bar
                            #baz)
                receiver:nil.
        m open
"
! !

!MenuView class methodsFor:'instance creation'!

labels:labels
    "create and return a new MenuView. The parent view,
     selectors and receiver should be set later."

    ^ self labels:labels selectors:nil args:nil receiver:nil 
!

labels:labels selector:aSelector args:argArray receiver:anObject for:aTopMenu
    "create and return a new MenuView
     - receiverObject gets message aSelector with argument from
       argArray for ALL entries"

    "OBSOLETE protocol: labels:selectors:args:receiver: knows how to handle a
     single symbol-arg for selectors ..."

    ^ self labels:labels selectors:aSelector args:argArray receiver:anObject in:(aTopMenu superView)
!

labels:labels selector:aSelector args:argArray receiver:anObject in:aTopMenu
    "create and return a new MenuView
     - receiverObject gets message aSelector with argument from
       argArray for all entries"

    "OBSOLETE protocol: labels:selectors:args:receiver: knows how to handle a
     single symbol-arg for selectors ..."

    ^ self labels:labels selectors:aSelector args:argArray receiver:anObject in:aTopMenu
!

labels:labels selectors:selArray
    "create and return a new MenuView. The parent veiw
     and receiver should be set later."

    ^ self labels:labels selectors:selArray args:nil receiver:nil 
!

labels:labels selectors:selArray accelerators:shorties
    "create and return a new MenuView. The parent veiw
     and receiver should be set later."

    ^ self labels:labels selectors:selArray accelerators:shorties args:nil receiver:nil 
!

labels:labels selectors:selArray accelerators:shorties args:argArray receiver:anObject
    "create and return a new MenuView. The parent view
     should be set later."

    ^ (self new) 
        labels:labels
        selectors:selArray
        accelerators:shorties 
        args:argArray 
        receiver:anObject
!

labels:labels selectors:selArray accelerators:shorties args:argArray receiver:anObject in:aView
    "create and return a new MenuView in aView
     - receiverObject gets message from selectorArray with argument
       from argArray"

    ^ (self in:aView) 
        labels:labels 
        selectors:selArray
        accelerators:shorties 
        args:argArray
        receiver:anObject
!

labels:labels selectors:selArray accelerators:shorties receiver:anObject
    "create and return a new MenuView. The parent view
     should be set later."

    ^ self labels:labels selectors:selArray accelerators:shorties args:nil receiver:anObject
!

labels:labels selectors:selArray args:argArray
    "create and return a new MenuView. The parent view
     should be set later."

    ^ self labels:labels selectors:selArray args:argArray
!

labels:labels selectors:selArray args:argArray receiver:anObject
    "create and return a new MenuView. The parent view
     should be set later."

    ^ (self new) 
	labels:labels
	selectors:selArray
	args:argArray 
	receiver:anObject
!

labels:labels selectors:selArray args:argArray receiver:anObject for:aTopMenu
    "create and return a new MenuView for a topMenu"

    ^ self labels:labels selectors:selArray args:argArray receiver:anObject in:(aTopMenu superView)
!

labels:labels selectors:selArray args:argArray receiver:anObject in:aView
    "create and return a new MenuView in aView
     - receiverObject gets message from selectorArray with argument
       from argArray"

    ^ (self in:aView) 
	labels:labels 
	selectors:selArray
	args:argArray
	receiver:anObject
!

labels:labels selectors:selArray receiver:anObject
    "create and return a new MenuView. The parent view
     should be set later."

    ^ self labels:labels selectors:selArray args:nil receiver:anObject
!

labels:labels selectors:selArray receiver:anObject for:aTopMenu
    ^ self labels:labels selectors:selArray args:nil receiver:anObject for:aTopMenu
!

labels:labels selectors:selArray receiver:anObject in:aView
    "create and return a new MenuView in aView
     - receiverObject gets message from selectorArray without argument"

    ^ self labels:labels selectors:selArray args:nil receiver:anObject in:aView
! !

!MenuView class methodsFor:'defaults'!

showAcceleratorKeys
    ^ ShowAcceleratorKeys ~~ false

    "Created: 2.3.1996 / 14:52:34 / cg"
    "Modified: 2.3.1996 / 14:54:58 / cg"
!

showAcceleratorKeys:aBoolean
    ShowAcceleratorKeys := aBoolean

    "Created: 2.3.1996 / 14:52:43 / cg"
!

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

    <resource: #style (#menuForegroundColor #menuBackgroundColor
                       #menuViewBackground
                       #menuShadowColor #menuLightColor
                       #menuHilightForegroundColor #menuHilightBackgroundColor
                       #menuHilightFrameColor #selectionHilightFrameColor
                       #menuHilightLevel #menuHilightStyle
                       #menuSeparatingLineLevel #menuSeparatingLineInset
                       #menuDisabledForegroundColor #menuCheckColor
                       #menuFont #menuShowAccelerators)>

    DefaultViewBackground := StyleSheet colorAt:'menuViewBackground'.
    DefaultForegroundColor := StyleSheet colorAt:'menuForegroundColor'.
    DefaultBackgroundColor := StyleSheet colorAt:'menuBackgroundColor'.
    DefaultShadowColor := StyleSheet colorAt:'menuShadowColor'.
    DefaultLightColor := StyleSheet colorAt:'menuLightColor'.
    DefaultHilightForegroundColor := StyleSheet colorAt:'menuHilightForegroundColor'.
    DefaultHilightBackgroundColor := StyleSheet colorAt:'menuHilightBackgroundColor'.
    DefaultHilightFrameColor := StyleSheet colorAt:'menuHilightFrameColor' 
                                default:(StyleSheet colorAt:'selectionHilightFrameColor').
    DefaultHilightLevel := StyleSheet at:'menuHilightLevel'.
    DefaultHilightStyle := StyleSheet at:'menuHilightStyle'.
    DefaultLineLevel := StyleSheet at:'menuSeparatingLineLevel'.
    DefaultLineInset := StyleSheet at:'menuSeparatingLineInset'.
    DefaultDisabledForegroundColor := StyleSheet colorAt:'menuDisabledForegroundColor' default:Color darkGrey.
    DefaultCheckColor := StyleSheet colorAt:'menuCheckColor'.
    DefaultFont := StyleSheet fontAt:'menuFont'.
    ShowAcceleratorKeys := StyleSheet at:'menuShowAccelerators' default:true.

    "Modified: 1.3.1996 / 13:45:31 / cg"
! !

!MenuView methodsFor:'accessing-behavior'!

disable:indexOrName
    "disable an entry"

    self setEnable:indexOrName to:false
!

disableAll
    "disable all entries"

    self disableAll:selectors

    "Created: 23.12.1995 / 16:56:05 / cg"
!

disableAll:collectionOfIndicesOrNames
    "disable an collection of entries"

    collectionOfIndicesOrNames do:[:entry |
	self disable:entry
    ]
!

enable:indexOrName
    "enable an entry"

    self setEnable:indexOrName to:true 
!

enableAll:collectionOfIndicesOrNames
    "enable an collection of entries"

    collectionOfIndicesOrNames do:[:entry |
	self enable:entry
    ]
!

hideOnRelease:aBoolean
    hideOnRelease := aBoolean
!

isEnabled:indexOrName
    |index|

    index := self indexOf:indexOrName.
    index ~~ 0 ifTrue:[
	enableFlags isNil ifTrue:[^ true].
	^ enableFlags at:index
    ].
    "ask submenus for convenience"
    (indexOrName isNumber not and:[subMenus notNil]) ifTrue:[
	subMenus do:[:m |
	    m notNil ifTrue:[
		m enable:indexOrName
	    ]
	]
    ]
!

setEnable:indexOrName to:aBoolean
    "enable/disable an entry"

    |index|

    index := self indexOf:indexOrName.
    index ~~ 0 ifTrue:[
	(enableFlags at:index) ~~ aBoolean ifTrue:[
	    enableFlags at:index put:aBoolean.
	    shown ifTrue:[
		self redrawLine:index
	    ]
	]
    ] ifFalse:[
	"try submenus for convenience"
	(indexOrName isNumber not and:[subMenus notNil]) ifTrue:[
	    subMenus do:[:m |
		m notNil ifTrue:[
		    m setEnable:indexOrName to:aBoolean
		]
	    ]
	]
    ]
! !

!MenuView methodsFor:'accessing-items'!

accelerators:collectionOfShortKeys
    "set the accelerator keys collection.
     You should pass translated symbolic keys - the menu will automatically
     show the untranslated original key sequences."

    shortKeys := collectionOfShortKeys.
    maxShortKeyStringLen := nil.
    shown ifTrue:[
        self resize
    ] ifFalse:[
        needResize := true
    ].

    "Created: 28.2.1996 / 17:15:31 / cg"
    "Modified: 28.2.1996 / 18:27:30 / cg"
!

addLabel:aLabel selector:aSelector
    "add another label/selector pair at the end"

    self addLabel:aLabel selector:aSelector after:nil

    "Modified: 28.2.1996 / 17:54:11 / cg"
!

addLabel:aLabel selector:aSelector after:aLabelOrSelectorOrNumber 
    "insert another label/selector pair at some place.
     Being very friendly here, allowing label-string, selector or numeric
     index for the argument aLabelOrSelectorOrNumber.

     To be independent of the entries label, we recommend you use the selector
     as index; in systems which translate strings for national variants,
     this makes your code easier to maintain."

    self 
        addLabels:(Array with:aLabel)
        selectors:(Array with:aSelector)
        after:aLabelOrSelectorOrNumber

    "
     |v1 v2 v3 v4|

     v1 := CodeView new open.

     v2 := CodeView new open.
     v2 middleButtonMenu:
        (v2 editMenu addLabel:'new entry' selector:#foo after:#pasteSelection; yourself).

     v3 := CodeView new open.
     v3 middleButtonMenu:
        (v3 editMenu addLabel:'new entry' selector:#foo after:#others; yourself).

     v4 := CodeView new open.
     v4 middleButtonMenu:
        (v4 editMenu addLabel:'new entry' selector:#foo after:1; yourself).
    "

    "Modified: 28.2.1996 / 18:04:35 / cg"
!

addLabel:aLabel selector:aSelector arg:anArg
    "add another label/selector/argument trio.
     OBSOLETE"

    |idx|

    idx := list size + 1.
    self addLabel:aLabel selector:aSelector.
    args at:idx put:anArg

    "Modified: 28.2.1996 / 18:08:39 / cg"
!

addLabel:aLabel selector:aSelector before:aLabelOrSelectorOrNumber 
    "insert another label/selector pair at some place.
     Being very friendly here, allowing label-string, selector or numeric
     index for the argument aLabelOrSelectorOrNumber.

     To be independent of the entries label, we recommend you use the selector
     as index; in systems which translate strings for national variants,
     this makes your code easier to maintain."

    self 
        addLabels:(Array with:aLabel)
        selectors:(Array with:aSelector)
        before:aLabelOrSelectorOrNumber

    "
     |v1 v2 v3 v4 v5|

     v1 := CodeView new open.

     v2 := CodeView new open.
     v2 middleButtonMenu:
        (v2 editMenu addLabel:'new entry' selector:#foo before:'paste'; yourself).

     v3 := CodeView new open.
     v3 middleButtonMenu:
        (v3 editMenu addLabel:'new entry' selector:#foo before:#pasteOrReplace; yourself).

     v4 := CodeView new open.
     v4 middleButtonMenu:
        (v4 editMenu addLabel:'new entry' selector:#foo before:#again; yourself).

     v5 := CodeView new open.
     v5 middleButtonMenu:
        (v5 editMenu addLabel:'new entry' selector:#foo before:1; yourself).

     Notice: v2 above is an example on how NOT to do it - it will not work with nationalized menus
    "

    "Modified: 28.2.1996 / 18:04:00 / cg"
!

addLabels:moreLabels selectors:moreSelectors
    "add more labels and selectors at the END"

    self addLabels:moreLabels selectors:moreSelectors after:nil

    "Modified: 28.2.1996 / 17:46:50 / cg"
!

addLabels:moreLabels selectors:moreSelectors accelerators:shorties
    "add more labels and selectors at the END"

    self addLabels:moreLabels selectors:moreSelectors accelerators:shorties after:nil

    "Modified: 28.2.1996 / 17:46:50 / cg"
    "Created: 28.2.1996 / 17:47:17 / cg"
!

addLabels:moreLabels selectors:moreSelectors accelerators:shorties after:aLabelOrSelectorOrNumber 
    "insert more labels/selectors at some place.
     Being very friendly here, allowing label-string, selector or numeric
     index for the argument aLabelOrSelectorOrNumber.
     If such an item is not found, insert the new items at the END.

     To be independent of the entries label, we recommend you use the selector
     as index; in systems which translate strings for national variants,
     this makes your code easier to maintain."

    |idx|

    aLabelOrSelectorOrNumber isNil ifTrue:[
        idx := list size + 1
    ] ifFalse:[
        idx := (self indexOf:aLabelOrSelectorOrNumber) + 1.
        idx == 1 ifTrue:[
            idx := list size + 1
        ]
    ].

    ^ self 
        addLabels:moreLabels 
        selectors:moreSelectors 
        accelerators:shorties
        before:idx

    "Created: 28.2.1996 / 17:48:24 / cg"
    "Modified: 4.3.1996 / 23:26:02 / cg"
!

addLabels:moreLabels selectors:moreSelectors accelerators:shorties before:aLabelOrSelectorOrNumber 
    "insert more labels/selectors at some place.
     Being very friendly here, allowing label-string, selector or numeric
     index for the argument aLabelOrSelectorOrNumber. 
     If such an item is not found, insert the new items at the beginning.

     To be independent of the entries label, we recommend you use the selector
     as index; in systems which translate strings for national variants,
     this makes your code easier to maintain."

    |idx oldSize
     i     "{ Class: SmallInteger }" 
     nMore "{ Class: SmallInteger }"|

    list isNil ifTrue:[
        ^ self addLabels:moreLabels selectors:moreSelectors
    ].
    "
     be user friendly - allow both label or selector
     to be passed
    "
    aLabelOrSelectorOrNumber isNil ifTrue:[
        idx := 1
    ] ifFalse:[
        idx := self indexOf:aLabelOrSelectorOrNumber.
        (idx between:2 and:(list size + 1)) ifFalse:[
            "add to beginning"
            idx := 1
        ]
    ].

    nMore := moreLabels size.
    "/ just a check
    moreSelectors size ~~ nMore ifTrue:[
        ^ self error
    ].

    oldSize := list size.

    list := list asOrderedCollection.
    i := idx.
    moreLabels do:[:aLabel |
        list add:aLabel beforeIndex:i. i := i + 1.
    ].

    selectors := selectors asOrderedCollection.
    i := idx.
    moreSelectors do:[:sel |
        selectors add:sel beforeIndex:i. i := i + 1.
    ].

    enableFlags := enableFlags asOrderedCollection.
    i := idx.
    nMore timesRepeat:[
        enableFlags add:true beforeIndex:i. i := i + 1.
    ].

    subMenus notNil ifTrue:[
        subMenus := subMenus asOrderedCollection.
        i := idx.
        nMore timesRepeat:[
            subMenus add:nil beforeIndex:i. i := i + 1.
        ].
    ].
    args notNil ifTrue:[
        args := args asOrderedCollection.
        i := idx.
        nMore timesRepeat:[
            args add:nil beforeIndex:i. i := i + 1.
        ]
    ].
    onOffFlags notNil ifTrue:[
        onOffFlags := onOffFlags asOrderedCollection.
        i := idx.
        nMore timesRepeat:[
            onOffFlags add:nil beforeIndex:i. i := i + 1.
        ]
    ].
    shortKeys isNil ifTrue:[
        shortKeys := OrderedCollection new:oldSize.
        shortKeys grow:oldSize
    ].
    shortKeys := shortKeys asOrderedCollection.
    i := idx.
    shorties isNil ifTrue:[
        nMore timesRepeat:[
            shortKeys add:nil beforeIndex:i. i := i + 1.
        ]
    ] ifFalse:[
        maxShortKeyStringLen := nil.
        shorties do:[:sel |
            shortKeys add:sel beforeIndex:i. i := i + 1.
        ]
    ].

    shown ifTrue:[
        self resize
    ] ifFalse:[
        needResize := true
    ].

    "
     |v1 v2 v3 v4 v5 m|


     v1 := CodeView new open.
     v1 contents:'original menu'.

     v2 := CodeView new open.
     v2 contents:'before copy'.
     m := v2 editMenu.
     m
        addLabels:#('new entry1' 'new entry2') 
        selectors:#(foo bar) 
        before:#copySelection 
        accelerators:#(Copy Cut Paste).
     v2 middleButtonMenu:m.

     v3 := CodeView new open.
     v3 contents:'before again '.
     m := v3 editMenu.
     m
        addLabels:#('new entry1' 'new entry2') 
        selectors:#(foo bar) 
        before:#again.
     v3 middleButtonMenu:m.

     v4 := CodeView new open.
     v4 contents:'at beginning '.
     m := v4 editMenu.
     m
        addLabels:#('new entry1' 'new entry2' '-') 
        selectors:#(foo bar nil) 
        before:1.
     v4 middleButtonMenu:m.

     v5 := CodeView new open.
     v5 contents:'at end '.
     m := v5 editMenu.
     m
        addLabels:#('-' 'new entry1' 'new entry2') 
        selectors:#(nil foo bar).
     v5 middleButtonMenu:m.
    "

    "Created: 28.2.1996 / 17:49:44 / cg"
    "Modified: 5.3.1996 / 14:49:35 / cg"
!

addLabels:moreLabels selectors:moreSelectors after:aLabelOrSelectorOrNumber 
    "insert more labels/selectors at some place.
     Being very friendly here, allowing label-string, selector or numeric
     index for the argument aLabelOrSelectorOrNumber.
     If such an item is not found, insert the new items at the END.

     To be independent of the entries label, we recommend you use the selector
     as index; in systems which translate strings for national variants,
     this makes your code easier to maintain."

    ^ self 
        addLabels:moreLabels 
        selectors:moreSelectors 
        accelerators:nil
        after:aLabelOrSelectorOrNumber

    "Modified: 28.2.1996 / 17:47:52 / cg"
!

addLabels:moreLabels selectors:moreSelectors before:aLabelOrSelectorOrNumber 
    "insert more labels/selectors at some place.
     Being very friendly here, allowing label-string, selector or numeric
     index for the argument aLabelOrSelectorOrNumber.
     If such an item is not found, insert the new items at the beginning.

     To be independent of the entries label, we recommend you use the selector
     as index; in systems which translate strings for national variants,
     this makes your code easier to maintain."

    self 
        addLabels:moreLabels 
        selectors:moreSelectors 
        accelerators:nil 
        before:aLabelOrSelectorOrNumber 

    "
     |v1 v2 v3 v4 m|


     v1 := CodeView new open.

     v2 := CodeView new open.
     m := v2 editMenu.
     m
        addLabels:#('new entry1' 'new entry2') 
        selectors:#(foo bar) 
        before:'paste'.
     v2 middleButtonMenu:m.

     v3 := CodeView new open.
     m := v3 editMenu.
     m
        addLabels:#('new entry1' 'new entry2') 
        selectors:#(foo bar) 
        before:#again.
     v3 middleButtonMenu:m.

     v4 := CodeView new open.
     m := v4 editMenu.
     m
        addLabels:#('new entry1' 'new entry2') 
        selectors:#(foo bar) 
        before:1.
     v4 middleButtonMenu:m.
    "

    "Modified: 28.2.1996 / 17:49:30 / cg"
!

addSeparatingLine
    "add a separating line at the END"

    self addLabel:'-' selector:nil

    "Modified: 28.2.1996 / 17:50:08 / cg"
!

addSeparatingLineAfter:aLabelOrSelectorOrNumber
    "add a separating line after an item"

    self addLabel:'-' selector:nil after:aLabelOrSelectorOrNumber

    "Modified: 28.2.1996 / 17:50:14 / cg"
!

args
    "return the argument array"

    ^ args
!

args:anArray
    "set the argument array"

    args := anArray
!

argsAt:indexOrName put:something
    "set an individual selector"

    |i|

    i := self indexOf:indexOrName.
    i ~~ 0 ifTrue:[args at:i put:something]
!

checkFlags 
    "return an array filled with the check-mark flags.
     Non check-menu items have a nil entry in this array."

    ^ onOffFlags
!

checkToggleAt:indexOrName
    "return a check-toggles boolean state"

    |index|

    index := self indexOf:indexOrName.
    index == 0 ifTrue:[^ false].
    onOffFlags isNil ifTrue:[^ false].
    ^ onOffFlags at:index
!

checkToggleAt:indexOrName put:aBoolean
    "set/clear a check-toggle"

    |index|

    index := self indexOf:indexOrName.
    index == 0 ifTrue:[
"/        'no item: ' print. indexOrName printNL.
        ^ self
    ].

    onOffFlags isNil ifTrue:[
        onOffFlags := Array new:(list size)
    ].
    onOffFlags at:index put:aBoolean.
    shown ifTrue:[
        self redrawLine:index
    ]

    "Modified: 6.3.1996 / 16:31:43 / cg"
!

indexOf:indexOrName
    "return the index of the label named:aName or , if its a symbol
     the index in the selector list"

    indexOrName isSymbol ifTrue:[
	^ selectors indexOf:indexOrName
    ].
    indexOrName isString ifTrue:[
	^ list indexOf:indexOrName
    ].
    indexOrName isNil ifTrue:[^ 0].
    ^ indexOrName
!

labelAt:indexOrName put:aString
    "change the label at index to be aString"

    |i nItems|

    i := self indexOf:indexOrName.
    i == 0 ifTrue:[^ self].
    list at:i put:aString.

    "create onOff flags, if this label has a check-mark"
    (self isCheckItem:aString) ifTrue:[
	nItems := list size.
	onOffFlags isNil ifTrue:[
	    onOffFlags := Array new:nItems
	] ifFalse:[
	    [onOffFlags size < nItems] whileTrue:[
		onOffFlags := onOffFlags copyWith:nil 
	    ]
	].
	onOffFlags at:i put:false
    ].
    shown ifTrue:[
	self resize
    ] ifFalse:[
	needResize := true
    ]
!

labels
    "return the menu-labels"

    ^ list
!

labels:text
    "set the labels to the argument, text"

    |l|

    (text isString) ifTrue:[
	l := text asStringCollection
    ] ifFalse:[
	l := text
    ].
"/    self list:l 
    self setList:l expandTabs:false.
    enableFlags := Array new:(list size) withAll:true.
    onOffFlags := Array new:(list size).
    text keysAndValuesDo:[:index :line |
	(line notNil and:[line includes:$\ ]) ifTrue:[
	    onOffFlags at:index put:false
	].
    ].
    shown ifTrue:[
	self resize
    ] ifFalse:[
	needResize := true
    ]
!

labels:text selectors:selArray accelerators:shorties args:argArray receiver:anObject
    "set all relevant stuff"

    self labels:text.
    selectors := selArray.
    args := argArray.
    receiver := anObject.
    shortKeys := shorties.

    "Created: 28.2.1996 / 18:56:38 / cg"
!

labels:text selectors:selArray args:argArray receiver:anObject
    "set all relevant stuff"

    self labels:text.
    selectors := selArray.
    args := argArray.
    receiver := anObject
!

receiver
    "return the receiver of the message"

    ^ receiver
!

receiver:anObject
    "set the receiver of the message"

    receiver := anObject.
    subMenus notNil ifTrue:[
	subMenus do:[:aMenu |
	    aMenu notNil ifTrue:[
		aMenu receiver:anObject
	    ]
	]
    ]
!

remove:indexOrName
    "remove the label at index"

    |i|

    i := self indexOf:indexOrName.
    i == 0 ifTrue:[^ self].
    list := list asOrderedCollection removeIndex:i.
    selectors := selectors asOrderedCollection removeIndex:i.
    enableFlags := enableFlags asOrderedCollection removeIndex:i.
    subMenus notNil ifTrue:[
        subMenus := subMenus asOrderedCollection removeIndex:i.
    ].
    shortKeys notNil ifTrue:[
        shortKeys := shortKeys asOrderedCollection removeIndex:i.
        maxShortKeyStringLen := nil.
    ].
    shown ifTrue:[
        self resize
    ] ifFalse:[
        needResize := true
    ]

    "Modified: 28.2.1996 / 18:27:57 / cg"
!

selectorAt:indexOrName
    "return an individual selector"

    |i|

    i := self indexOf:indexOrName.
    i ~~ 0 ifTrue:[^ selectors at:i].
    ^ nil
!

selectorAt:indexOrName put:aSelector
    "set an individual selector"

    |i|

    i := self indexOf:indexOrName.
    i ~~ 0 ifTrue:[selectors at:i put:aSelector]
!

selectors
    "return the selector array"

    ^ selectors
!

selectors:anArray
    "set the selector array"

    selectors := anArray
!

someMenuItemLabeled:aLabel
    "find a menu item.
     Currently, in ST/X, instances of MenuItem are only created as dummy"

    |idx|

    idx := self indexOf:aLabel.
    idx ~~ 0 ifTrue:[
	^ MenuItem new menu:self index:idx
    ].
    subMenus notNil ifTrue:[
	subMenus do:[:aMenu |
	    |item|

	    aMenu notNil ifTrue:[
		(item := aMenu someMenuItemLabeled:aLabel) notNil ifTrue:[
		    ^ item
		]
	    ]
	].
    ].
    ^ nil
! !

!MenuView methodsFor:'accessing-look'!

font:aFont
    "adjust size for new font"

    super font:(aFont on:device).
    shown ifTrue:[
	self resize
    ] ifFalse:[
	needResize := true
    ]
! !

!MenuView methodsFor:'accessing-misc'!

masterView
    "return the popup-masterview I am contained in."

    ^ masterView
!

masterView:aPopUpView
    "set the popup-masterview I am contained in."

    masterView := aPopUpView
!

selection:index
    |sel line|

    sel := index.
    sel notNil ifTrue:[
	line := self listAt:index.
	(self isGraphicItem:line) ifTrue:[
	    "
	     not really selectable, but a separating line
	    "
	    sel := nil
	]
    ].
    super selection:sel
!

sizeFixed:aBoolean
    sizeFixed := aBoolean

    "Created: 9.2.1996 / 01:12:40 / cg"
!

superMenu
    "ret the menu I am contained in 
     - need this to hide main menus when a submenu performed its action"

    ^ superMenu
!

superMenu:aMenu
    "set the menu I am contained in 
     - need this to hide main menus when a submenu performed its action"

    superMenu := aMenu
! !

!MenuView methodsFor:'accessing-submenus'!

subMenuAt:indexOrName
    "return a submenu, or nil"

    |i|

    subMenus isNil ifTrue:[^ nil].
    i := self indexOf:indexOrName.
    i == 0 ifTrue:[^ nil].
    ^ subMenus at:i
!

subMenuAt:indexOrName put:aPopUpMenu
    "define a submenu"

    |i newSubMenus|

    i := self indexOf:indexOrName.
    i == 0 ifTrue:[^ nil].

    subMenus size < i ifTrue:[
        newSubMenus := Array new:(list size max:i).
        subMenus notNil ifTrue:[
            newSubMenus replaceFrom:1 with:subMenus.
        ].
        subMenus := newSubMenus.
        shown ifTrue:[
            self resize
        ] ifFalse:[
            needResize := true
        ]
    ].
    subMenus at:i put:aPopUpMenu.

    (receiver notNil and:[aPopUpMenu receiver isNil]) ifTrue:[
        aPopUpMenu receiver:receiver
    ].

    "Modified: 8.3.1996 / 14:42:51 / cg"
!

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

    ^ subMenuShown
! !

!MenuView methodsFor:'disabled scrolling'!

makeSelectionVisible
    ^ self
! !

!MenuView methodsFor:'drawing'!

drawAccelerator:aSymbolicKey inVisibleLine:visLineNr with:fg and:bg
    "draw the accelerator at the right."

    |s x l isSubMenuEntry|

    "/ this is somewhat complicated: we have the symbolic key at hand,
    "/ but want to show the untranslated (inverse keyBoardMapped) key & modifier
    "/

    s := self shortKeyStringFor:aSymbolicKey.
    s isNil ifTrue:[^ self].

    l := self visibleLineToAbsoluteLine:visLineNr.
    isSubMenuEntry := (subMenus notNil and:[(subMenus at:l) notNil]).

    isSubMenuEntry ifFalse:[
        "/ this aligns them along their left
        x := width - textStartLeft - self shortKeyInset.
    ] ifTrue:[
        "/ this aligns them at the right
        x := width - leftMargin - (font widthOf:s).
        x := x - 16    "/ should query for the arrow size here ...
    ].

    hilightStyle == #openwin ifTrue:[
        x := x - 2            "/ inset of rounded rectangle
    ].

    self drawLine:s fromX:x inVisible:visLineNr with:fg and:bg

    "Created: 28.2.1996 / 18:48:05 / cg"
    "Modified: 2.3.1996 / 16:24:13 / cg"
!

drawCheckLine:line inVisibleLine:visLineNr with:fg and:bg
    "draw an on/off-mark (or the space for it).
     Supported checkmark types:
        \c  simple mark; space if off
        \b  box mark
        \t  thumbsUp/thumbsDown mark
    "

    |w h y x l check xR yB form markIndex i2 markType|

    l := self visibleLineToListLine:visLineNr.
    onOffFlags isNil ifTrue:[
        check := false
    ] ifFalse:[
        check := (onOffFlags at:l) == true.
    ].

    i2 := markIndex := 1.
    [markIndex ~~ 0 and:[i2 ~~ (markIndex+1)]] whileTrue:[
        markIndex := line indexOf:$\.
        i2 := line indexOfAny:'cbt' startingAt:markIndex+1.
    ].
    markType := line at:i2.

    x := (self xOfCol:markIndex inVisibleLine:visLineNr) - leftOffset.
    y := (self yOfVisibleLine:visLineNr) - (lineSpacing//2).

    markIndex ~~ 1 ifTrue:[
        super drawVisibleLine:visLineNr from:1 to:(markIndex-1) with:fg and:bg.
    ] ifFalse:[
        self paint:bg.
        self fillRectangleX:margin y:y width:(textStartLeft - margin) height:fontHeight.
    ].

    (markType == $c) ifTrue:[
        w := font widthOf:'V'.
    ] ifFalse:[
        (markType == $b) ifTrue:[
            w := font maxWidth. "/ font widthOf:'   '.
        ] ifFalse:[
            (markType == $t) ifTrue:[
                w := 16.
                check ifTrue:[form := Cursor thumbsUp sourceForm]
                      ifFalse:[form := Cursor thumbsDown sourceForm]
            ]
        ]
    ].

    self paint:bg.
    self fillRectangleX:x y:y width:w height:fontHeight.

    self drawLine:(line copyFrom:markIndex+2) fromX:x+w inVisible:visLineNr with:fg and:bg.
    self paint:(check ifTrue:[checkColor == bg ifTrue:[fg] ifFalse:[checkColor]] ifFalse:[fg]).

    h := font ascent.
    y := y + (font height - h // 2).
    yB := y + h - 1.

    (markType == $c) ifTrue:[
        check ifTrue:[
            xR := x + (w // 3).
            self displayLineFromX:x y:(y + (h // 2)) toX:xR y:yB.
            self displayLineFromX:xR y:yB toX:(x + w - 1) y:y
        ]
    ] ifFalse:[
        (markType == $t) ifTrue:[
            self displayForm:form x:x y:y
        ] ifFalse:[
            (markType == $b) ifTrue:[
                check ifTrue:[
                    xR := x + w - 2.
                    self displayLineFromX:x y:y toX:xR y:yB.
                    self displayLineFromX:xR y:y toX:x y:yB.
                ].
                self paint:fg.
                self displayRectangleX:x y:y width:h height:h.
            ]
        ]
    ]

    "Modified: 31.8.1995 / 19:27:02 / claus"
    "Created: 26.2.1996 / 23:18:00 / cg"
    "Modified: 28.2.1996 / 14:14:29 / cg"
!

drawVisibleLine:visLineNr with:fg and:bg
    |l lineString isSpecial key|

    l := self visibleLineToListLine:visLineNr.
    lineString := self visibleAt:visLineNr.

    isSpecial := lineString notNil and:[lineString includes:$\].
    isSpecial ifFalse:[
        "
         a normal entry
        "
        super drawVisibleLine:visLineNr with:fg and:bg
    ] ifTrue:[
        "
         some speciality in this line
        "
        (self isCheckItem:lineString) ifTrue:[
            "
             (check-mark)
            "
            self drawCheckLine:lineString inVisibleLine:visLineNr with:fg and:bg
        ] ifFalse:[
            super drawLine:lineString inVisible:visLineNr with:fg and:bg.
        ].
    ].

    "/
    "/ is there a shortKey ?
    "/
    ((ShowAcceleratorKeys ~~ false)
    and:[shortKeys notNil 
    and:[(key := shortKeys at:l ifAbsent:nil) notNil]]) ifTrue:[
        self drawAccelerator:key inVisibleLine:visLineNr with:fg and:bg
    ]

    "Modified: 2.3.1996 / 14:54:43 / cg"
!

drawVisibleLineSelected:visLineNr with:fg and:bg
    "redraw a single line as selected."

    |listLine
     y  "{ Class: SmallInteger }" 
     y2 "{ Class: SmallInteger }" 
     r2 radius topLeftColor botRightColor |


    hilightStyle ~~ #openwin ifTrue:[
        ^ super drawVisibleLineSelected:visLineNr with:fg and:bg.
    ].

    "
     openwin draws selections in a menu as (edged) rounded rectangles
    "
    listLine := self visibleLineToListLine:visLineNr.
    listLine notNil ifTrue:[

        self drawVisibleLine:visLineNr with:fg and:bg.

        y := (self yOfVisibleLine:visLineNr)  - (lineSpacing//2).
        y2 := y + fontHeight - 1.
        r2 := font height.
        radius := r2 // 2.
        "
         refill with normal bg, where arcs will be drawn below
        "
        self paint:bgColor.
        self fillRectangleX:margin y:y width:radius height:fontHeight.
        self fillRectangleX:width-radius-margin y:y width:radius height:fontHeight.
        "
         fill the arcs
        "
        self paint:hilightBgColor.
        self fillArcX:1+margin+1 y:y w:r2 h:r2+1+1 from:90 angle:180. 
        self fillArcX:width-r2-1-1-margin-1 y:y w:r2 h:r2+1+1 from:270 angle:180. 

        "
         a highlight-border around
        "
        hilightFrameColor notNil ifTrue:[
            self paint:hilightFrameColor.
            self displayLineFromX:radius+2 y:y toX:width-radius-3 y:y.
            self displayLineFromX:radius+2 y:y2 toX:width-radius-3 y:y2.

            self displayArcX:1+margin+1 y:y w:r2 h:r2+1+1 from:90 angle:180. 
            self displayArcX:width-r2-1-1-margin-1 y:y w:r2 h:r2+1+1 from:270 angle:180. 
            ^ self
        ].

        "
         an edge around
        "
        (hilightLevel ~~ 0) ifTrue:[
            (hilightLevel < 0) ifTrue:[
                topLeftColor := shadowColor.
                botRightColor := lightColor.
            ] ifFalse:[
                topLeftColor := lightColor.
                botRightColor := shadowColor.
            ].

            self paint:topLeftColor.
            self displayLineFromX:radius+2 y:y toX:width-radius-3 y:y.

            self displayArcX:1+margin+1 y:y w:r2 h:r2+1+1 from:90 angle:125. 
            self displayArcX:width-r2-1-1-margin-1 y:y w:r2 h:r2+1+1 from:270+125 angle:55. 

            self paint:botRightColor.

            self displayLineFromX:radius+2 y:y2 toX:width-radius-3 y:y2.
            self displayArcX:1+margin+1 y:y w:r2 h:r2+1+1 from:90+125 angle:55. 
            self displayArcX:width-r2-1-1-margin-1 y:y w:r2 h:r2+1+1 from:270 angle:125. 
        ].
        ^ self
    ].
    ^ super drawVisibleLine:visLineNr with:fg and:bg

    "Created: 28.2.1996 / 18:41:17 / cg"
    "Modified: 28.2.1996 / 19:42:57 / cg"
! !

!MenuView methodsFor:'event handling'!

buttonMotion:state x:x y:y
    state ~~ 0 ifTrue:[
	self setSelectionForX:x y:y
    ]
!

buttonPress:button x:x y:y
    self setSelectionForX:x y:y
!

buttonRelease:button x:x y:y
    |hide|

    subMenuShown notNil ifTrue:[
        ^ self
    ].

    (x >= 0 and:[x < width]) ifTrue:[
        (y >= 0 and:[y < height]) ifTrue:[
            superMenu notNil ifTrue:[
                superMenu submenuTriggered.

                shown not ifTrue:[
                    superView notNil ifTrue:[
                        superView shown ifTrue:[
                            superView hide
                        ]
                    ]
                ]
            ].
            self performSelectedAction.
        ]
    ].

    "/
    "/ not within mySelf
    "/

    superMenu notNil ifTrue:[
        hide := hideOnRelease.
        hide ifFalse:[
            superMenu shown not ifTrue:[
                superView notNil ifTrue:[
                    superView shown ifTrue:[
                        hide := true
                    ]
                ]
            ].
        ].
        hide ifTrue:[
            superView hide
        ].
    ].

"/    (superView notNil and:[superView isPopUpView]) ifTrue:[
"/ 'refetch focus' printNL.
"/        superView regainControl.
"/        superView getKeyboardFocus.
"/        superView hide
"/    ]

    "Modified: 8.3.1996 / 14:06:15 / cg"
!

keyPress:aKey x:x y:y

    <resource: #keyboard (#Return #MenuSelect #Escape)>

    |m|

    subMenuShown notNil ifTrue:[
        subMenuShown keyPress:aKey x:0 y:0.
        ^ self
    ].

    "
     Return, space or the (virtual) MenuSelect
     key trigger a selected entry.
    "
    (aKey == #Return
    or:[aKey == #MenuSelect
    or:[aKey == Character space]]) ifTrue:[
        selection notNil ifTrue:[
            (subMenus notNil and:[(m := subMenus at:selection) notNil]) ifTrue:[
                self showSubmenu:selection.
                m hideOnLeave:false
            ] ifFalse:[
                subMenuShown := nil.
                self buttonRelease:2 x:0 y:0.
            ]
        ].
        ^ self
    ].
    aKey == #Escape ifTrue:[
        masterView notNil ifTrue:[
            masterView hideSubmenu.
            masterView regainControl.
            masterView hide.
        ].
        superView hide.

        ^ self
    ].
    super keyPress:aKey x:x y:y

    "Modified: 7.3.1996 / 13:17:25 / cg"
!

pointerLeave:state
    subMenuShown notNil ifTrue:[
	^ self
    ].
"/    self setSelectionForX:-1 y:-1. "force deselect"
    subMenuShown isNil ifTrue:[
	self selection:nil
    ].
"/    superMenu notNil ifTrue:[
"/        superMenu regainControl.
"/    ]
! !

!MenuView methodsFor:'initialize / release'!

create
    super create.
    subMenuShown := nil.
    self resizeIfChanged
!

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

initEvents
    super initEvents.
    self enableLeaveEvents.

    windowGroup notNil ifTrue:[
        windowGroup sensor compressMotionEvents:true
    ]

    "Modified: 7.3.1996 / 14:18:09 / cg"
!

initStyle
    |style|

    super initStyle.

"/    DefaultFont notNil ifTrue:[font := DefaultFont on:device].

    DefaultCheckColor notNil ifTrue:[
        checkColor := DefaultCheckColor
    ] ifFalse:[
        checkColor := fgColor.
    ].
    disabledFgColor := DefaultDisabledForegroundColor on:device.

    DefaultForegroundColor notNil ifTrue:[
        fgColor := DefaultForegroundColor on:device
    ].
    DefaultBackgroundColor notNil ifTrue:[
        bgColor := DefaultBackgroundColor on:device
    ].

    DefaultShadowColor notNil ifTrue:[
        shadowColor := DefaultShadowColor on:device
    ].
    DefaultLightColor notNil ifTrue:[
        lightColor := DefaultLightColor on:device
    ].

    DefaultHilightLevel notNil ifTrue:[
        hilightLevel := DefaultHilightLevel
    ] ifFalse:[
        hilightLevel := 0.
    ].
    hilightStyle := DefaultHilightStyle.

    hilightFrameColor := DefaultHilightFrameColor.

    styleSheet is3D ifTrue:[
        "some 3D style menu - set hilight defaults to same"

        DefaultHilightForegroundColor notNil ifTrue:[
            hilightFgColor := DefaultHilightForegroundColor on:device
        ] ifFalse:[
            hilightFgColor := fgColor.
        ].
        DefaultHilightBackgroundColor notNil ifTrue:[
            hilightBgColor := DefaultHilightBackgroundColor on:device
        ] ifFalse:[
            hilightBgColor := bgColor.
        ].
        DefaultLineLevel notNil ifTrue:[
            lineLevel := DefaultLineLevel
        ] ifFalse:[
            lineLevel := -1.
        ]
    ] ifFalse:[
        "some 2D style menu - set hilight defaults to inverse"
        DefaultHilightForegroundColor notNil ifTrue:[
            hilightFgColor := DefaultHilightForegroundColor on:device
        ] ifFalse:[
            hilightFgColor := bgColor.
        ].
        DefaultHilightBackgroundColor notNil ifTrue:[
            hilightBgColor := DefaultHilightBackgroundColor on:device
        ] ifFalse:[
            hilightBgColor := fgColor.
        ].
        DefaultLineLevel notNil ifTrue:[
            lineLevel := DefaultLineLevel
        ] ifFalse:[
            lineLevel := 0.
        ]
    ].

    DefaultLineInset notNil ifTrue:[
        lineInset := DefaultLineInset
    ] ifFalse:[
        lineInset := (device horizontalPixelPerMillimeter * 0.8) rounded.
    ].

    "
     the following has to be changed to
     use the styleSheet too
    "
    style := styleSheet name.

    (style == #iris) ifTrue:[
        device hasGreyscales ifTrue:[
            lineSpacing := 3
        ].
    ].
    (style == #motif) ifTrue:[
        lineSpacing := (2 * hilightLevel)
    ].
"/ stupid - these are clobbered somewhere; see initialize and recreate
"/    hilightStyle == #openwin ifTrue:[
"/        "add some space for rounded-hilight area"
"/        self leftMargin:(font height // 2 + 2 "inset of rounded rect") "10".
"/    ] ifFalse:[
"/        (hilightLevel ~~ 0) ifTrue:[
"/            self leftMargin:hilightLevel abs + self margin abs + 1.
"/            lineSpacing := lineSpacing max:(hilightLevel abs * 2).
"/        ]
"/    ].
    (style == #st80) ifTrue:[
        level := 0.
    ].
    DefaultViewBackground notNil ifTrue:[
        viewBackground := DefaultViewBackground on:device
    ].

    "Modified: 28.2.1996 / 19:40:12 / cg"
!

initialize
    |style|

    super initialize.
    hideOnRelease := false.
    autoScroll := false.
    sizeFixed := false.

    (((style := styleSheet name) ~~ #normal) 
    and:[style ~~ #mswindows]) ifTrue:[
        borderWidth := 1.
        (style ~~ #st80) ifTrue:[self level:1]
    ].

    "stupid - have to redo this ..."
    hilightStyle == #openwin ifTrue:[
        "add some space for rounded-hilight area"
        self leftMargin:(font height // 2 + 2 "inset of rounded rect") "10".
    ] ifFalse:[
        (hilightLevel ~~ 0) ifTrue:[
            self leftMargin:hilightLevel abs + self margin abs + 1.
            lineSpacing := lineSpacing max:(hilightLevel abs * 2).
        ]
    ].

    "Modified: 28.2.1996 / 19:39:28 / cg"
!

recreate
    "when recreated after a snapin, resize myself, in case
     font dimensions have changed on the display"

    super recreate.
    hilightStyle == #openwin ifTrue:[
        "add some space for rounded-hilight area"
        self leftMargin:(font height // 2 + 2 "inset of rounded rect") "10".
    ] ifFalse:[
        (hilightLevel ~~ 0) ifTrue:[
            self leftMargin:hilightLevel abs + self margin abs + 1.
            lineSpacing := lineSpacing max:(hilightLevel abs * 2).
        ]
    ].
    self resize

    "Modified: 28.2.1996 / 19:39:37 / cg"
!

reinitialize
    "this is called right after snapIn;
     a kind of kludge - reset cursor (in case the save was
     done with myself being shown and active)"

    super reinitialize.
    selection := nil. "self selection:nil."
    self showPassive
! !

!MenuView methodsFor:'private'!

hideSubmenu
    subMenuShown notNil ifTrue:[
        subMenuShown hide.
        subMenuShown := nil.
        self deselect.
    ].

    "Modified: 8.3.1996 / 14:16:09 / cg"
!

isCheckItem:line
    line notNil ifTrue:[
        (line includesString:'\c') ifTrue:[^ true].
        (line includesString:'\b') ifTrue:[^ true].
        (line includesString:'\t')ifTrue:[^ true].
    ].
    ^ false.

    "Modified: 26.2.1996 / 23:16:12 / cg"
!

isGraphicItem:line
    (line = '-') ifTrue:[^ true].
    (line = '=') ifTrue:[^ true].
    (line = '') ifTrue:[^ true].
    ^ false.
!

performSelectedAction
    |theSelector isCheck checkOn val|

    superView isPopUpView ifTrue:[superView hide].
    superMenu notNil ifTrue:[superMenu submenuTriggered].

    selection notNil ifTrue:[
        (subMenus isNil or:[(subMenus at:selection) isNil]) ifTrue:[
            self showActive.
            [
                superMenu notNil ifTrue:[
                    superMenu showActive
                ].

                val := selection.
                args notNil ifTrue:[
                    val := args at:selection
                ].

                isCheck := false.
                onOffFlags notNil ifTrue:[
                    onOffFlags size >= selection ifTrue:[
                        checkOn := (onOffFlags at:selection).
                        isCheck := checkOn notNil.
                        isCheck ifTrue:[
                            checkOn := val := checkOn not.
                            onOffFlags at:selection put:checkOn.
                        ]
                    ]
                ].

                "
                 ST-80 style model notification
                "
                self sendChangeMessageWith:val.

                "
                 either action-block or selectors-array-style
                "
                actionBlock notNil ifTrue:[
                    AbortSignal handle:[:ex |
                        ex return
                    ] do:[
                        actionBlock numArgs == 1 ifTrue:[
                            actionBlock value:selection
                        ] ifFalse:[
                            actionBlock value:self value:selection
                        ]
                    ]
                ] ifFalse:[
                    selectors notNil ifTrue: [
                        device activePointerGrab == self ifTrue:[
                            device ungrabPointer.
                        ].
                        selectors isSymbol ifFalse:[
                            (selection notNil 
                             and:[selection <= selectors size]) ifTrue:[
                                theSelector := selectors at:selection
                            ]
                        ] ifTrue:[
                            theSelector := selectors
                        ].
                        theSelector notNil ifTrue:[
                            AbortSignal handle:[:ex |
                                ex return
                            ] do:[
                                theSelector numArgs == 0 ifTrue:[
                                    receiver perform:theSelector
                                ] ifFalse:[
                                    isCheck ifTrue:[
                                        self redrawLine:selection.
                                        val := checkOn.
                                    ].
                                
                                    receiver perform:theSelector with:val 
                                ]
                            ]
                        ]
                    ]
                ].
            ] valueNowOrOnUnwindDo:[
                realized ifTrue:[
                    self showPassive.
                ].
                superMenu notNil ifTrue:[
                    superMenu showPassive
                ]
            ].
        ].
    ]

    "Created: 4.3.1996 / 11:19:22 / cg"
    "Modified: 7.3.1996 / 18:59:59 / cg"
!

recomputeSize
    "resize myself to my preferred size
     OBSOLETE - use resize"

    self resize.
!

resize
    "resize myself to my preferred size"

    sizeFixed == true ifFalse:[
        widthOfWidestLine := nil.  "/ i.e. unknown
        super resize.
    ]

    "Modified: 9.2.1996 / 02:42:32 / cg"
!

resizeIfChanged
    needResize == true ifTrue:[
	self resize.
	needResize := false
    ]
!

selectionChangedFrom:oldSelection

    "Created: 4.3.1996 / 22:10:54 / cg"
!

setSelectionForX:x y:y
    "select whatever is under x/y coordinate - if there is
     a subMenu, show it"

    |newSelection subMenu|

    (x < 0 
    or:[x >= width
    or:[y < 0
    or:[y >= height]]]) ifTrue:[
        "
         moved outside submenu, but not within self
        "
        subMenuShown notNil ifTrue:[
            ^ self
        ].
        superMenu notNil ifTrue:[
            superMenu regainControl
        ].
    ].

    newSelection := self positionToSelectionX:x y:y.
    newSelection ~= selection ifTrue:[
        newSelection notNil ifTrue:[
            (enableFlags at:newSelection) ifFalse:[
                newSelection := nil
            ]
        ].

        subMenuShown notNil ifTrue:[
            self hideSubmenu.
        ].

        self selection:newSelection.
    ].

    subMenu := nil.
    selection notNil ifTrue:[
        subMenus notNil ifTrue:[
            x > (width // 2) ifTrue:[
                subMenu := (subMenus at:selection)
            ]
        ]
    ].
    subMenu notNil ifTrue:[
        self showSubmenu:selection.
    ] ifFalse:[
        subMenuShown notNil ifTrue:[
            self hideSubmenu.
        ].
        subMenuShown := nil
    ]

    "Modified: 8.3.1996 / 14:20:59 / cg"
!

showSubmenu:index
    "show subMenu at index"

    |org mx my m|

    m := subMenus at:index.
    m isNil ifTrue:[^ self].
    m == subMenuShown ifTrue:[^ self].

    mx := width - 5.
    my := self yOfVisibleLine:index.
    "
     need to know the physical screen coordinate,
     to map the subview there
    "
    org := device 
                translatePoint:(mx @ my) 
                from:(self id) 
                to:(device rootWindowId).

    "
     before showing, process all of my expose events
    "
    "/ mhmh - is this still needed ?
    windowGroup notNil ifTrue:[
        windowGroup processExposeEvents
    ].

    m superMenu:self.

    actionBlock notNil ifTrue:[
        "/ mhmh - I am an ST-80 style menu
        "/ which does not send any messages to the receiver,
        "/ but returns the selector instead.
        "/ let my submenu do so as well ...

         m menuView action:actionBlock
    ].

    "
     realize the submenu in MY windowgroup
    "
    windowGroup notNil ifTrue:[
        m windowGroup:windowGroup.
        windowGroup addTopView:m.
    ].
    m fixSize.
    m origin:org.
    m makeFullyVisible.
    m noShadow.
    m realize. 
    device flush.

    subMenuShown := m

    "Modified: 7.3.1996 / 18:23:59 / cg"
! !

!MenuView methodsFor:'queries'!

preferredExtent 
    |margin2 w h extra|

    widthOfWidestLine := nil.  "/ i.e. unknown

    margin2 := margin * 2.
    w := self widthOfContents + leftMargin + leftMargin + margin2.
    h := (self numberOfLines) * fontHeight - lineSpacing + (2 * topMargin) + margin2.
    hilightLevel ~~ 0 ifTrue:[
        h := h + (hilightLevel abs)
    ].

    extra := 0.
    "if there is a submenu, add some space for the right arrow"
    subMenus notNil ifTrue:[
        extra := 16
    ].
    ((ShowAcceleratorKeys ~~ false) and:[shortKeys notNil]) ifTrue:[
        extra := extra max:(self shortKeyInset) + 10 "/ spacing
    ].
    ^ ((w+extra) @ h).

    "Modified: 2.3.1996 / 14:54:52 / cg"
!

shortKeyInset
    "compute the width req'd for the shortKey"

    maxShortKeyStringLen isNil ifTrue:[

        shortKeys isNil ifTrue:[
            maxShortKeyStringLen := 0
        ] ifFalse:[
            maxShortKeyStringLen := shortKeys 
                                        inject:0 
                                        into:[:maxSoFar :thisKey | |short|

                                                thisKey isNil ifTrue:[
                                                    maxSoFar
                                                ] ifFalse:[
                                                    short := self shortKeyStringFor:thisKey.
                                                    short isNil ifTrue:[
                                                        maxSoFar
                                                    ] ifFalse:[
                                                        maxSoFar max:(font widthOf:short)
                                                    ]
                                                ]
                                             ]
        ].
    ].
    ^ maxShortKeyStringLen

    "Created: 28.2.1996 / 16:30:09 / cg"
    "Modified: 28.2.1996 / 18:26:37 / cg"
!

shortKeyPrefixFor:aModifier
    |m|

"/    aModifier = 'Alt' ifTrue:[
"/        ^ '@-'
"/    ].
"/    aModifier = 'Cmd' ifTrue:[
"/        ^ '@-'
"/    ].
"/    aModifier = 'Meta' ifTrue:[
"/        ^ '$-'
"/    ].
"/    aModifier = 'Ctrl' ifTrue:[
"/        ^ '^-'
"/    ].
"/    ^ aModifier.

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

    aModifier = 'Alt' ifTrue:[
        ^ 'Alt-'
    ].
    aModifier = 'Cmd' ifTrue:[
        (device keyboardMap keyAtValue:'Cmd' ifAbsent:nil) notNil ifTrue:[
            self halt.
        ].
        ^ 'Cmd-'
    ].
    aModifier = 'Meta' ifTrue:[
        ^ 'Meta-'
    ].
    aModifier = 'Ctrl' ifTrue:[
        ^ 'Ctrl-'
    ].
    ^ aModifier

    "Created: 28.2.1996 / 16:32:17 / cg"
    "Modified: 28.2.1996 / 17:08:29 / cg"
!

shortKeyStringFor:aSymbolicKey
    |untranslatedKey x|

    "/ this is somewhat complicated: we have the symbolic key at hand,
    "/ but want to show the untranslated (inverse keyBoardMapped) key & modifier
    "/

    untranslatedKey := device keyboardMap keyAtValue:aSymbolicKey ifAbsent:nil.
    untranslatedKey notNil ifTrue:[
        "/
        "/ some modifier-key combination ?
        "/
        (untranslatedKey startsWith:'Cmd') ifTrue:[
            ^ (self shortKeyPrefixFor:'Cmd') , (untranslatedKey copyFrom:4)
        ].
        (untranslatedKey startsWith:'Alt') ifTrue:[
            ^ (self shortKeyPrefixFor:'Alt') , (untranslatedKey copyFrom:4)
        ].
        (untranslatedKey startsWith:'Meta') ifTrue:[
            ^ (self shortKeyPrefixFor:'Meta') , (untranslatedKey copyFrom:5)
        ].
        (untranslatedKey startsWith:'Ctrl') ifTrue:[
            ^ (self shortKeyPrefixFor:'Ctrl') , (untranslatedKey copyFrom:5)
        ].
        "/
        "/ a function key ?
        "/
        (untranslatedKey startsWith:'F') ifTrue:[
            (untranslatedKey size > 1) ifTrue:[
                (untranslatedKey at:2) isDigit ifTrue:[
                    ^ untranslatedKey
                ]
            ]
        ].
        "/
        "/ some other special key ?
        "/
        untranslatedKey isSymbol ifTrue:[
            ^ untranslatedKey
        ]
    ].
    ^ aSymbolicKey

    "Created: 28.2.1996 / 18:20:09 / cg"
    "Modified: 2.3.1996 / 13:56:09 / cg"
! !

!MenuView methodsFor:'redrawing'!

redrawFromVisibleLine:start to:stop
    "redraw a line range - redefined to care for special entries."

    "/ the natural way to do it is:
    "/
    "/    start to:stop do:[:visLine |
    "/        self redrawVisibleLine:visLine
    "/    ]
    "/
    "/ but I want to draw the stuff in big chunks for slow machines ...
    "/ Q: is it worth it ?

    |first 
     index   "{ Class: SmallInteger }"
     current "{ Class: SmallInteger }"
     line special index0|

    index0 := self visibleLineToListLine:start.
    index0 notNil ifTrue:[
        index := index0.
        first := start.
        current := start.
        [current <= stop] whileTrue:[
            line := (self visibleAt:current) string.

            special := line notNil 
                       and:[(self isGraphicItem:line) 
                            or:[line includes:$\ ]].

            (special
            or:[shortKeys notNil
            or:[(enableFlags at:index) not]]) ifTrue:[
                "a special case"
                (first < current) ifTrue:[
                    super redrawFromVisibleLine:first to:(current - 1)
                ].
                self redrawVisibleLine:current.
                first := current + 1
            ].
            current := current + 1.
            index := index + 1
        ].
        (first < current) ifTrue:[
            super redrawFromVisibleLine:first to:(current - 1)
        ].

        "draw submenu marks"
        subMenus notNil ifTrue:[
            index := index0.
            start to:stop do:[:l |
                index <= subMenus size ifTrue:[
                    (subMenus at:index) notNil ifTrue:[
                        self drawRightArrowInVisibleLine:l
                    ].
                    index := index + 1
                ]
            ]
        ]
    ]

    "Modified: 28.2.1996 / 14:52:05 / cg"
!

redrawVisibleLine:visLineNr
    "redefined from normal list-line drawing, to handle special
     lines. These are:
        lines consisting of '-' only: draw a horizontal separating line
        lines consisting of '=' only: draw double separating line
        empty line                  : leave blank
     there may be more in the future.
    "

    |line lineNr y isSpecial isSeparatingLine 
     isDoubleLine right clr1 clr2 key|

    line := self visibleAt:visLineNr.

    isSpecial := isDoubleLine := isSeparatingLine := false.
    (line = '-') ifTrue:[
        isSeparatingLine := isSpecial := true.
    ] ifFalse:[
        (line = '=') ifTrue:[
            isSeparatingLine := isSpecial := isDoubleLine := true.
        ] ifFalse:[
            (line = '') ifTrue:[
                isSpecial := true
            ]
        ]
    ].

    isSpecial ifFalse:[
        lineNr := self visibleLineToListLine:visLineNr.
        (enableFlags at:lineNr) ifFalse:[
            self drawVisibleLine:visLineNr with:disabledFgColor and:bgColor
        ] ifTrue:[
            super redrawVisibleLine:visLineNr
        ].

        "/
        "/ is there a submenu ?
        "/
        (subMenus notNil and:[(subMenus at:lineNr ifAbsent:nil) notNil]) ifTrue:[
            self drawRightArrowInVisibleLine:visLineNr
        ].
        ^ self
    ].

    "/
    "/ handle separating lines
    "/

    y := self yOfVisibleLine:visLineNr.

    self paint:bgColor.
    self fillRectangleX:0 y:y width:width height:fontHeight.

    isSeparatingLine ifTrue:[
        y := y + (fontHeight // 2).
        isDoubleLine ifTrue:[
            y := y - (fontHeight // 8).
        ].

        right := width - 1 - lineInset.

        lineLevel == 0 ifTrue:[
            self paint:fgColor.
            self displayLineFromX:lineInset y:y toX:right y:y.
            isDoubleLine ifTrue:[
                y := y + (fontHeight // 4).
                self displayLineFromX:lineInset y:y toX:right y:y
            ]
        ] ifFalse:[
            "the inset on each side"

            lineLevel < 0 ifTrue:[
                clr1 := shadowColor.
                clr2 := lightColor.
            ] ifFalse:[
                clr1 := lightColor.
                clr2 := shadowColor.
            ].

            self paint:clr1.
            self displayLineFromX:lineInset y:y toX:right y:y.
            self paint:clr2.
            y := y + 1.
            self displayLineFromX:lineInset y:y toX:right y:y.
            isDoubleLine ifTrue:[
                y := y + (fontHeight // 4).
                self displayLineFromX:lineInset y:y toX:right y:y.
                y := y - 1.
                self paint:clr1.
                self displayLineFromX:lineInset y:y toX:right y:y.
            ]
        ]
    ]

    "Modified: 2.3.1996 / 14:48:08 / cg"
!

redrawVisibleLine:visLine col:col
    "redefined to always draw a full line - for openwin handling"

    self redrawVisibleLine:visLine
!

redrawVisibleLine:visLine from:startCol
    "redefined to always draw a full line - for openwin handling"

    self redrawVisibleLine:visLine
!

redrawVisibleLine:visLine from:startCol to:endCol
    "redefined to always draw a full line - for openwin handling"

    self redrawVisibleLine:visLine
! !

!MenuView methodsFor:'selections'!

isValidSelection:aNumber
    "return true, if aNumber is ok for a selection lineNo"

    |line|

    (super isValidSelection:aNumber) ifFalse:[^ false].

    line := self listAt:aNumber.
    ^ (self isGraphicItem:line) not
! !

!MenuView methodsFor:'showing'!

realize
    self resizeIfChanged.
    super realize

    "Modified: 28.2.1996 / 18:17:05 / cg"
!

show
    hiddenOnRealize := false.
    self realize
! !

!MenuView methodsFor:'submenu notifications'!

regainControl
    "take over pointer control from a submenu"

    masterView notNil ifTrue:[
        masterView regainControl.
        subMenuShown := nil.
    ].

    "Modified: 4.3.1996 / 23:17:15 / cg"
!

showActive
    "submenu is about to perform a menu-action - show wait cursor here as well"

    self cursor:(Cursor wait)
!

showPassive
    "submenu has finished its menu-action - show normal cursor again"

    self cursor:(Cursor hand)
!

submenuTriggered
    "submenu has performed some action - have to deselect here"

    self selection:nil.

    "a bad kludge - 5 minutes before writing the alpha tapes ..."
    superView isPopUpView ifTrue:[
        superView hide
    ].
    superMenu notNil ifTrue:[
        superMenu submenuTriggered 
    ].

    "Modified: 4.3.1996 / 23:00:19 / cg"
! !

!MenuView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/MenuView.st,v 1.62 1996-03-08 13:44:36 cg Exp $'
! !