NewLauncher.st
changeset 2712 9e861058daab
parent 2708 6eac2958b3ee
child 2713 3867d98f0a54
--- a/NewLauncher.st	Thu Aug 17 11:56:50 2000 +0200
+++ b/NewLauncher.st	Thu Aug 17 16:00:42 2000 +0200
@@ -16,11 +16,18 @@
 
 AbstractLauncherApplication subclass:#NewLauncher
 	instanceVariableNames:'isMainLauncher helpIsOn'
-	classVariableNames:'UserAddedTools'
+	classVariableNames:'UserAddedMenuItems UserAddedToolBarItems'
 	poolDictionaries:''
 	category:'Interface-Smalltalk'
 !
 
+Object subclass:#AddedToolInfo
+	instanceVariableNames:'item positionSpec space before menuWithNewItem'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:NewLauncher
+!
+
 !NewLauncher class methodsFor:'documentation'!
 
 copyright
@@ -64,6 +71,65 @@
         Claus Gittinger, eXept Software AG
 "
 
+!
+
+examples
+"
+    reopening a standard launcher (without any added tools)
+                                                                        [exBegin]
+     NewLauncher removeAllUserAddedTools.
+     NewLauncher open.
+                                                                        [exEnd]
+
+
+
+    adding your own menu items (for user-applications)
+
+    an additional item in the tools menu:
+                                                                        [exBegin]
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Foo';
+                        value: [Transcript showCR:'foo invoked'];
+                        isButton: false;
+                        labelImage: nil;
+                        nameKey: #foo;
+                        activeHelpKey: #Foo)
+        in:#menu
+        position:(#before #workspace)
+        space:true
+                                                                        [exEnd]
+
+    an additional item in the tools menu:
+                                                                        [exBegin]
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Foo';
+                        value: [Transcript showCR:'foo invoked'];
+                        isButton: false;
+                        labelImage: nil;
+                        activeHelpKey: #Foo)
+        in:#menu
+        position:(#after #guiPainter)
+        space:true
+                                                                        [exEnd]
+
+    an additional item in one of the tools sub menus:
+                                                                        [exBegin]
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Foo';
+                        value: [Transcript showCR:'foo invoked'];
+                        isButton: false;
+                        labelImage: nil;
+                        activeHelpKey: #Foo)
+        in:#menu
+        position:'Workspace'
+        before:true
+        space:true
+                                                                        [exEnd]
+"
+
 ! !
 
 !NewLauncher class methodsFor:'accessing'!
@@ -73,6 +139,10 @@
     ^'Launcher'
 
 
+!
+
+removeAllUserAddedTools
+    UserAddedTools := nil
 ! !
 
 !NewLauncher class methodsFor:'defaults'!
@@ -2369,116 +2439,18 @@
 
 !NewLauncher methodsFor:'menu configuration'!
 
-addUserTool:toolName action:actionBlock icon:iconOrNil
-    "adds a menu item labeled toolName, and action and icon both to the
-     sub menu 'Tools' and the tool bar.
-     This can be invoked by a classes #initialize method, to add an item
-     for itself to the toolbar.
-    "
-
-    self 
-        addUserTool:toolName 
-        action:actionBlock 
-        in:nil 
-        icon:iconOrNil 
-        space:true
-
-    "
-     Transcript topView application
-        addUserTool:'Foo' 
-        action:[Transcript showCR:'foo'] 
-        icon:nil
-    "
-!
-
-addUserTool:toolName action:actionBlock in:where after:afterOrNil icon:icon space:space
-    "adds a menu item labeled toolName, and actionBlock and icon;
+addMenuItem:newItem in:where position:positionSpecOrNilArg space:space
+    "adds a menu item;
        where == #menu        - menu item is added at the end of the sub menu 'Tools',
        where == #toolbar     - menu item is added at the end of the tool bar,
        where == #menu.<name> - menu item is added at the end of the sub menu named 'name',
 
-     If space is true, some empty space is inserted.
-     This can be invoked by a classes #initialize method, to add an item
-     for itself to the toolbar or menu.
-    "
-
-    ^ self
-        addUserTool:toolName action:actionBlock in:where position:afterOrNil before:false icon:icon space:space
-
-    "
-     Transcript topView application
-        addUserTool:'Foo' 
-        action:[Transcript showCR:'foo']
-        in:#menu
-        icon:nil
-        space:false
-    "
-    "
-     Transcript topView application
-        addUserTool:'Bar' 
-        action:[Transcript showCR:'bar']
-        in:#menu
-        icon:nil
-        space:false
-    "
-!
-
-addUserTool:toolName action:actionBlock in:where before:afterOrNil icon:icon space:space
-    "adds a menu item labeled toolName, and actionBlock and icon;
-       where == #menu        - menu item is added at the end of the sub menu 'Tools',
-       where == #toolbar     - menu item is added at the end of the tool bar,
-       where == #menu.<name> - menu item is added at the end of the sub menu named 'name',
-
-     If space is true, some empty space is inserted.
-     This can be invoked by a classes #initialize method, to add an item
-     for itself to the toolbar or menu.
-    "
-
-    ^ self
-        addUserTool:toolName action:actionBlock in:where position:afterOrNil before:true icon:icon space:space
-!
-
-addUserTool:toolName action:actionBlock in:what icon:icon space:space
-    "adds a menu item labeled toolName, and actionBlock and icon;
-     for what == #menu    menu item is added at the end of the sub menu 'Tools',
-     for what == #toolbar menu item is added at the end of the tool bar,
-     If space is true, some empty space is inserted.
-     This can be invoked by a classes #initialize method, to add an item
-     for itself to the toolbar or menu.
-    "
-
-    ^ self
-        addUserTool:toolName 
-        action:actionBlock 
-        in:what 
-        after:nil 
-        icon:icon 
-        space:space
-
-    "
-     Transcript topView application
-        addUserTool:'Foo' 
-        action:[Transcript showCR:'foo']
-        in:#menu
-        icon:nil
-        space:false
-    "
-    "
-     Transcript topView application
-        addUserTool:'Bar' 
-        action:[Transcript showCR:'bar']
-        in:#menu
-        icon:nil
-        space:false
-    "
-
-!
-
-addUserTool:toolName action:actionBlock in:where position:itemNameOrNil before:before icon:icon space:space
-    "adds a menu item labeled toolName, and actionBlock and icon;
-       where == #menu        - menu item is added at the end of the sub menu 'Tools',
-       where == #toolbar     - menu item is added at the end of the tool bar,
-       where == #menu.<name> - menu item is added at the end of the sub menu named 'name',
+    position may be one of:
+        ( #before <someItemPath> )
+        ( #after  <someItemPath> )
+        ( #first )   or #first
+        ( #last )    or #last
+        nil   (same as last)
 
      If space is true, some empty space is inserted.
      This can be invoked by a classes #initialize method, to add an item
@@ -2486,14 +2458,33 @@
     "
 
     |what menuPanel freeMenuIndex mainMenuPanel item subViews subMenuPath 
-     rest subMenu subItem menuWithNewItem nItems|
+     rest subMenu subItem nItems idx 
+     positionSpecOrNil itemNameOrNil before|
+
+    positionSpecOrNil := positionSpecOrNilArg.
+    positionSpecOrNil isArray ifTrue:[
+        positionSpecOrNil size > 1 ifTrue:[
+            itemNameOrNil := positionSpecOrNil at:2.
+        ].
+        positionSpecOrNil := positionSpecOrNil at:1.
+    ].
+    before := (positionSpecOrNil == #first) or:[positionSpecOrNil == #before].
 
     what := where.
     (what isNil or: [what = 'toolbar']) ifTrue:[
+        "/ look if not already in the toolBar
         menuPanel := builder namedComponents at: #menuToolbarView.
 
-        (menuPanel findFirst: [:i| i activeHelpKey = toolName or:[i label = toolName]]) == 0
-        ifTrue:[
+        idx := 0.
+        newItem nameKey notNil ifTrue:[
+            idx := menuPanel findFirst: [:i| i nameKey = newItem nameKey].
+        ].
+        idx == 0 ifTrue:[
+            idx := menuPanel findFirst: [:i| (newItem activeHelpKey notNil and:[ i activeHelpKey = newItem activeHelpKey])
+                                              or:[ newItem label notNil and:[ i label = newItem label] ]]
+        ].
+        idx == 0 ifTrue:[
+            "/ ok, not there; search for the position to put the item
             nItems := menuPanel numberOfItems.
             freeMenuIndex := 0.
             itemNameOrNil notNil ifTrue:[
@@ -2502,22 +2493,29 @@
                     freeMenuIndex := menuPanel findFirst: [:i| i activeHelpKey = itemNameOrNil or:[i label = itemNameOrNil]].
                 ]
             ].
+
             freeMenuIndex == 0 ifTrue:[
-                freeMenuIndex := (before ifTrue:1 ifFalse:[nItems + 1]).
+                freeMenuIndex := before ifTrue:1 ifFalse:[nItems + 1].
+            ] ifFalse:[
+                before ifFalse:[freeMenuIndex := freeMenuIndex +1].
             ].
 
             space ifTrue:[
                 (menuPanel createAtIndex: freeMenuIndex) menuItem: (MenuItem labeled: '').
                 freeMenuIndex := freeMenuIndex + (before ifTrue:0 ifFalse:1).
+
             ].
 
-            (menuPanel createAtIndex: freeMenuIndex) menuItem:
-                (MenuItem new 
-                    label: toolName;
-                    value: actionBlock;
-                    isButton: true;
-                    labelImage: icon;
-                    activeHelpKey: toolName asSymbol)
+            (menuPanel createAtIndex: freeMenuIndex) menuItem:newItem.
+
+            UserAddedToolBarItems isNil ifTrue: [UserAddedToolBarItems := Dictionary new].
+            UserAddedToolBarItems at:newItem put:(AddedToolInfo new
+                                                item:newItem;
+                                                positionSpec:positionSpecOrNilArg;
+                                                space:space;
+                                                before:before;
+                                                menuWithNewItem:menuPanel;
+                                                yourself)
         ].
     ].
 
@@ -2571,8 +2569,19 @@
         item isNil ifTrue:[^ self].
         menuPanel := item submenu.
 
-        (menuPanel findFirst: [:i| i activeHelpKey = toolName or:[i label = toolName]]) == 0
-        ifTrue:[
+        "/ look if not already in the menu
+        idx := 0.
+        newItem nameKey notNil ifTrue:[
+            idx := menuPanel findFirst: [:i| i nameKey = newItem nameKey].
+        ].
+        idx == 0 ifTrue:[
+            idx := menuPanel findFirst: [:i| (newItem activeHelpKey notNil and:[ i activeHelpKey = newItem activeHelpKey])
+                                              or:[ newItem label notNil and:[ i label = newItem label] ]]
+        ].
+
+        idx == 0 ifTrue:[
+            "/ ok, not there; search for the position to put the item
+
             nItems := menuPanel numberOfItems.
             freeMenuIndex := 0.
             itemNameOrNil notNil ifTrue:[
@@ -2582,27 +2591,138 @@
                 ]
             ].
             freeMenuIndex == 0 ifTrue:[
-                freeMenuIndex := (before ifTrue:1 ifFalse:[nItems + 1]).
+                freeMenuIndex := before ifTrue:1 ifFalse:[nItems + 1].
+            ] ifFalse:[
+                before ifFalse:[freeMenuIndex := freeMenuIndex +1].
             ].
             space ifTrue:[
                 (menuPanel createAtIndex: freeMenuIndex) menuItem: (MenuItem labeled: '-').
                 freeMenuIndex := freeMenuIndex + (before ifTrue:0 ifFalse:1).
             ].
 
-            (menuPanel createAtIndex:freeMenuIndex) menuItem:
-                (MenuItem new 
-                    label: toolName;
-                    value: actionBlock;
-                    labelImage: (LabelAndIcon icon: icon string: toolName);
-                    activeHelpKey: toolName asSymbol) .
-            menuWithNewItem := menuPanel.
+            (menuPanel createAtIndex:freeMenuIndex) menuItem:newItem.
+
+            UserAddedMenuItems isNil ifTrue: [UserAddedMenuItems := Dictionary new].
+            UserAddedMenuItems at:newItem put:(AddedToolInfo new
+                                                item:newItem;
+                                                positionSpec:positionSpecOrNilArg;
+                                                space:space;
+                                                before:before;
+                                                menuWithNewItem:menuPanel;
+                                                yourself)
         ].
     ].
 
-    UserAddedTools isNil ifTrue: [UserAddedTools := Dictionary new].
-    UserAddedTools 
-        at:toolName 
-        put:(Array with:actionBlock with:what with:icon with:space with:itemNameOrNil with:before with:menuWithNewItem)
+    "
+     UserAddedToolBarItems := nil.
+     UserAddedMenuItems := nil.
+     NewLauncher open.
+
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Foo';
+                        value: [Transcript showCR:'foo'];
+                        isButton: false;
+                        labelImage: nil;
+                        nameKey: #foo)
+        in:#menu
+        position:#(#before 'Workspace')
+        space:true
+
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Bar';
+                        value: [Transcript showCR:'bar'];
+                        isButton: false;
+                        labelImage: nil;
+                        nameKey: #bar)
+        in:#menu
+        position:#(#after #foo)
+        space:true
+
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Baz';
+                        value: [Transcript showCR:'baz'];
+                        isButton: false;
+                        labelImage: nil;
+                        nameKey: #baz)
+        in:#menu
+        position:#(#before #bar)
+        space:false
+
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Baz2';
+                        value: [Transcript showCR:'baz2'];
+                        isButton: false;
+                        labelImage: nil;
+                        nameKey: #baz2)
+        in:#menu
+        position:#(#after #bar)
+        space:false
+
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Foo2';
+                        value: [Transcript showCR:'foo2'];
+                        isButton: false;
+                        labelImage: nil;
+                        nameKey: #foo2)
+        in:'menu.classes'
+        position:#last
+        space:false
+
+     Transcript topView application
+        addMenuItem:(MenuItem new 
+                        label: 'Foo3';
+                        value: [Transcript showCR:'foo3'];
+                        isButton: false;
+                        labelImage: nil;
+                        nameKey: #foo3)
+        in:'menu.classes.special'
+        position:#first
+        space:true
+    "
+!
+
+addUserTool:toolName action:actionBlock icon:iconOrNil
+    "adds a menu item labeled toolName, and action and icon both to the
+     sub menu 'Tools' and the tool bar.
+     This can be invoked by a classes #initialize method, to add an item
+     for itself to the toolbar.
+     OBSOLETE
+    "
+
+    self 
+        addUserTool:toolName 
+        action:actionBlock 
+        in:nil 
+        icon:iconOrNil 
+        space:true
+
+    "
+     Transcript topView application
+        addUserTool:'Foo' 
+        action:[Transcript showCR:'foo'] 
+        icon:nil
+    "
+!
+
+addUserTool:toolName action:actionBlock in:where after:afterOrNil icon:icon space:space
+    "adds a menu item labeled toolName, and actionBlock and icon;
+       where == #menu        - menu item is added at the end of the sub menu 'Tools',
+       where == #toolbar     - menu item is added at the end of the tool bar,
+       where == #menu.<name> - menu item is added at the end of the sub menu named 'name',
+
+     If space is true, some empty space is inserted.
+     This can be invoked by a classes #initialize method, to add an item
+     for itself to the toolbar or menu.
+     OBSOLETE
+    "
+
+    ^ self
+        addUserTool:toolName action:actionBlock in:where position:afterOrNil before:false icon:icon space:space
 
     "
      Transcript topView application
@@ -2622,54 +2742,186 @@
     "
 !
 
-removeUserTool:toolName
+addUserTool:toolName action:actionBlock in:where before:afterOrNil icon:icon space:space
+    "adds a menu item labeled toolName, and actionBlock and icon;
+       where == #menu        - menu item is added at the end of the sub menu 'Tools',
+       where == #toolbar     - menu item is added at the end of the tool bar,
+       where == #menu.<name> - menu item is added at the end of the sub menu named 'name',
+
+     If space is true, some empty space is inserted.
+     This can be invoked by a classes #initialize method, to add an item
+     for itself to the toolbar or menu.
+     OBSOLETE
+    "
+
+    ^ self
+        addUserTool:toolName action:actionBlock in:where position:afterOrNil before:true icon:icon space:space
+!
+
+addUserTool:toolName action:actionBlock in:what icon:icon space:space
+    "adds a menu item labeled toolName, and actionBlock and icon;
+     for what == #menu    menu item is added at the end of the sub menu 'Tools',
+     for what == #toolbar menu item is added at the end of the tool bar,
+     If space is true, some empty space is inserted.
+     This can be invoked by a classes #initialize method, to add an item
+     for itself to the toolbar or menu.
+     OBSOLETE
+    "
+
+    ^ self
+        addUserTool:toolName 
+        action:actionBlock 
+        in:what 
+        after:nil 
+        icon:icon 
+        space:space
+
+    "
+     UserAddedTools := nil.
+     NewLauncher open.
+
+     Transcript topView application
+        addUserTool:'Foo' 
+        action:[Transcript showCR:'foo']
+        in:#menu
+        icon:nil
+        space:false
+    "
+    "
+     Transcript topView application
+        addUserTool:'Bar' 
+        action:[Transcript showCR:'bar']
+        in:#menu
+        icon:nil
+        space:true
+    "
+
+!
+
+addUserTool:toolName action:actionBlock in:where position:itemNameOrNil before:before icon:icon space:space
+    "adds a menu item labeled toolName, and actionBlock and icon;
+       where == #menu        - menu item is added at the end of the sub menu 'Tools',
+       where == #toolbar     - menu item is added at the end of the tool bar,
+       where == #menu.<name> - menu item is added at the end of the sub menu named 'name',
+
+     If space is true, some empty space is inserted.
+     This can be invoked by a classes #initialize method, to add an item
+     for itself to the toolbar or menu.
+     OBSOLETE
+    "
+
+    |newItem positionSpecOrNilArg|
+
+    newItem := (MenuItem new 
+                    label: toolName;
+                    value: actionBlock;
+                    isButton: false;
+                    labelImage: icon;
+                    nameKey: toolName asSymbol;
+                    activeHelpKey: toolName asSymbol).
+
+    itemNameOrNil isNil ifTrue:[
+        positionSpecOrNilArg := before ifTrue:[#first] ifFalse:[#last].
+    ] ifFalse:[
+        positionSpecOrNilArg := before ifTrue:[#before] ifFalse:[#after].
+        positionSpecOrNilArg := Array with:itemNameOrNil with:positionSpecOrNilArg.
+    ].
+
+    ^ self addMenuItem:newItem in:where position:positionSpecOrNilArg space:space
+
+!
+
+removeUserTool:toolNameOrMenuItem
     "removes a menu item labeled toolName
      This can be invoked by a classes #deinitialize method, 
      to remove its item from the toolbar or menu.
     "
 
-    |userToolInfo space menuIndex removeInMenuBlock whichMenu before|
-
-    UserAddedTools isNil ifTrue: [^nil].
-    userToolInfo  := UserAddedTools at: toolName ifAbsent: [^nil].
-    space     := userToolInfo at: 4.
-    before    := userToolInfo at: 6.
-    whichMenu := userToolInfo at: 7.
-
-    removeInMenuBlock := 
-    [:menuPanel|
-        (menuIndex := menuPanel findFirst: [:i| i activeHelpKey = toolName]) ~~ 0
-        ifTrue:
-        [              
-            menuPanel remove: menuIndex.
-            space ifTrue: [
-                menuPanel remove:(menuIndex - (before ifTrue:0 ifFalse:1))
-            ].
-        ].
-    ].
-
-    removeInMenuBlock value: (builder namedComponents at: #menuToolbarView).
-    removeInMenuBlock value: ((self builder window subViews at: 1 ifAbsent: [^self]) itemAt: 4) submenu.
-    whichMenu notNil ifTrue:[removeInMenuBlock value: whichMenu].
-
-    UserAddedTools removeKey: toolName 
-
+    self removeUserTool:toolNameOrMenuItem from:UserAddedToolBarItems.
+    self removeUserTool:toolNameOrMenuItem from:UserAddedMenuItems.
+
+    "
+     Transcript topView application
+        removeUserTool:'Bar' 
+    "
     "
      Transcript topView application
         removeUserTool:'Foo' 
     "
+
+!
+
+removeUserTool:toolNameOrMenuItem from:addedToolsCollection
+    "removes a menu item labeled toolName
+     This can be invoked by a classes #deinitialize method, 
+     to remove its item from the toolbar or menu.
+    "
+
+    |info space menuIndex removeInMenuBlock whichMenu before menuItemToRemove|
+
+    addedToolsCollection size == 0 ifTrue: [^nil].
+
+    [true] whileTrue:[
+        (toolNameOrMenuItem isString or:[toolNameOrMenuItem isSymbol]) ifTrue:[
+            info := addedToolsCollection detect:[:eachInfo | |eachItem|
+                                            eachItem := eachInfo item.
+                                            (eachItem nameKey notNil and:[ toolNameOrMenuItem = eachItem nameKey])
+                                            or:[ (eachItem activeHelpKey notNil and:[ toolNameOrMenuItem = eachItem activeHelpKey])
+                                            or:[ (eachItem label notNil and:[ toolNameOrMenuItem = eachItem label])]]
+                                          ]
+                                   ifNone:nil.
+        ] ifFalse:[
+            info := addedToolsCollection detect:[:eachInfo | |eachItem| eachItem := eachInfo item. (eachItem == toolNameOrMenuItem)] ifNone:nil.
+        ].
+        info isNil ifTrue:[^ self].
+
+        space     := info space.
+        whichMenu := info menuWithNewItem.
+        menuItemToRemove := info item.
+        before := info before.
+
+        menuIndex := whichMenu findFirst:[:item | 
+                                                (item nameKey notNil and:[item nameKey == menuItemToRemove nameKey])
+                                                or:[ (item activeHelpKey notNil and:[item activeHelpKey == menuItemToRemove activeHelpKey])
+                                                or:[ (item label notNil and:[item label = menuItemToRemove label]) ]]
+                                         ].
+        menuIndex ~~ 0 ifTrue:[              
+            whichMenu remove: menuIndex.
+            space ifTrue: [
+                whichMenu remove:(menuIndex - (before ifTrue:0 ifFalse:1))
+            ].
+            addedToolsCollection removeKey:menuItemToRemove 
+        ] ifFalse:[
+            self halt.
+        ].
+    ].
+
+
     "
      Transcript topView application
         removeUserTool:'Bar' 
     "
+    "
+     Transcript topView application
+        removeUserTool:'Foo' 
+    "
 
 !
 
-userAddedTools
-    "return a collection of user-added tools.
+userAddedMenuItems
+    "return a dictionary of user-added menu item infos.
     "
 
-    ^ UserAddedTools ? #()
+    ^ UserAddedMenuItems ? #()
+
+
+!
+
+userAddedToolBarItems
+    "return a dictionary of user-added toolBar item infos.
+    "
+
+    ^ UserAddedToolBarItems ? #()
 
 
 ! !
@@ -2778,14 +3030,17 @@
 
     "/ add user tools
     UserAddedTools notNil ifTrue:[
-        UserAddedTools associationsDo: 
-        [:userTool| 
-            self addUserTool: userTool key 
-                action: (userTool value at: 1)  
-                in:     (userTool value at: 2) 
-                after:  (userTool value at: 5)
-                icon:   (userTool value at: 3)
-                space:  (userTool value at: 4)
+        UserAddedTools do:[:toolInfo| 
+            |item|
+
+            item := toolInfo at:1.
+self halt.        
+"/            self addUserTool: userTool key 
+"/                action: (userTool value at: 1)  
+"/                in:     (userTool value at: 2) 
+"/                after:  (userTool value at: 5)
+"/                icon:   (userTool value at: 3)
+"/                space:  (userTool value at: 4)
         ].
     ].
 
@@ -3102,8 +3357,60 @@
     "Created: / 21.8.1998 / 20:44:12 / cg"
 ! !
 
+!NewLauncher::AddedToolInfo methodsFor:'accessing'!
+
+before
+    "return the value of the instance variable 'before' (automatically generated)"
+
+    ^ before!
+
+before:something
+    "set the value of the instance variable 'before' (automatically generated)"
+
+    before := something.!
+
+item
+    "return the value of the instance variable 'item' (automatically generated)"
+
+    ^ item!
+
+item:something
+    "set the value of the instance variable 'item' (automatically generated)"
+
+    item := something.!
+
+menuWithNewItem
+    "return the value of the instance variable 'menuWithNewItem' (automatically generated)"
+
+    ^ menuWithNewItem!
+
+menuWithNewItem:something
+    "set the value of the instance variable 'menuWithNewItem' (automatically generated)"
+
+    menuWithNewItem := something.!
+
+positionSpec
+    "return the value of the instance variable 'positionSpec' (automatically generated)"
+
+    ^ positionSpec!
+
+positionSpec:something
+    "set the value of the instance variable 'positionSpec' (automatically generated)"
+
+    positionSpec := something.!
+
+space
+    "return the value of the instance variable 'space' (automatically generated)"
+
+    ^ space!
+
+space:something
+    "set the value of the instance variable 'space' (automatically generated)"
+
+    space := something.! !
+
 !NewLauncher class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/NewLauncher.st,v 1.189 2000-08-16 12:31:49 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/NewLauncher.st,v 1.190 2000-08-17 14:00:42 cg Exp $'
 ! !