OldLauncher.st
changeset 219 379dfea373d7
parent 165 df29ee4514c1
child 553 b67caadfe334
--- a/OldLauncher.st	Sat Nov 25 19:09:44 1995 +0100
+++ b/OldLauncher.st	Mon Nov 27 23:17:59 1995 +0100
@@ -11,10 +11,10 @@
 "
 
 StandardSystemView subclass:#Launcher
-       instanceVariableNames:'myMenu logoLabel'
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Interface-Smalltalk'
+	 instanceVariableNames:'myMenu logoLabel'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Interface-Smalltalk'
 !
 
 !Launcher class methodsFor:'documentation'!
@@ -33,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libtool/OldLauncher.st,v 1.33 1995-11-11 15:40:19 cg Exp $'
-!
-
 documentation
 "
     Launcher allows startup of smalltalk applications.
@@ -65,8 +61,147 @@
     ^ 'smallTalk'
 ! !
 
+!Launcher methodsFor:'accessing'!
+
+menu
+    ^ myMenu
+! !
+
+!Launcher methodsFor:'demo menu actions'!
+
+openDemo:className
+    (Smalltalk at:className) open
+!
+
+startAnimation
+    self openDemo:#Animation 
+!
+
+startCommanderDemo
+    self openDemo:#CommanderDemo 
+!
+
+startGlobeDemo
+    self openDemo:#GlobeDemo 
+!
+
+startLogicTool
+    self openDemo:#LogicTool 
+!
+
+startPenDemo
+    self openDemo:#PenDemo 
+!
+
+startTetris
+    self openDemo:#Tetris
+!
+
+startTicTacToe
+    self openDemo:#TicTacToe 
+! !
+
+!Launcher methodsFor:'doc menu actions'!
+
+showAbout
+    AboutBox new show
+!
+
+showCustomizing
+    self showOnlineHelp:'custom/TOP'
+!
+
+showGettingStarted
+    self showOnlineHelp:'getstart/TOP'
+!
+
+showOnlineHelp:baseName
+    self warn:'HTML online help support is is not included in this package.
+Use any HTML viewer on the files found in doc/online.
+
+Starting view on ascii version of the text ....
+'.
+    self showDocumentFile:'doc/online/english/' , baseName
+!
+
+showOverview
+    self showDocumentFile:'misc/overview'
+!
+
+warnIfAbsent:aPath
+    |s|
+
+    s := Smalltalk systemFileStreamFor:aPath.
+    s isNil ifTrue:[
+	self warn:('document ' , aPath , ' not available').
+	^ nil
+    ].
+    ^ s  pathName
+! !
+
+!Launcher methodsFor:'event handling'!
+
+saveAndTerminate
+    "
+     some windowManagers can send this, to shutDown an application
+     but let it save its state before, for restart. We are already
+     prepared for this ;-)"
+
+    ObjectMemory snapShotOn:name
+! !
+
+!Launcher methodsFor:'goody menu actions'!
+
+startAddressBook
+    AddressBook open
+!
+
+startCalendar
+    Calendar open
+!
+
+startClock
+    Clock open
+!
+
+startDrawTool
+    DrawView open
+!
+
+startMailTool
+    MailView open
+!
+
+startNewsTool
+    NewsView open
+!
+
+startRoundClock
+    RoundClock2 open
+!
+
+startXterm
+    OperatingSystem executeCommand:'xterm &'
+! !
+
 !Launcher methodsFor:'initialize / release'!
 
+addToCurrentProject
+    "ignored here - the launcher is always global."
+
+    ^ self
+!
+
+destroy
+    "re-confirm when closing Launcher - we do this,
+     since if you close the last launcher, you might loose the possibility to
+     communicate with the system ..."
+
+    (self confirm:(resources string:'close ' , self class name , ' ?')) ifTrue:[
+	super destroy
+    ]
+!
+
 initialize
     super initialize.
 
@@ -515,95 +650,85 @@
     super reinitialize.
 "/    myMenu reinitialize.
 "/    self extent:(myMenu extent).
