Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
TheWorldMenu - a simpler version
Last updated at 12:08 pm UTC on 31 October 2017
A simpler version for TheWorldMenu proposed by Edgar J De Cleene.

It may be used in a image meant for distribution as an 'application'.

See How to lockdown an image for release

 !TheWorldMenu methodsFor: 'construction' stamp: 'edc 1/29/2006 07:18'!
buildWorldMenu
   "Build the menu that is put up when the screen-desktop is  clicked on"
   | menu |
   menu := MenuMorph new defaultTarget: self.
   menu commandKeyHandler: self.
   self colorForDebugging: menu.

   menu addStayUpItem.

   self fillIn: menu from: {
       {'restore display (r)'. {World. #restoreMorphicDisplay}. 
        'repaint the screen -- useful for removing unwanted display artifacts, lingering cursors, etc.'}. nil}.

   Preferences simpleMenus
       ifFalse: [self fillIn: menu from: 
                  {{'open...'. {self. #openWindow}}.
                  {'windows...'. {self. #windowsDo}}. 
                  {'changes...'. {self. #changesDo}}}
                ].

   self fillIn: menu from: 
                  {{'help...'. {self. #helpDo}. 'puts up a menu of useful items for updating the system, determining what version you are running, and much else'}.              
                  {'appearance...'. {self. #appearanceDo}. 'put up a menu offering many controls over appearance.'}}.


   Preferences simpleMenus
       ifFalse: [self fillIn: menu from: 
                  {{'do...'. {Utilities.  #offerCommonRequests}. 'put up an editible list of convenient expressions, and evaluate the one selected.'}}
                ].


   self fillIn: menu from: {
       nil.
       {'new morph...' . { self  . #newMorph }. 'Offers a variety of ways to create new objects'}.
       nil.}.


   Preferences simpleMenus
       ifFalse: [self fillIn: menu from: 
                  {{'debug...'. {self. #debugDo}. 'a  menu of debugging items'}}
                ].

   self fillIn: menu from: 
                 {nil. 
                 {'save'. {SmalltalkImage current. #saveSession}. 'save the current version of the image on disk'}. 
                 {'save as...'. {SmalltalkImage current. #saveAs}. 'save the current version of the image on disk under a new name.'}. 
                 {'save as new version'. {SmalltalkImage current. #saveAsNewVersion}. 'give the current image a new version-stamped name and save it under that name on disk.'}. 
                 {'save and quit'. {self. #saveAndQuit}. 'save the current image on disk, and quit out of Squeak.'}.
                 {'quit'. {self. #quitSession}. 'quit out of Squeak.'}
                 }.

   ^ menu! !



Based on what you have in your image adapt it to your needs. This is just a proposal.

See also
buildWorldMenu