-!
-
-destroy
-    "re-confirm when closing Launcher - we do this,
-     since if you close the last launcher, you might loose the possibility to
-     communicate with the system ..."
-
-    (self confirm:(resources string:'close ' , self class name , ' ?')) ifTrue:[
-	super destroy
-    ]
-!
-
-addToCurrentProject
-    "ignored here - the launcher is always global."
-
-    ^ self
-! !
-
-!Launcher methodsFor:'accessing'!
-
-menu
-    ^ myMenu
-! !
-
-!Launcher methodsFor:'private'!
-
-showDocumentFile:name
-    |s f isRTF|
-
-    isRTF := true.
-    s := Smalltalk systemFileStreamFor:name , '.rtf'.
-    s isNil ifTrue:[
-	isRTF := false.
-	s := Smalltalk systemFileStreamFor:name , '.doc'.
-	s isNil ifTrue:[
-	    self warn:('document ' , name , ' (.rtf/.doc) not available.\\check your installation.' withCRs).
-	    ^ nil
-	].
-    ].
-    f := s pathName.
-
-    isRTF ifTrue:[
-	DocumentView openOn:f.
-	^ self
-    ].
-
-    (Workspace openOn:f) readOnly
-!
-
-saveScreenImage:anImage
-    "save an image into a file 
-     - ask user for filename using a fileSelectionBox."
-
-    |fileName|
-
-    fileName := Dialog
-		    requestFileName:'save image in:'
-		    default:''
-		    ok:'save'
-		    abort:'abort'
-		    pattern:'*.tiff'.
-
-    fileName notNil ifTrue:[
-	anImage saveOn:fileName
-    ].
-!
-
-closeDownViews
-    "tell each topview that we are going to terminate and give it chance
-     to save its contents."
-
-    ObjectMemory changed:#aboutToExit
-! !
-
-!Launcher methodsFor:'event handling'!
-
-saveAndTerminate
-    "
-     some windowManagers can send this, to shutDown an application
-     but let it save its state before, for restart. We are already
-     prepared for this ;-)"
-
-    ObjectMemory snapShotOn:name
 ! !
 
 !Launcher methodsFor:'menu actions'!
 
-startSystemBrowser
-    SystemBrowser open
+exitSmalltalk
+    |exitBox|
+
+    exitBox := EnterBox2 title:(resources at:'save state before exiting ?\\filename for image:') withCRs.
+    exitBox okText:(resources at:'exit').
+    exitBox okText2:(resources at:'save & exit').
+    exitBox label:'exit Smalltalk'.
+
+    exitBox action:[:dummyName | 
+	self closeDownViews.
+	Smalltalk exit
+    ].
+
+    exitBox action2:[:fileName | 
+	(ObjectMemory snapShotOn:fileName) ifFalse:[
+	    "
+	     snapshot failed for some reason (disk full, no permission etc.)
+	     Do NOT exit in this case.
+	    "
+	    self warn:(resources string:'failed to save snapshot image (disk full or not writable)').
+	] ifTrue:[
+	    "
+	     closeDownViews tells all views to shutdown neatly 
+	     (i.e. offer a chance to save the contents to a file).
+
+	     This is NOT required - all data should be in the snapshot ...
+	     ... however, if remote disks/mountable filesystems are involved,
+	     which may not be present the next time, it may make sense to 
+	     uncomment it and query for saving - time will show which is better.
+	    "
+"
+	    self closeDownViews.
+"
+	    Smalltalk exit
+	]
+    ].
+
+    exitBox initialText:(ObjectMemory nameForSnapshot).
+    exitBox showAtPointer
+!
+
+saveImage
+    |saveBox|
+
+    saveBox := EnterBox title:(resources at:'filename for image:') withCRs.
+    saveBox okText:(resources at:'save').
+    saveBox action:[:fileName | 
+	(ObjectMemory snapShotOn:fileName) ifFalse:[
+	    "
+	     snapshot failed for some reason (disk full, no permission etc.)
+	     Do NOT exit in this case.
+	    "
+	    self warn:(resources string:'failed to save snapshot image (disk full or not writable)').
+	]
+    ].
+
+    saveBox initialText:(ObjectMemory nameForSnapshot).
+    saveBox label:'save image'.
+    saveBox showAtPointer
+!
+
+startChangesBrowser
+    ChangesBrowser open
+!
+
+startDirectoryBrowser
+    DirectoryBrowser open
+!
+
+startDirectoryView
+    DirectoryView open
+!
+
+startFileBrowser
+    FileBrowser open
 !
 
 startHierarchyBrowser
@@ -652,216 +777,84 @@
     enterBox showAtPointer
 !
 
-startChangesBrowser
-    ChangesBrowser open
-!
-
-startFileBrowser
-    FileBrowser open
-!
-
-startDirectoryBrowser
-    DirectoryBrowser open
-!
-
-startDirectoryView
-    DirectoryView open
+startSystemBrowser
+    SystemBrowser open
 !
 
 startWorkspace
     Workspace open
-!
-
-saveImage
-    |saveBox|
-
-    saveBox := EnterBox title:(resources at:'filename for image:') withCRs.
-    saveBox okText:(resources at:'save').
-    saveBox action:[:fileName | 
-	(ObjectMemory snapShotOn:fileName) ifFalse:[
-	    "
-	     snapshot failed for some reason (disk full, no permission etc.)
-	     Do NOT exit in this case.
-	    "
-	    self warn:(resources string:'failed to save snapshot image (disk full or not writable)').
-	]
-    ].
-
-    saveBox initialText:(ObjectMemory nameForSnapshot).
-    saveBox label:'save image'.
-    saveBox showAtPointer
-!
-
-exitSmalltalk
-    |exitBox|
-
-    exitBox := EnterBox2 title:(resources at:'save state before exiting ?\\filename for image:') withCRs.
-    exitBox okText:(resources at:'exit').
-    exitBox okText2:(resources at:'save & exit').
-    exitBox label:'exit Smalltalk'.
-
-    exitBox action:[:dummyName | 
-	self closeDownViews.
-	Smalltalk exit
-    ].
-
-    exitBox action2:[:fileName | 
-	(ObjectMemory snapShotOn:fileName) ifFalse:[
-	    "
-	     snapshot failed for some reason (disk full, no permission etc.)
-	     Do NOT exit in this case.
-	    "
-	    self warn:(resources string:'failed to save snapshot image (disk full or not writable)').
-	] ifTrue:[
-	    "
-	     closeDownViews tells all views to shutdown neatly 
-	     (i.e. offer a chance to save the contents to a file).
-
-	     This is NOT required - all data should be in the snapshot ...
-	     ... however, if remote disks/mountable filesystems are involved,
-	     which may not be present the next time, it may make sense to 
-	     uncomment it and query for saving - time will show which is better.
-	    "
-"
-	    self closeDownViews.
-"
-	    Smalltalk exit
-	]
-    ].
-
-    exitBox initialText:(ObjectMemory nameForSnapshot).
-    exitBox showAtPointer
 ! !
 
-!Launcher methodsFor:'utility menu actions'!
+!Launcher methodsFor:'misc'!
 
-viewHardcopy
-    "after a second (to allow redraw of views under menu ...),
-     let user specify a view and save its contents."
+processName
+    "the name of my process - for the processMonitor only"
 
-    Processor addTimedBlock:[
-	|v|
+    ^ 'Launcher'.
+! !
 
-	v := Screen current viewFromUser.
-	v notNil ifTrue:[
-	    self saveScreenImage:(Image fromView:(v topView))
-	]
-    ] afterSeconds:1
-!
+!Launcher methodsFor:'private'!
 
-fullScreenHardcopy
-    "after a second (to allow redraw of views under menu ...),
-     save the contents of the whole screen."
+closeDownViews
+    "tell each topview that we are going to terminate and give it chance
+     to save its contents."
 
-    Processor addTimedBlock:[
-	self saveScreenImage:(Image fromScreen)
-    ] afterSeconds:1
+    ObjectMemory changed:#aboutToExit
 !
 
-screenHardcopy
-    "after a second (to allow redraw of views under menu ...),
-     let user specify a rectangular area on the screen
-     and save its contents."
-
-    |area|
+saveScreenImage:anImage
+    "save an image into a file 
+     - ask user for filename using a fileSelectionBox."
 
-    Processor addTimedBlock:[
-	area := Rectangle fromUser.
-	(area width > 0 and:[area height > 0]) ifTrue:[
-	    self saveScreenImage:(Image fromScreen:area)
-	]
-    ] afterSeconds:1
-!
-
-viewKiller
-    |v|
+    |fileName|
 
-    (Delay forSeconds:1) wait.
-    v := Screen current viewFromUser.
-    v isNil ifTrue:[
-	self warn:'sorry, this is not a smalltalk view'
-    ] ifFalse:[
-	v topView destroy
-    ]
-!
-
-viewInspector
-    |v|
+    fileName := Dialog
+		    requestFileName:'save image in:'
+		    default:''
+		    ok:'save'
+		    abort:'abort'
+		    pattern:'*.tiff'.
 
-    (Delay forSeconds:1) wait.
-    v := Screen current viewFromUser.
-    v isNil ifTrue:[
-	self warn:'sorry, this is not a smalltalk view'
-    ] ifFalse:[
-	v topView inspect
-    ]
-!
-
-startWindowTreeView
-    WindowTreeView open
+    fileName notNil ifTrue:[
+	anImage saveOn:fileName
+    ].
 !
 
-startClassTreeView
-    ClassTreeGraphView open
-!
-
-startEventMonitor
-    EventMonitor open
-!
-
-startProcessMonitor
-    ProcessMonitor open
-!
-
-startMemoryMonitor
-    MemoryMonitor open
-!
-
-startMemoryUsage
-    MemoryUsageView open
-!
+showDocumentFile:name
+    |s f isRTF|
 
-startTranscript
-    (Transcript isKindOf:TextCollector) ifTrue:[
-	"there is only one transcript - rais it"
-	Transcript topView raiseDeiconified.
-    ] ifFalse:[
-	Transcript := TextCollector newTranscript
-    ]
-!
-
-startScreenSaver1
-    ScreenSaver open
-!
+    isRTF := true.
+    s := Smalltalk systemFileStreamFor:name , '.rtf'.
+    s isNil ifTrue:[
+	isRTF := false.
+	s := Smalltalk systemFileStreamFor:name , '.doc'.
+	s isNil ifTrue:[
+	    self warn:('document ' , name , ' (.rtf/.doc) not available.\\check your installation.' withCRs).
+	    ^ nil
+	].
+    ].
+    f := s pathName.
 
-startScreenSaver2
-    LightInTheDark open
-!
+    isRTF ifTrue:[
+	DocumentView openOn:f.
+	^ self
+    ].
 
-startScreenSaver3
-    LightInTheDark2 open
-!
-
-garbageCollect
-    ObjectMemory markAndSweep
-!
-
-compressingGarbageCollect
-    ObjectMemory verboseGarbageCollect
+    (Workspace openOn:f) readOnly
 ! !
 
 !Launcher methodsFor:'project menu actions'!
 
+newProject
+    (ProjectView for:(Project new)) open
+!
+
 projectMenu
     "this is sent, if ST/X has been built without Projects/ChangeSets."
 
     self warn:'The system has been built without support for projects'.
 !
 
-newProject
-    (ProjectView for:(Project new)) open
-!
-
 selectProject
     |list box|
 
@@ -883,116 +876,125 @@
     box showAtPointer
 ! !
 
-!Launcher methodsFor:'goody menu actions'!
+!Launcher methodsFor:'utility menu actions'!
 
-startXterm
-    OperatingSystem executeCommand:'xterm &'
-!
-
-startAddressBook
-    AddressBook open
+compressingGarbageCollect
+    ObjectMemory verboseGarbageCollect
 !
 
-startNewsTool
-    NewsView open
+fullScreenHardcopy
+    "after a second (to allow redraw of views under menu ...),
+     save the contents of the whole screen."
+
+    Processor addTimedBlock:[
+	self saveScreenImage:(Image fromScreen)
+    ] afterSeconds:1
 !
 
-startDrawTool
-    DrawView open
-!
-
-startMailTool
-    MailView open
-!
-
-startClock
-    Clock open
+garbageCollect
+    ObjectMemory markAndSweep
 !
 
-startCalendar
-    Calendar open
+screenHardcopy
+    "after a second (to allow redraw of views under menu ...),
+     let user specify a rectangular area on the screen
+     and save its contents."
+
+    |area|
+
+    Processor addTimedBlock:[
+	area := Rectangle fromUser.
+	(area width > 0 and:[area height > 0]) ifTrue:[
+	    self saveScreenImage:(Image fromScreen:area)
+	]
+    ] afterSeconds:1
 !
 
-startRoundClock
-    RoundClock2 open
-! !
-
-!Launcher methodsFor:'demo menu actions'!
-
-openDemo:className
-    (Smalltalk at:className) open
+startClassTreeView
+    ClassTreeGraphView open
 !
 
-startLogicTool
-    self openDemo:#LogicTool 
+startEventMonitor
+    EventMonitor open
+!
+
+startMemoryMonitor
+    MemoryMonitor open
 !
 
-startAnimation
-    self openDemo:#Animation 
+startMemoryUsage
+    MemoryUsageView open
 !
 
-startGlobeDemo
-    self openDemo:#GlobeDemo 
+startProcessMonitor
+    ProcessMonitor open
 !
 
-startPenDemo
-    self openDemo:#PenDemo 
+startScreenSaver1
+    ScreenSaver open
 !
 
-startCommanderDemo
-    self openDemo:#CommanderDemo 
+startScreenSaver2
+    LightInTheDark open
 !
 
-startTicTacToe
-    self openDemo:#TicTacToe 
+startScreenSaver3
+    LightInTheDark2 open
 !
 
-startTetris
-    self openDemo:#Tetris
-! !
-
-!Launcher methodsFor:'doc menu actions'!
-
-warnIfAbsent:aPath
-    |s|
-
-    s := Smalltalk systemFileStreamFor:aPath.
-    s isNil ifTrue:[
-	self warn:('document ' , aPath , ' not available').
-	^ nil
-    ].
-    ^ s  pathName
+startTranscript
+    (Transcript isKindOf:TextCollector) ifTrue:[
+	"there is only one transcript - rais it"
+	Transcript topView raiseDeiconified.
+    ] ifFalse:[
+	Transcript := TextCollector newTranscript
+    ]
 !
 
-showAbout
-    AboutBox new show
+startWindowTreeView
+    WindowTreeView open
 !
 
-showOverview
-    self showDocumentFile:'misc/overview'
-!
+viewHardcopy
+    "after a second (to allow redraw of views under menu ...),
+     let user specify a view and save its contents."
 
-showCustomizing
-    self showOnlineHelp:'custom/TOP'
-!
+    Processor addTimedBlock:[
+	|v|
 
-showGettingStarted
-    self showOnlineHelp:'getstart/TOP'
+	v := Screen current viewFromUser.
+	v notNil ifTrue:[
+	    self saveScreenImage:(Image fromView:(v topView))
+	]
+    ] afterSeconds:1
 !
 
-showOnlineHelp:baseName
-    self warn:'HTML online help support is is not included in this package.
-Use any HTML viewer on the files found in doc/online.
+viewInspector
+    |v|
 
-Starting view on ascii version of the text ....
-'.
-    self showDocumentFile:'doc/online/english/' , baseName
+    (Delay forSeconds:1) wait.
+    v := Screen current viewFromUser.
+    v isNil ifTrue:[
+	self warn:'sorry, this is not a smalltalk view'
+    ] ifFalse:[
+	v topView inspect
+    ]
+!
+
+viewKiller
+    |v|
+
+    (Delay forSeconds:1) wait.
+    v := Screen current viewFromUser.
+    v isNil ifTrue:[
+	self warn:'sorry, this is not a smalltalk view'
+    ] ifFalse:[
+	v topView destroy
+    ]
 ! !
 
-!Launcher methodsFor:'misc'!
+!Launcher class methodsFor:'documentation'!
 
-processName
-    "the name of my process - for the processMonitor only"
-
-    ^ 'Launcher'.
+version
+    ^ '$Header: /cvs/stx/stx/libtool/OldLauncher.st,v 1.34 1995-11-27 22:17:59 cg Exp $'
 ! !