Launcher.st
changeset 1129 983669d631f0
parent 1128 48ceeb13f45d
child 1130 7c1dd53a3b55
--- a/Launcher.st	Thu Apr 10 20:30:55 1997 +0200
+++ b/Launcher.st	Thu Apr 10 21:00:11 1997 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -23,7 +23,7 @@
 copyright
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -46,38 +46,38 @@
     adding more buttons to the button-panel:
 
       see the method #buttonPanelSpec;
-        it defines a list of selectors and icons, which is used by 
-        #setupButtonPanelIn:. 
-        There, for each entry, a button with that icon is created, 
-        which sends a selector-message to the launcher.
-
-        Add entries to that list, and define appropriate methods.
-        For example, to add a button which opens a drawTool,
-        change #buttonPanelSpec to:
-
-        buttonPanelSpec
-            ^ #(
-                #(startSystemBrowser  'SBrowser32x32.xbm')
-                #(startFileBrowser    'FBrowser32x32.xbm')
-                #(nil nil)
-                #(startChangesBrowser 'CBrowser32x32.xbm')
-                #(nil nil)
-                #(nil nil)
-                #(startDrawTool       'DrawTool.xbm')
-             )
-
-        the panel adjusts its height as appropriate - you may want to
-        create new (small) icons for a good look.
+	it defines a list of selectors and icons, which is used by 
+	#setupButtonPanelIn:. 
+	There, for each entry, a button with that icon is created, 
+	which sends a selector-message to the launcher.
+
+	Add entries to that list, and define appropriate methods.
+	For example, to add a button which opens a drawTool,
+	change #buttonPanelSpec to:
+
+	buttonPanelSpec
+	    ^ #(
+		#(startSystemBrowser  'SBrowser32x32.xbm')
+		#(startFileBrowser    'FBrowser32x32.xbm')
+		#(nil nil)
+		#(startChangesBrowser 'CBrowser32x32.xbm')
+		#(nil nil)
+		#(nil nil)
+		#(startDrawTool       'DrawTool.xbm')
+	     )
+
+	the panel adjusts its height as appropriate - you may want to
+	create new (small) icons for a good look.
 
     adding an entry to a menu:
 
-        see the #setupMenu method; either add another top-menu, or
-        add entries to an existing menu.
-        All menu setup has been extracted into separate init-methods,
-        so there is often only a need to redefine one of those
-        (for example, to add your own demos, only redefine setupDemoMenu).
-        To add a new master-item with its own pullDown, redefine setupMainMenu
-        to include another selector and add the correspoonding menu there.
+	see the #setupMenu method; either add another top-menu, or
+	add entries to an existing menu.
+	All menu setup has been extracted into separate init-methods,
+	so there is often only a need to redefine one of those
+	(for example, to add your own demos, only redefine setupDemoMenu).
+	To add a new master-item with its own pullDown, redefine setupMainMenu
+	to include another selector and add the correspoonding menu there.
 "
 !
 
@@ -94,18 +94,18 @@
     launcher functions.
 
     Notice:
-        Since there can only be one SystemTranscript, opening a new launcher
-        will automatically close the current one (except for a remote launcher,
-        opened on another display).
+	Since there can only be one SystemTranscript, opening a new launcher
+	will automatically close the current one (except for a remote launcher,
+	opened on another display).
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        Examples_misc::MyLauncher
+	Examples_misc::MyLauncher
 
     [start with:]
-        Launcher open
+	Launcher open
 "
 !
 
@@ -114,18 +114,18 @@
     As ST/X can handle multiple screens, there is nothing (except fear ;-)
     from preventing you to work with your friend in the same image.
     To do this, evaluate (replace localhost by whatever):
-                                                                        [exBegin]
-        |display2|
-
-        display2 := XWorkstation new initializeFor:'localhost:0'.
-        display2 isNil ifTrue:[
-            self warn:'cannot connect.'.
-        ] ifFalse:[
-            display2 startDispatch.
-            display2 keyboardMap:(Display keyboardMap).
-            Launcher openOnDevice:display2.
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|display2|
+
+	display2 := XWorkstation new initializeFor:'localhost:0'.
+	display2 isNil ifTrue:[
+	    self warn:'cannot connect.'.
+	] ifFalse:[
+	    display2 startDispatch.
+	    display2 keyboardMap:(Display keyboardMap).
+	    Launcher openOnDevice:display2.
+	]
+									[exEnd]
     But you should be somewhat careful, the other guy may change things so
     that you are blocked (start high prio processes, change classes etc.)
     Anyway, a nice demo ....
@@ -139,9 +139,9 @@
      (for access via addMenu/ removeMenu)"
 
     OpenLaunchers do:[:aLauncher |
-        aLauncher window graphicsDevice == Screen current ifTrue:[
-            ^ aLauncher
-        ]
+	aLauncher window graphicsDevice == Screen current ifTrue:[
+	    ^ aLauncher
+	]
     ].
     ^ nil.
 
@@ -165,18 +165,18 @@
 
     image := Image fromFile:'SmalltalkX.xbm'.
     image notNil ifTrue:[
-        |green dark|
-
-        Screen current hasColors ifTrue:[
-            green := (Color redPercent:0 greenPercent:80 bluePercent:20) "darkened".
-            dark := Color grayPercent:10.
-            image photometric:#palette.
-        ] ifFalse:[
-            dark := Color black.
-            green := Color white.
-            image photometric:#blackIs0.
-        ].
-        image colorMap:(Array with:dark with:green).
+	|green dark|
+
+	Screen current hasColors ifTrue:[
+	    green := (Color redPercent:0 greenPercent:80 bluePercent:20) "darkened".
+	    dark := Color grayPercent:10.
+	    image photometric:#palette.
+	] ifFalse:[
+	    dark := Color black.
+	    green := Color white.
+	    image photometric:#blackIs0.
+	].
+	image colorMap:(Array with:dark with:green).
 "/        Screen current depth > 2 ifTrue:[
 "/            image := (Image implementorForDepth:Screen current depth) fromImage:image.
 "/        ]
@@ -214,7 +214,7 @@
      handler is the notifying one."
 
     NotifyingEmergencyHandler isNil ifTrue:[
-        NotifyingEmergencyHandler := Exception notifyingEmergencyHandler
+	NotifyingEmergencyHandler := Exception notifyingEmergencyHandler
     ].
     ^ NotifyingEmergencyHandler
 
@@ -229,7 +229,7 @@
 
     image := self aboutIcon.
     image notNil ifTrue:[
-        image := image magnifiedBy:0.4.
+	image := image magnifiedBy:0.4.
     ].
     ^ image
 
@@ -275,19 +275,19 @@
      its better than nothing ...
     "
     HTMLDocumentView notNil ifTrue:[
-        "
-         temporary kludge;
-         not all machines can autoload binaries;
-         however, on my SGI (which can) we want it
-         to load automatically.
-        "
-        HTMLDocumentView isLoaded ifFalse:[
-            ErrorSignal catch:[HTMLDocumentView autoload]
-        ].
-        HTMLDocumentView isLoaded ifTrue:[
-            HTMLDocumentView openFullOnDocumentationFile:aRelativeDocFilePath. 
-            ^ self
-        ].
+	"
+	 temporary kludge;
+	 not all machines can autoload binaries;
+	 however, on my SGI (which can) we want it
+	 to load automatically.
+	"
+	HTMLDocumentView isLoaded ifFalse:[
+	    ErrorSignal catch:[HTMLDocumentView autoload]
+	].
+	HTMLDocumentView isLoaded ifTrue:[
+	    HTMLDocumentView openFullOnDocumentationFile:aRelativeDocFilePath. 
+	    ^ self
+	].
     ].
 
     self warn:'Sorry, the ST/X HTML reader is not (yet) 
@@ -309,9 +309,9 @@
 
     ((lang := Smalltalk language) = 'de'
     or:[lang = 'german']) ifTrue:[
-        doc := 'german/LICENCE.STX.html'
+	doc := 'german/LICENCE.STX.html'
     ] ifFalse:[
-        doc := 'english/LICENCE.STX.html'
+	doc := 'english/LICENCE.STX.html'
     ].
     doc := resources at:'LICENCEFILE' default:doc.
     self showDocumentation:('../' , doc)
@@ -364,12 +364,12 @@
     "turn on/off active help"
 
     ActiveHelp notNil ifTrue:[
-        helpIsOn := aBoolean.
-        helpIsOn ifTrue:[
-            ActiveHelp start
-        ] ifFalse:[
-            ActiveHelp stop
-        ]
+	helpIsOn := aBoolean.
+	helpIsOn ifTrue:[
+	    ActiveHelp start
+	] ifFalse:[
+	    ActiveHelp stop
+	]
     ].
 
     "Modified: 8.1.1997 / 14:37:30 / cg"
@@ -385,9 +385,9 @@
     enterBox := EnterBox title:(resources at:'Browse implementors of:') withCRs.
     enterBox okText:(resources at:'browse').
     enterBox action:[:selectorName |
-        |cls|
-
-        self withWaitCursorDo:[SystemBrowser browseImplementorsOf:selectorName]  
+	|cls|
+
+	self withWaitCursorDo:[SystemBrowser browseImplementorsOf:selectorName]  
     ].
     enterBox showAtPointer
 
@@ -424,28 +424,28 @@
     box destroy.
 
     box accepted ifTrue:[
-        rsrc := resourceHolder value.
-        value := valueHolder value.
-
-        (rsrc isNil or:[rsrc isEmpty or:[rsrc = '*' or:[rsrc = '* any *']]]) ifTrue:[
-            t := 'methods with any resource'.
-            rsrc := nil
-        ] ifFalse:[
-            t := 'methods with #' , rsrc , '-resource'.
-            rsrc := rsrc withoutSeparators asSymbol
-        ].
-        (value isNil or:[value isEmpty or:[value = '*']]) ifTrue:[
-            t := t , ' and any value'.
-            value := nil
-        ] ifFalse:[
-            t := t , ' and value ' , value.
-        ].
-        self withWaitCursorDo:[
-            SystemBrowser browseForResource:rsrc
-                          containing:value
-                          in:(Smalltalk allClasses)
-                          title:t
-        ]  
+	rsrc := resourceHolder value.
+	value := valueHolder value.
+
+	(rsrc isNil or:[rsrc isEmpty or:[rsrc = '*' or:[rsrc = '* any *']]]) ifTrue:[
+	    t := 'methods with any resource'.
+	    rsrc := nil
+	] ifFalse:[
+	    t := 'methods with #' , rsrc , '-resource'.
+	    rsrc := rsrc withoutSeparators asSymbol
+	].
+	(value isNil or:[value isEmpty or:[value = '*']]) ifTrue:[
+	    t := t , ' and any value'.
+	    value := nil
+	] ifFalse:[
+	    t := t , ' and value ' , value.
+	].
+	self withWaitCursorDo:[
+	    SystemBrowser browseForResource:rsrc
+			  containing:value
+			  in:(Smalltalk allClasses)
+			  title:t
+	]  
     ].
 
     "Created: 28.5.1996 / 13:15:16 / cg"
@@ -460,9 +460,9 @@
     enterBox := EnterBox title:(resources at:'Browse senders of:') withCRs.
     enterBox okText:(resources at:'browse').
     enterBox action:[:selectorName |
-        |cls|
-
-        self withWaitCursorDo:[SystemBrowser browseAllCallsOn:selectorName]  
+	|cls|
+
+	self withWaitCursorDo:[SystemBrowser browseAllCallsOn:selectorName]  
     ].
     enterBox showAtPointer
 
@@ -521,7 +521,7 @@
     "open a javaBrowser (not included in the standard distribution)"
 
     JavaBrowser notNil ifTrue:[
-        self withWaitCursorDo:[JavaBrowser open]
+	self withWaitCursorDo:[JavaBrowser open]
     ]
 
     "Created: 18.4.1996 / 15:55:44 / cg"
@@ -598,8 +598,8 @@
 
     (self confirm:(resources string:'Are you certain you want to exit without saving ?'))
     ifTrue:[
-        self saveAllViews.
-        Smalltalk exit
+	self saveAllViews.
+	Smalltalk exit
     ]
 
     "Modified: 8.1.1997 / 14:50:00 / cg"
@@ -630,68 +630,68 @@
     list2 := SelectionInList new.
 
     moduleListUpdater := [
-            |l|
-
-            list2 list:nil.
-
-            l := Array new.
-            handles := Array new.
-
-            (showModules value or:[showBuiltIn value]) ifTrue:[
-                allModules := ObjectMemory binaryModuleInfo asOrderedCollection.
-                (showBuiltIn value and:[showModules value]) ifFalse:[
-                    allModules := allModules select:[:i |
-                        |wantToSee|
-
-                        wantToSee := i dynamic.
-                        showBuiltIn value ifTrue:[
-                            wantToSee := wantToSee not
-                        ].
-                        wantToSee
-                    ]
-                ].
-
-                "/ sorting by reverse id brings newest ones to the top (a side effect)
-                allModules sort:[:a :b | (a id) > (b id)].
-                moduleNames := allModules collect:[:entry | entry name].
-                l := l , moduleNames.
-                handles := handles , allModules.
-            ].
-
-            showMethods value ifTrue:[
-                allObjects := ObjectFileLoader loadedObjectHandles.
-                methodObjects := (allObjects select:[:h | h isMethodHandle]) asArray.
-                methodNames := methodObjects collect:[:mH | mH method isNil ifTrue:[
-                                                                'compiled method - removed' , ' (in ' , mH pathName , ')'
-                                                            ] ifFalse:[
-                                                                'compiled method ' , mH method whoString , ' (in ' , mH pathName , ')'
-                                                            ].
-                                                     ].
-                l := l , methodNames.
-                handles := handles , methodObjects.
-            ].
-
-            showCObjects value ifTrue:[
-                allObjects := ObjectFileLoader loadedObjectHandles.
-                cObjects := (allObjects select:[:h | h isFunctionObjectHandle]) asArray.
-                cObjectNames := cObjects collect:[:entry | entry pathName].
-                l := l , cObjectNames.
-                handles := handles , cObjects.
-            ].
-
-            showOthers value ifTrue:[
-                allObjects := ObjectFileLoader loadedObjectHandles.
-                otherObjects := (allObjects select:[:h | (h isFunctionObjectHandle
-                                                         or:[h isMethodHandle
-                                                         or:[h isClassLibHandle]]) not]) asArray.
-                otherObjectNames := otherObjects collect:[:entry | entry pathName].
-                l := l , otherObjectNames.
-                handles := handles , otherObjects.
-            ].
-
-            list1 list:l.
-            unloadButton disable.
-        ].
+	    |l|
+
+	    list2 list:nil.
+
+	    l := Array new.
+	    handles := Array new.
+
+	    (showModules value or:[showBuiltIn value]) ifTrue:[
+		allModules := ObjectMemory binaryModuleInfo asOrderedCollection.
+		(showBuiltIn value and:[showModules value]) ifFalse:[
+		    allModules := allModules select:[:i |
+			|wantToSee|
+
+			wantToSee := i dynamic.
+			showBuiltIn value ifTrue:[
+			    wantToSee := wantToSee not
+			].
+			wantToSee
+		    ]
+		].
+
+		"/ sorting by reverse id brings newest ones to the top (a side effect)
+		allModules sort:[:a :b | (a id) > (b id)].
+		moduleNames := allModules collect:[:entry | entry name].
+		l := l , moduleNames.
+		handles := handles , allModules.
+	    ].
+
+	    showMethods value ifTrue:[
+		allObjects := ObjectFileLoader loadedObjectHandles.
+		methodObjects := (allObjects select:[:h | h isMethodHandle]) asArray.
+		methodNames := methodObjects collect:[:mH | mH method isNil ifTrue:[
+								'compiled method - removed' , ' (in ' , mH pathName , ')'
+							    ] ifFalse:[
+								'compiled method ' , mH method whoString , ' (in ' , mH pathName , ')'
+							    ].
+						     ].
+		l := l , methodNames.
+		handles := handles , methodObjects.
+	    ].
+
+	    showCObjects value ifTrue:[
+		allObjects := ObjectFileLoader loadedObjectHandles.
+		cObjects := (allObjects select:[:h | h isFunctionObjectHandle]) asArray.
+		cObjectNames := cObjects collect:[:entry | entry pathName].
+		l := l , cObjectNames.
+		handles := handles , cObjects.
+	    ].
+
+	    showOthers value ifTrue:[
+		allObjects := ObjectFileLoader loadedObjectHandles.
+		otherObjects := (allObjects select:[:h | (h isFunctionObjectHandle
+							 or:[h isMethodHandle
+							 or:[h isClassLibHandle]]) not]) asArray.
+		otherObjectNames := otherObjects collect:[:entry | entry pathName].
+		l := l , otherObjectNames.
+		handles := handles , otherObjects.
+	    ].
+
+	    list1 list:l.
+	    unloadButton disable.
+	].
 
     showBuiltIn onChangeSend:#value to:moduleListUpdater.
     showModules onChangeSend:#value to:moduleListUpdater.
@@ -706,119 +706,119 @@
     listView1 model:list1.
     listView1 origin:0.0@0.0 corner:1.0@0.4. "/ ; inset:2.
     listView1 action:[:sel |
-        |info classNames tabs module|
-
-        listView1 middleButtonMenu:nil.
-
-        box withWaitCursorDo:[
-            |nm fileName addr entry1 entry2 entry3 method|
-
-            tabs := TabulatorSpecification unit:#inch positions:#(0 2.6).
-
-            (showModules value or:[showBuiltIn value]) ifTrue:[
-                info := allModules at:sel ifAbsent:nil.
-            ].
-            info isNil ifTrue:[
-                "/ selected a method, cObject or unknown
-
-                module := handles at:sel.
-                fileName := module pathName.
-
-                module isMethodHandle ifTrue:[
-
-                    (method := module method) isNil ifTrue:[
-                        nm := '** removed **'.
-                    ] ifFalse:[
-                        menu := PopUpMenu
-                                    labels:#('inspect' 'browse')
-                                    selectors:#(inspect browse).
-                        menu actionAt:#inspect put:[ method inspect ].
-                        menu actionAt:#browse put:[ |who|
-                                                    who := method who.
-                                                    SystemBrowser 
-                                                        openInClass:(who methodClass) 
-                                                        selector:(who methodSelector) 
-                                                  ].
-                        listView1 middleButtonMenu:menu.
-
-                        nm := (method whoString) asText emphasizeAllWith:(#color->Color blue).
-                    ].
-                    entry1 := MultiColListEntry new:2 tabulatorSpecification:tabs.
-                    entry1 colAt:1 put:'compiled method'; colAt:2 put:nm.
-
-                    entry2 := MultiColListEntry new:2 tabulatorSpecification:tabs.
-                    entry2 colAt:1 put:'path'; colAt:2 put:fileName.
-
-                    entry3 := MultiColListEntry new:2 tabulatorSpecification:tabs.
-                    entry3 colAt:1 put:'address'; colAt:2 put:('(16r) ' , (method code hexPrintString leftPaddedTo:8 with:$0)).
-
-                    list2 list:(Array with:entry1 with:entry2 with:entry3).
-                ] ifFalse:[
-                    (module isFunctionObjectHandle 
-                    and:[module functions notEmpty]) ifTrue:[
-
-                        menu := PopUpMenu
-                                    labels:#('inspect')
-                                    selectors:#(inspect).
-                        menu actionAt:#inspect put:[ module functions inspect  ].
-                        listView1 middleButtonMenu:menu.
-
-                        list2 list:((module functions select:[:f | f notNil])
-                                        collect:[:f | |entry|
-                                                        entry := MultiColListEntry new:2 tabulatorSpecification:tabs.
-                                                        entry colAt:1 put:(f name asText emphasizeAllWith:(#color->Color blue)).
-                                                        entry colAt:2 put:('address: (16r) ' , (f code hexPrintString leftPaddedTo:8 with:$0)).
-                                                        entry
-                                                ]).
-                    ] ifFalse:[
-                        list2 list:#('nothing known about contents (no functions have been extracted)').    
-                    ]
-                ].
+	|info classNames tabs module|
+
+	listView1 middleButtonMenu:nil.
+
+	box withWaitCursorDo:[
+	    |nm fileName addr entry1 entry2 entry3 method|
+
+	    tabs := TabulatorSpecification unit:#inch positions:#(0 2.6).
+
+	    (showModules value or:[showBuiltIn value]) ifTrue:[
+		info := allModules at:sel ifAbsent:nil.
+	    ].
+	    info isNil ifTrue:[
+		"/ selected a method, cObject or unknown
+
+		module := handles at:sel.
+		fileName := module pathName.
+
+		module isMethodHandle ifTrue:[
+
+		    (method := module method) isNil ifTrue:[
+			nm := '** removed **'.
+		    ] ifFalse:[
+			menu := PopUpMenu
+				    labels:#('inspect' 'browse')
+				    selectors:#(inspect browse).
+			menu actionAt:#inspect put:[ method inspect ].
+			menu actionAt:#browse put:[ |who|
+						    who := method who.
+						    SystemBrowser 
+							openInClass:(who methodClass) 
+							selector:(who methodSelector) 
+						  ].
+			listView1 middleButtonMenu:menu.
+
+			nm := (method whoString) asText emphasizeAllWith:(#color->Color blue).
+		    ].
+		    entry1 := MultiColListEntry new:2 tabulatorSpecification:tabs.
+		    entry1 colAt:1 put:'compiled method'; colAt:2 put:nm.
+
+		    entry2 := MultiColListEntry new:2 tabulatorSpecification:tabs.
+		    entry2 colAt:1 put:'path'; colAt:2 put:fileName.
+
+		    entry3 := MultiColListEntry new:2 tabulatorSpecification:tabs.
+		    entry3 colAt:1 put:'address'; colAt:2 put:('(16r) ' , (method code hexPrintString leftPaddedTo:8 with:$0)).
+
+		    list2 list:(Array with:entry1 with:entry2 with:entry3).
+		] ifFalse:[
+		    (module isFunctionObjectHandle 
+		    and:[module functions notEmpty]) ifTrue:[
+
+			menu := PopUpMenu
+				    labels:#('inspect')
+				    selectors:#(inspect).
+			menu actionAt:#inspect put:[ module functions inspect  ].
+			listView1 middleButtonMenu:menu.
+
+			list2 list:((module functions select:[:f | f notNil])
+					collect:[:f | |entry|
+							entry := MultiColListEntry new:2 tabulatorSpecification:tabs.
+							entry colAt:1 put:(f name asText emphasizeAllWith:(#color->Color blue)).
+							entry colAt:2 put:('address: (16r) ' , (f code hexPrintString leftPaddedTo:8 with:$0)).
+							entry
+						]).
+		    ] ifFalse:[
+			list2 list:#('nothing known about contents (no functions have been extracted)').    
+		    ]
+		].
                 
-                unloadButton enable.
-            ] ifFalse:[
-                "/ selected a package
-
-                "/ fill bottom list with class-info
-
-                classNames := info classNames asSortedCollection.
-                classNames := classNames collect:[:cName |
-                                |cls entry rev listEntry|
-
-                                listEntry := MultiColListEntry new:2 tabulatorSpecification:tabs.
-                                listEntry colAt:1 put:cName.
-
-                                cls := Smalltalk classNamed:cName.
-                                cls isNil ifTrue:[
-                                    listEntry colAt:2 put:'(class removed)'.
-                                ] ifFalse:[
-                                    rev := cls binaryRevision.
-                                    rev notNil ifTrue:[
-                                        cls isLoaded ifFalse:[
-                                            entry := '(stub for: ' , rev.
-                                        ] ifTrue:[
-                                            entry :='(bin: ' , rev.
-                                        ].    
-                                        cls revision ~= rev ifTrue:[
-                                            entry := entry , ' / src: ' , cls revision    
-                                        ].
-                                        listEntry colAt:2 put:entry , ')'
-                                    ] ifFalse:[
-                                       cls revision notNil ifTrue:[
-                                            listEntry colAt:2 put:'(overloaded by: ' , cls revision , ')' 
-                                       ]
-                                    ]
-                                ].
-                                listEntry
-                              ].
-                list2 list:classNames.
-                info dynamic ifTrue:[
-                    unloadButton enable.
-                ] ifFalse:[
-                    unloadButton disable.
-                ].
-            ]
-        ]
+		unloadButton enable.
+	    ] ifFalse:[
+		"/ selected a package
+
+		"/ fill bottom list with class-info
+
+		classNames := info classNames asSortedCollection.
+		classNames := classNames collect:[:cName |
+				|cls entry rev listEntry|
+
+				listEntry := MultiColListEntry new:2 tabulatorSpecification:tabs.
+				listEntry colAt:1 put:cName.
+
+				cls := Smalltalk classNamed:cName.
+				cls isNil ifTrue:[
+				    listEntry colAt:2 put:'(class removed)'.
+				] ifFalse:[
+				    rev := cls binaryRevision.
+				    rev notNil ifTrue:[
+					cls isLoaded ifFalse:[
+					    entry := '(stub for: ' , rev.
+					] ifTrue:[
+					    entry :='(bin: ' , rev.
+					].    
+					cls revision ~= rev ifTrue:[
+					    entry := entry , ' / src: ' , cls revision    
+					].
+					listEntry colAt:2 put:entry , ')'
+				    ] ifFalse:[
+				       cls revision notNil ifTrue:[
+					    listEntry colAt:2 put:'(overloaded by: ' , cls revision , ')' 
+				       ]
+				    ]
+				].
+				listEntry
+			      ].
+		list2 list:classNames.
+		info dynamic ifTrue:[
+		    unloadButton enable.
+		] ifFalse:[
+		    unloadButton disable.
+		].
+	    ]
+	]
     ].
 
 
@@ -830,27 +830,27 @@
     box makeTabable:check.
     panel add:(check := CheckBox label:'classLibs' model:showModules).
     canDoIt ifFalse:[
-        check disable
+	check disable
     ] ifTrue:[
-        box makeTabable:check.
+	box makeTabable:check.
     ].
     panel add:(check := CheckBox label:'methods' model:showMethods).
     canDoIt ifFalse:[
-        check disable
+	check disable
     ] ifTrue:[
-        box makeTabable:check.
+	box makeTabable:check.
     ].
     panel add:(check := CheckBox label:'c-objects' model:showCObjects).
     canDoIt ifFalse:[
-        check disable
+	check disable
     ] ifTrue:[
-        box makeTabable:check.
+	box makeTabable:check.
     ].
     panel add:(check := CheckBox label:'others' model:showOthers).
     canDoIt ifFalse:[
-        check disable
+	check disable
     ] ifTrue:[
-        box makeTabable:check.
+	box makeTabable:check.
     ].
 
     panel horizontalLayout:#fitSpace.
@@ -877,29 +877,29 @@
 
     unloadButton := Button label:(resources string:'unload').
     unloadButton action:[
-        self withWaitCursorDo:[
-            box withWaitCursorDo:[
-                |info idx pathName|
-
-                idx := list1 selectionIndex.
-                info := allModules at:idx ifAbsent:nil.
-
-                list1 selectionIndex:nil.
-
-                info isNil ifTrue:[
-                    "/ selected a method
-                    "/ idx := idx - allModules size.
-                    pathName := (handles at:idx) pathName.
-
-                ] ifFalse:[
-                    "/ selected a package
-                    pathName := info pathName.
-                ].
-                ObjectFileLoader unloadObjectFile:pathName.
-                moduleListUpdater value.
-                unloadButton disable.
-            ]
-        ]
+	self withWaitCursorDo:[
+	    box withWaitCursorDo:[
+		|info idx pathName|
+
+		idx := list1 selectionIndex.
+		info := allModules at:idx ifAbsent:nil.
+
+		list1 selectionIndex:nil.
+
+		info isNil ifTrue:[
+		    "/ selected a method
+		    "/ idx := idx - allModules size.
+		    pathName := (handles at:idx) pathName.
+
+		] ifFalse:[
+		    "/ selected a package
+		    pathName := info pathName.
+		].
+		ObjectFileLoader unloadObjectFile:pathName.
+		moduleListUpdater value.
+		unloadButton disable.
+	    ]
+	]
     ].
     moduleListUpdater value.
 
@@ -927,24 +927,24 @@
     |fileName|
 
     fileName := DialogBox
-                    request:(resources at:'filename for image:') withCRs
-              initialAnswer:(ObjectMemory nameForSnapshot) 
-                    okLabel:(resources at:'save')
-                      title:(resources string:'save image')
-                   onCancel:nil.
+		    request:(resources at:'filename for image:') withCRs
+	      initialAnswer:(ObjectMemory nameForSnapshot) 
+		    okLabel:(resources at:'save')
+		      title:(resources string:'save image')
+		   onCancel:nil.
 
     fileName notNil ifTrue:[
-        self showCursor:Cursor write.
-        [
-            (ObjectMemory snapShotOn:fileName) ifFalse:[
-                "
-                 snapshot failed for some reason (disk full, no permission etc.)
-                "
-                self warn:(resources string:'failed to save snapshot image (disk full or not writable)').
-            ]
-        ] valueNowOrOnUnwindDo:[
-            self restoreCursors.
-        ].
+	self showCursor:Cursor write.
+	[
+	    (ObjectMemory snapShotOn:fileName) ifFalse:[
+		"
+		 snapshot failed for some reason (disk full, no permission etc.)
+		"
+		self warn:(resources string:'failed to save snapshot image (disk full or not writable)').
+	    ]
+	] valueNowOrOnUnwindDo:[
+	    self restoreCursors.
+	].
     ].
 
     "Modified: 8.1.1997 / 14:50:29 / cg"
@@ -956,41 +956,41 @@
     |fileName ok|
 
     fileName := DialogBox
-                    request:(resources at:'filename for image:') withCRs
-              initialAnswer:(ObjectMemory nameForSnapshot) 
-                    okLabel:(resources at:'save & exit')
-                      title:(resources string:'save image & exit')
-                   onCancel:nil.
+		    request:(resources at:'filename for image:') withCRs
+	      initialAnswer:(ObjectMemory nameForSnapshot) 
+		    okLabel:(resources at:'save & exit')
+		      title:(resources string:'save image & exit')
+		   onCancel:nil.
 
     fileName notNil ifTrue:[
-        self showCursor:Cursor write.
-        [
-            ok := ObjectMemory snapShotOn:fileName.
-        ] valueNowOrOnUnwindDo:[
-            self restoreCursors.
-        ].
-
-        ok 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:[
-            "
-             saveAllViews 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 showCursor:Cursor write.
+	[
+	    ok := ObjectMemory snapShotOn:fileName.
+	] valueNowOrOnUnwindDo:[
+	    self restoreCursors.
+	].
+
+	ok 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:[
+	    "
+	     saveAllViews 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 saveAllViews.
+	    self saveAllViews.
 "
-            Smalltalk exit
-        ]
+	    Smalltalk exit
+	]
     ].
 
     "Modified: 8.1.1997 / 14:50:36 / cg"
@@ -1046,7 +1046,7 @@
     "creates a new project & opens a projectView for it"
 
     Project notNil ifTrue:[
-        (ProjectView for:(Project new)) open
+	(ProjectView for:(Project new)) open
     ]
 
     "Modified: 8.1.1997 / 14:52:07 / cg"
@@ -1058,23 +1058,23 @@
     |list box|
 
     Project notNil ifTrue:[
-        list := Project allInstances.
-        box := ListSelectionBox new.
-        box list:(list collect:[:p | p name]).
-        box title:(resources string:'select a project').
-        box action:[:selection |
-            |project|
-
-            project := list detect:[:p | p name = selection] ifNone:[nil].
-            project isNil ifTrue:[
-                transcript showCR:'no such project.'
-            ] ifFalse:[
-                project showViews.
-                Project current:project
-            ]
-        ].
-        box showAtPointer.
-        box destroy
+	list := Project allInstances.
+	box := ListSelectionBox new.
+	box list:(list collect:[:p | p name]).
+	box title:(resources string:'select a project').
+	box action:[:selection |
+	    |project|
+
+	    project := list detect:[:p | p name = selection] ifNone:[nil].
+	    project isNil ifTrue:[
+		transcript showCR:'no such project.'
+	    ] ifFalse:[
+		project showViews.
+		Project current:project
+	    ]
+	].
+	box showAtPointer.
+	box destroy
     ]
 
     "Modified: 8.1.1997 / 14:52:20 / cg"
@@ -1109,18 +1109,18 @@
 
     stcCompilationOptions := #( always default never).
     stcCompilation := SelectionInList new 
-                        list:(resources array:#('always' 
-                                                'primitive code only' 
-                                                'never'
-                                               )).
+			list:(resources array:#('always' 
+						'primitive code only' 
+						'never'
+					       )).
     stcCompilation selectionIndex:2.
     (supportsJustInTimeCompilation := ObjectMemory supportsJustInTimeCompilation)
     ifTrue:[
-        justInTimeCompilation := ObjectMemory justInTimeCompilation:nil.
-        fullSingleStep := ObjectMemory fullSingleStepSupport:nil.
+	justInTimeCompilation := ObjectMemory justInTimeCompilation:nil.
+	fullSingleStep := ObjectMemory fullSingleStepSupport:nil.
     ] ifFalse:[
-        justInTimeCompilation := false.
-        fullSingleStep := false.
+	justInTimeCompilation := false.
+	fullSingleStep := false.
     ].
     justInTimeCompilation := justInTimeCompilation asValue.
     fullSingleStep := fullSingleStep asValue.
@@ -1132,12 +1132,12 @@
     cc := Compiler ccPath asValue.
 
     ObjectFileLoader notNil ifTrue:[
-        (t := ObjectFileLoader searchedLibraries) notNil ifTrue:[
-            stcLibraries := (String fromStringCollection:t separatedBy:' ') asValue.
-        ].
-        (t := ObjectFileLoader libPath) notNil ifTrue:[
-            stcLibraryPath := t asValue.
-        ]
+	(t := ObjectFileLoader searchedLibraries) notNil ifTrue:[
+	    stcLibraries := (String fromStringCollection:t separatedBy:' ') asValue.
+	].
+	(t := ObjectFileLoader libPath) notNil ifTrue:[
+	    stcLibraryPath := t asValue.
+	]
     ].
 
     catchRedefs := Class catchMethodRedefinitions asValue.
@@ -1148,21 +1148,21 @@
     keepSource selectionIndex:1.
 
     warnEnabler := [
-              warnings value ifTrue:[
-                warnSTXBox enable. 
-                warnOldStyleBox enable.
-                warnCommonMistakesBox enable.
-                allowUnderscore value ifTrue:[
-                    warnUnderscoreBox enable.
-                ] ifFalse:[
-                    warnUnderscoreBox disable.
-                ].
-              ] ifFalse:[
-                warnSTXBox disable. 
-                warnUnderscoreBox disable.
-                warnOldStyleBox disable.
-                warnCommonMistakesBox disable.
-              ]].
+	      warnings value ifTrue:[
+		warnSTXBox enable. 
+		warnOldStyleBox enable.
+		warnCommonMistakesBox enable.
+		allowUnderscore value ifTrue:[
+		    warnUnderscoreBox enable.
+		] ifFalse:[
+		    warnUnderscoreBox disable.
+		].
+	      ] ifFalse:[
+		warnSTXBox disable. 
+		warnUnderscoreBox disable.
+		warnOldStyleBox disable.
+		warnCommonMistakesBox disable.
+	      ]].
 
     warnings onChangeSend:#value to:warnEnabler.
     allowUnderscore onChangeSend:#value to:warnEnabler.
@@ -1180,107 +1180,107 @@
     box addHorizontalLine.
 
     supportsJustInTimeCompilation ifTrue:[
-        component := box 
-                        addCheckBox:(resources string:'just in time compilation to machine code') 
-                        on:justInTimeCompilation.
-
-        component := box 
-                        addCheckBox:(resources string:'detailed single step support') 
-                        on:fullSingleStep.
-
-        box addHorizontalLine.
+	component := box 
+			addCheckBox:(resources string:'just in time compilation to machine code') 
+			on:justInTimeCompilation.
+
+	component := box 
+			addCheckBox:(resources string:'detailed single step support') 
+			on:fullSingleStep.
+
+	box addHorizontalLine.
     ].
 
     ObjectFileLoader notNil ifTrue:[
-        compilationList := box addPopUpList:(resources string:'stc compilation to machine code') on:stcCompilation.
-        stcCompilation selectionIndex:( stcCompilationOptions indexOf:(Compiler stcCompilation) ifAbsent:2).
-
-        component := box 
-                        addLabelledInputField:(resources string:'include directories:')
-                        adjust:#right
-                        on:stcIncludes 
-                        tabable:true
-                        separateAtX:0.3.
-        component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-        component preferredExtent:(250 @ component preferredExtent y).
+	compilationList := box addPopUpList:(resources string:'stc compilation to machine code') on:stcCompilation.
+	stcCompilation selectionIndex:( stcCompilationOptions indexOf:(Compiler stcCompilation) ifAbsent:2).
+
+	component := box 
+			addLabelledInputField:(resources string:'include directories:')
+			adjust:#right
+			on:stcIncludes 
+			tabable:true
+			separateAtX:0.3.
+	component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	component preferredExtent:(250 @ component preferredExtent y).
 
 "/        box addVerticalSpace.
 
-        component := box 
-                        addLabelledInputField:(resources string:'defines:')
-                        adjust:#right
-                        on:stcDefines 
-                        tabable:true
-                        separateAtX:0.3.
-        component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-        component preferredExtent:(250 @ component preferredExtent y).
+	component := box 
+			addLabelledInputField:(resources string:'defines:')
+			adjust:#right
+			on:stcDefines 
+			tabable:true
+			separateAtX:0.3.
+	component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	component preferredExtent:(250 @ component preferredExtent y).
 
 "/        box addVerticalSpace.
 
-        component := box 
-                        addLabelledInputField:(resources string:'stc options:')
-                        adjust:#right
-                        on:stcOptions 
-                        tabable:true
-                        separateAtX:0.3.
-        component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-        component preferredExtent:(250 @ component preferredExtent y).
+	component := box 
+			addLabelledInputField:(resources string:'stc options:')
+			adjust:#right
+			on:stcOptions 
+			tabable:true
+			separateAtX:0.3.
+	component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	component preferredExtent:(250 @ component preferredExtent y).
 
 "/        box addVerticalSpace.
 
-        component := box 
-                        addLabelledInputField:(resources string:'cc command:')
-                        adjust:#right
-                        on:cc 
-                        tabable:true
-                        separateAtX:0.3.
-        component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-        component preferredExtent:(250 @ component preferredExtent y).
-
-        component := box 
-                        addLabelledInputField:(resources string:'cc options:')
-                        adjust:#right
-                        on:ccOptions 
-                        tabable:true
-                        separateAtX:0.3.
-        component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-        component preferredExtent:(250 @ component preferredExtent y).
-
-        stcLibraries notNil ifTrue:[
+	component := box 
+			addLabelledInputField:(resources string:'cc command:')
+			adjust:#right
+			on:cc 
+			tabable:true
+			separateAtX:0.3.
+	component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	component preferredExtent:(250 @ component preferredExtent y).
+
+	component := box 
+			addLabelledInputField:(resources string:'cc options:')
+			adjust:#right
+			on:ccOptions 
+			tabable:true
+			separateAtX:0.3.
+	component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	component preferredExtent:(250 @ component preferredExtent y).
+
+	stcLibraries notNil ifTrue:[
 "/            box addVerticalSpace.
 
-            component := box 
-                            addLabelledInputField:(resources string:'C-libraries:')
-                            adjust:#right
-                            on:stcLibraries 
-                            tabable:true
-                            separateAtX:0.3.
-            component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-            component preferredExtent:(250 @ component preferredExtent y).
-        ].
-
-        stcLibraryPath notNil ifTrue:[
+	    component := box 
+			    addLabelledInputField:(resources string:'C-libraries:')
+			    adjust:#right
+			    on:stcLibraries 
+			    tabable:true
+			    separateAtX:0.3.
+	    component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	    component preferredExtent:(250 @ component preferredExtent y).
+	].
+
+	stcLibraryPath notNil ifTrue:[
 "/            box addVerticalSpace.
 
-            component := box 
-                            addLabelledInputField:(resources string:'stc libPath:')
-                            adjust:#right
-                            on:stcLibraryPath 
-                            tabable:true
-                            separateAtX:0.3.
-            component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-            component preferredExtent:(250 @ component preferredExtent y).
-        ].
+	    component := box 
+			    addLabelledInputField:(resources string:'stc libPath:')
+			    adjust:#right
+			    on:stcLibraryPath 
+			    tabable:true
+			    separateAtX:0.3.
+	    component immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	    component preferredExtent:(250 @ component preferredExtent y).
+	].
 
 "/        box addVerticalSpace.
-        box addHorizontalLine.
-
-        "/ if there is no compiler around,
-        "/ change to compile nothing, and disable the checkBoxes
-        Compiler canCreateMachineCode ifFalse:[
-            stcCompilation selectionIndex:3.
-            compilationList disable.
-        ].
+	box addHorizontalLine.
+
+	"/ if there is no compiler around,
+	"/ change to compile nothing, and disable the checkBoxes
+	Compiler canCreateMachineCode ifFalse:[
+	    stcCompilation selectionIndex:3.
+	    compilationList disable.
+	].
     ].
 
     y := box yPosition.
@@ -1336,59 +1336,59 @@
     box leftIndent:oldIndent.
 
     box 
-        addHelpButtonFor:'Launcher/compilerSettings.html';
-        addAbortButton; 
-        addOkButton.
+	addHelpButtonFor:'Launcher/compilerSettings.html';
+	addAbortButton; 
+	addOkButton.
 
     warnEnabler value.
     box open.
 
     box accepted ifTrue:[
-        HistoryManager notNil ifTrue:[
-            historyLines value ifTrue:[
-                HistoryManager activate
-            ] ifFalse:[
-                HistoryManager deactivate
-            ].
-        ].
-        Class catchMethodRedefinitions:catchRedefs value.
-        ClassCategoryReader sourceMode:(keepSourceOptions at:keepSource selectionIndex).
-        Compiler warnings:warnings value.
-        Compiler warnSTXSpecials:warnSTX value.
-        Compiler warnOldStyleAssignment:warnOldStyle value.
-        Compiler warnUnderscoreInIdentifier:warnUnderscore value.
-        Compiler warnCommonMistakes:warnCommonMistakes value.
-        Compiler allowUnderscoreInIdentifier:allowUnderscore value.
-        Compiler arraysAreImmutable:immutableArrays value.
-        fullLineNumbers value ifTrue:[
-            Compiler lineNumberInfo:#full.
-        ] ifFalse:[
-            Compiler lineNumberInfo:true
-        ].
-
-        Compiler stcCompilation:(stcCompilationOptions at:stcCompilation selectionIndex).
-        Compiler stcCompilationIncludes:stcIncludes value.
-        Compiler stcCompilationDefines:stcDefines value.
-        Compiler stcCompilationOptions:stcOptions value.
-        Compiler ccCompilationOptions:ccOptions value.
-        Compiler ccPath:cc value.
-        Compiler foldConstants:(constantFoldingOptions at:constantFolding selectionIndex).
-
-        supportsJustInTimeCompilation ifTrue:[
-            justInTimeCompilation value ifTrue:[
-                Method allInstancesDo:[:m | m checked:false].
-            ].
-            ObjectMemory justInTimeCompilation:justInTimeCompilation value.
-            ObjectMemory fullSingleStepSupport:fullSingleStep value.
-        ].
-        ObjectFileLoader notNil ifTrue:[
-            stcLibraries notNil ifTrue:[
-                ObjectFileLoader searchedLibraries:(stcLibraries value asCollectionOfWords).
-            ].
-            stcLibraryPath notNil ifTrue:[
-                ObjectFileLoader libPath:(stcLibraryPath value).
-            ]
-        ]
+	HistoryManager notNil ifTrue:[
+	    historyLines value ifTrue:[
+		HistoryManager activate
+	    ] ifFalse:[
+		HistoryManager deactivate
+	    ].
+	].
+	Class catchMethodRedefinitions:catchRedefs value.
+	ClassCategoryReader sourceMode:(keepSourceOptions at:keepSource selectionIndex).
+	Compiler warnings:warnings value.
+	Compiler warnSTXSpecials:warnSTX value.
+	Compiler warnOldStyleAssignment:warnOldStyle value.
+	Compiler warnUnderscoreInIdentifier:warnUnderscore value.
+	Compiler warnCommonMistakes:warnCommonMistakes value.
+	Compiler allowUnderscoreInIdentifier:allowUnderscore value.
+	Compiler arraysAreImmutable:immutableArrays value.
+	fullLineNumbers value ifTrue:[
+	    Compiler lineNumberInfo:#full.
+	] ifFalse:[
+	    Compiler lineNumberInfo:true
+	].
+
+	Compiler stcCompilation:(stcCompilationOptions at:stcCompilation selectionIndex).
+	Compiler stcCompilationIncludes:stcIncludes value.
+	Compiler stcCompilationDefines:stcDefines value.
+	Compiler stcCompilationOptions:stcOptions value.
+	Compiler ccCompilationOptions:ccOptions value.
+	Compiler ccPath:cc value.
+	Compiler foldConstants:(constantFoldingOptions at:constantFolding selectionIndex).
+
+	supportsJustInTimeCompilation ifTrue:[
+	    justInTimeCompilation value ifTrue:[
+		Method allInstancesDo:[:m | m checked:false].
+	    ].
+	    ObjectMemory justInTimeCompilation:justInTimeCompilation value.
+	    ObjectMemory fullSingleStepSupport:fullSingleStep value.
+	].
+	ObjectFileLoader notNil ifTrue:[
+	    stcLibraries notNil ifTrue:[
+		ObjectFileLoader searchedLibraries:(stcLibraries value asCollectionOfWords).
+	    ].
+	    stcLibraryPath notNil ifTrue:[
+		ObjectFileLoader libPath:(stcLibraryPath value).
+	    ]
+	]
     ].
     box destroy
 
@@ -1407,16 +1407,16 @@
 
     listOfSizes := resources at:'LIST_OF_OFFERED_SCREEN_SIZES' default:#default.
     listOfSizes == #default ifTrue:[
-        "/ nothing in resource file; offer at least some.
-        sizeInfos := #(
-                           ( '11.3'' (235mm x 175mm) LCD'   (235 175)    )
-                           ( '17''   (325mm x 245mm)'       (325 245)    )
-                           ( '19''   (340mm x 270mm)'       (340 270)    )
-                           ( '20''   (350mm x 280mm)'       (350 280)    )
-                           ( '21''   (365mm x 285mm)'       (365 285)    )
-                       ).
+	"/ nothing in resource file; offer at least some.
+	sizeInfos := #(
+			   ( '11.3'' (235mm x 175mm) LCD'   (235 175)    )
+			   ( '17''   (325mm x 245mm)'       (325 245)    )
+			   ( '19''   (340mm x 270mm)'       (340 270)    )
+			   ( '20''   (350mm x 280mm)'       (350 280)    )
+			   ( '21''   (365mm x 285mm)'       (365 285)    )
+		       ).
     ] ifFalse:[
-        sizeInfos := resources array:listOfSizes.
+	sizeInfos := resources array:listOfSizes.
     ].
     sizeNames := sizeInfos collect:[:entry | entry at:1].
     sizes := sizeInfos collect:[:entry | entry at:2].
@@ -1435,63 +1435,67 @@
     ditherList := SelectionInList new.
 
     (visual == #StaticGray or:[visual == #GrayScale]) ifTrue:[
-        ditherStyles := #('threshold' 'ordered dither' 'error diffusion').
-        ditherSyms := #(threshold ordered floydSteinberg).
+	ditherStyles := #('threshold' 'ordered dither' 'error diffusion').
+	ditherSyms := #(threshold ordered floydSteinberg).
     ] ifFalse:[
-        visual ~~ #TrueColor ifTrue:[
-            ditherStyles := #('nearest color' 'error diffusion').
-            ditherSyms := #(ordered floydSteinberg).
-        ]
+	visual ~~ #TrueColor ifTrue:[
+	    ditherStyles := #('nearest color' 'error diffusion').
+	    ditherSyms := #(ordered floydSteinberg).
+	]
     ].
     ditherSyms notNil ifTrue:[    
-        ditherList list:ditherStyles.
-        ditherList selectionIndex:(ditherSyms indexOf:(Image ditherAlgorithm) ifAbsent:#threshold).
+	ditherList list:ditherStyles.
+	ditherList selectionIndex:(ditherSyms indexOf:(Image ditherAlgorithm) ifAbsent:#threshold).
     ].
 
     box := DialogBox new.
     box label:(resources string:'Display screen settings').
 
     (box addTextLabel:(resources string:'Actual visible screen area:'))
-        adjust:#left.
+	adjust:#left.
 
     (box addPopUpList:(resources string:'common sizes:') on:sizeList)
-        label:'monitor size'.
+	label:'monitor size'.
 
     idx := sizes findFirst:[:entry |
-                                ((entry at:1) = sizeX value)
-                                and:[((entry at:2) = sizeY value)]
-                           ].
+				((entry at:1) = sizeX value)
+				and:[((entry at:2) = sizeY value)]
+			   ].
     idx ~~ 0 ifTrue:[
-        sizeList selectionIndex:idx
+	sizeList selectionIndex:idx
     ].
 
     sizeList onChangeSend:#value to:[
-                                        |idx|
-
-                                        idx := sizeList selectionIndex.
-                                        sizeX value:((sizes at:idx) at:1).
-                                        sizeY value:((sizes at:idx) at:2).
-                                    ].
+					|idx|
+
+					idx := sizeList selectionIndex.
+					sizeX value:((sizes at:idx) at:1).
+					sizeY value:((sizes at:idx) at:2).
+				    ].
 
     y := box yPosition.
     component := box addTextLabel:(resources string:'screen size:').
     component width:0.3; adjust:#right; borderWidth:0.
 
     box yPosition:y.
-    component := box addInputFieldOn:(TypeConverter onNumberValue:sizeX) tabable:true.
+    component := box addInputFieldOn:nil tabable:true.
     component width:0.25; left:0.3; 
-              immediateAccept:false; acceptOnLeave:false; 
-              cursorMovementWhenUpdating:#beginOfLine.
+	      immediateAccept:false; acceptOnLeave:false; 
+	      cursorMovementWhenUpdating:#beginOfLine;
+	      converter:(PrintConverter new initForInteger);
+	      model:sizeX.
 
     box yPosition:y.
     component := box addTextLabel:(' x ').
     component width:0.1; left:0.55; adjust:#center; borderWidth:0.
 
     box yPosition:y.
-    component := box addInputFieldOn:(TypeConverter onNumberValue:sizeY) tabable:true.
+    component := box addInputFieldOn:nil tabable:true.
     component width:0.25; left:0.65; 
-              immediateAccept:false; acceptOnLeave:false; 
-              cursorMovementWhenUpdating:#beginOfLine.
+	      immediateAccept:false; acceptOnLeave:false; 
+	      cursorMovementWhenUpdating:#beginOfLine;
+	      converter:(PrintConverter new initForInteger);
+	      model:sizeY.
 
     box yPosition:y.
     component := box addTextLabel:('(mm)').
@@ -1504,51 +1508,51 @@
     box addCheckBox:(resources string:'color monitor') on:isColorMonitor.
 
     visual == #PseudoColor ifTrue:[
-        box addVerticalSpace.
-        component := box addCheckBox:(resources string:'use fix color palette (6x6x4)') on:useFixPalette.
+	box addVerticalSpace.
+	component := box addCheckBox:(resources string:'use fix color palette (6x6x4)') on:useFixPalette.
     ].
 
     ditherSyms notNil ifTrue:[
-        box addVerticalSpace.
-        component := box addPopUpList:(resources string:'image display:') on:ditherList.
-        component defaultLabel:'image display'.
-        component superView horizontalLayout:#leftSpace.
+	box addVerticalSpace.
+	component := box addPopUpList:(resources string:'image display:') on:ditherList.
+	component defaultLabel:'image display'.
+	component superView horizontalLayout:#leftSpace.
     ].
 
     box addVerticalSpace.
     box addCheckBox:(resources string:'allow colored/grayscale icons') on:deepIcons.
 
     box 
-        addHelpButtonFor:'Launcher/screenSettings.html';
-        addAbortButton; addOkButton.
+	addHelpButtonFor:'Launcher/screenSettings.html';
+	addAbortButton; addOkButton.
     box open.
 
     box accepted ifTrue:[
-        Image flushDeviceImages.
-
-        screen visualType == #PseudoColor ifTrue:[
-            useFixPalette value ifTrue:[
-                Color colorAllocationFailSignal handle:[:ex |
-                    self warn:(resources string:'Could not allocate colors.').
-                ] do:[
-                    Color getColorsRed:6 green:6 blue:4 on:screen
-                ]
-            ] ifFalse:[
-                screen releaseFixColors
-            ]
-        ].
-        screen hasColors:isColorMonitor value.
-        screen widthInMillimeter:sizeX value.
-        screen heightInMillimeter:sizeY value.
-
-        screen supportsDeepIcons:deepIcons value.
-        ditherSyms notNil ifTrue:[
-            Image ditherAlgorithm:(ditherSyms at:ditherList selectionIndex).
-        ].
-
-        self withWaitCursorDo:[
-            View defaultStyle:(View defaultStyle).
-        ].
+	Image flushDeviceImages.
+
+	screen visualType == #PseudoColor ifTrue:[
+	    useFixPalette value ifTrue:[
+		Color colorAllocationFailSignal handle:[:ex |
+		    self warn:(resources string:'Could not allocate colors.').
+		] do:[
+		    Color getColorsRed:6 green:6 blue:4 on:screen
+		]
+	    ] ifFalse:[
+		screen releaseFixColors
+	    ]
+	].
+	screen hasColors:isColorMonitor value.
+	screen widthInMillimeter:sizeX value.
+	screen heightInMillimeter:sizeY value.
+
+	screen supportsDeepIcons:deepIcons value.
+	ditherSyms notNil ifTrue:[
+	    Image ditherAlgorithm:(ditherSyms at:ditherList selectionIndex).
+	].
+
+	self withWaitCursorDo:[
+	    View defaultStyle:(View defaultStyle).
+	].
     ].
     box destroy
 
@@ -1560,7 +1564,7 @@
     "open a dialog on font related settings"
 
     (self fontBoxForEncoding:nil) ifTrue:[
-        self reopenLauncher.
+	self reopenLauncher.
     ]
 
     "Created: 26.2.1996 / 22:52:51 / cg"
@@ -1582,62 +1586,62 @@
 
     selectionForwarder := Plug new.
     selectionForwarder respondTo:#showFunction
-                  with:[
-                        |raw|
-                        raw := list1 selection.
-                        list2 retractInterestsFor:selectionForwarder.
-                        list2 selection:(mappings at:raw asSymbol) asString.
-                        list2 onChangeSend:#showRawKey to:selectionForwarder.
-                       ].
+		  with:[
+			|raw|
+			raw := list1 selection.
+			list2 retractInterestsFor:selectionForwarder.
+			list2 selection:(mappings at:raw asSymbol) asString.
+			list2 onChangeSend:#showRawKey to:selectionForwarder.
+		       ].
     selectionForwarder respondTo:#showRawKey
-                  with:[
-                        |f raw|
-
-                        f := list2 selection.
-                        list1 retractInterestsFor:selectionForwarder.
-                        raw := mappings keyAtValue:f asString.
-                        raw isNil ifTrue:[
-                            raw := mappings keyAtValue:f first.
-                            raw isNil ifTrue:[
-                                raw := mappings keyAtValue:f asSymbol.
-                            ]
-                        ].
-                        list1 selection:raw.
-                        list1 onChangeSend:#showFunction to:selectionForwarder.
-                       ].
+		  with:[
+			|f raw|
+
+			f := list2 selection.
+			list1 retractInterestsFor:selectionForwarder.
+			raw := mappings keyAtValue:f asString.
+			raw isNil ifTrue:[
+			    raw := mappings keyAtValue:f first.
+			    raw isNil ifTrue:[
+				raw := mappings keyAtValue:f asSymbol.
+			    ]
+			].
+			list1 selection:raw.
+			list1 onChangeSend:#showFunction to:selectionForwarder.
+		       ].
 
     macroForwarder := [
-                        |f macro indent|
-                        f := list2 selection.
-                        (f startsWith:'Cmd') ifTrue:[
-                            f := f copyFrom:4
-                        ].
-                        macro := FunctionKeySequences at:(f asSymbol) ifAbsent:nil.
-                        macro notNil ifTrue:[
-                            macro := macro asStringCollection.
-                            indent := macro
-                                         inject:99999 into:[:min :element |
-                                             |stripped|
-
-                                             stripped := element withoutLeadingSeparators.
-                                             stripped size == 0 ifTrue:[
-                                                 min
-                                             ] ifFalse:[
-                                                 min min:(element size - stripped size)
-                                             ]
-                                         ].
-                            indent ~~ 0 ifTrue:[
-                                macro := macro collect:[:line | 
-                                             line size > indent ifTrue:[
-                                                line copyFrom:indent+1
-                                             ] ifFalse:[
-                                                line
-                                             ].
-                                        ]
-                            ].                        
-                        ].
-                        macroTextView contents:macro.
-                       ].
+			|f macro indent|
+			f := list2 selection.
+			(f startsWith:'Cmd') ifTrue:[
+			    f := f copyFrom:4
+			].
+			macro := FunctionKeySequences at:(f asSymbol) ifAbsent:nil.
+			macro notNil ifTrue:[
+			    macro := macro asStringCollection.
+			    indent := macro
+					 inject:99999 into:[:min :element |
+					     |stripped|
+
+					     stripped := element withoutLeadingSeparators.
+					     stripped size == 0 ifTrue:[
+						 min
+					     ] ifFalse:[
+						 min min:(element size - stripped size)
+					     ]
+					 ].
+			    indent ~~ 0 ifTrue:[
+				macro := macro collect:[:line | 
+					     line size > indent ifTrue:[
+						line copyFrom:indent+1
+					     ] ifFalse:[
+						line
+					     ].
+					]
+			    ].                        
+			].
+			macroTextView contents:macro.
+		       ].
 
     list1 := SelectionInList with:listOfRawKeys.
     list1 onChangeSend:#showFunction to:selectionForwarder.
@@ -1684,9 +1688,9 @@
     y := box yPosition.
 
     box
-        addHelpButtonFor:'Launcher/keyboardSetting.html';
-        "addAbortButton;" 
-        addOkButton.
+	addHelpButtonFor:'Launcher/keyboardSetting.html';
+	"addAbortButton;" 
+	addOkButton.
 
     macroTextView topInset:(l preferredExtent y + 5).
     macroTextView bottomInset:(box preferredExtent y - y).
@@ -1694,7 +1698,7 @@
     box open.
 
     box accepted ifTrue:[
-        "no action yet ..."
+	"no action yet ..."
     ].
     box destroy
 
@@ -1713,95 +1717,95 @@
     listOfLanguages := resources at:'LIST_OF_OFFERED_LANGUAGES' default:#('default').
     listOfLanguages := listOfLanguages asOrderedCollection.
     translatedLanguages := listOfLanguages collect:[:lang | |item|
-                                        item := resources at:lang.
-                                        item isString ifTrue:[
-                                            item
-                                        ] ifFalse:[
-                                            item at:1
-                                        ]
-                                ].
+					item := resources at:lang.
+					item isString ifTrue:[
+					    item
+					] ifFalse:[
+					    item at:1
+					]
+				].
     flags := listOfLanguages collect:[:lang | |item|
-                                        item := resources at:lang.
-                                        item isArray ifTrue:[
-                                            item at:2
-                                        ] ifFalse:[
-                                            nil
-                                        ]
-                                ].
+					item := resources at:lang.
+					item isArray ifTrue:[
+					    item at:2
+					] ifFalse:[
+					    nil
+					]
+				].
     flags := flags collect:[:nm | nm notNil ifTrue:[Image fromFile:nm] ifFalse:[nil]].
 
     languageList := translatedLanguages with:flags collect:[:lang :flag |
-                                LabelAndIcon icon:flag string:lang.
-                        ].
+				LabelAndIcon icon:flag string:lang.
+			].
 
     box := ListSelectionBox title:(resources string:'LANG_MSG') withCRs.
     box label:(resources string:'Language selection').
     box list:languageList.
     box initialText:(Language).
     box action:[:newLanguage |
-        self withWaitCursorDo:[
-            |fontPref idx language oldLanguage enc answer matchingFonts|
-
-            idx := translatedLanguages indexOf:newLanguage withoutSeparators.
-            idx ~~ 0 ifTrue:[
-                language := listOfLanguages at:idx
-            ] ifFalse:[
-                language := newLanguage
-            ].
-
-            "/ check if the new language needs a differently encoded font;
-            "/ ask user to switch font and allow cancellation.
-            "/ Otherwise, you are left with unreadable menu & button items ...
-
-            oldLanguage := Smalltalk language.
-            Smalltalk language:language asSymbol.
-            ResourcePack flushCachedResourcePacks.
-            fontPref := self class classResources at:'PREFERRED_FONT_ENCODING'.
-            Smalltalk language:oldLanguage.
-
-            switch := true.
-            enc := MenuView defaultFont encoding.
-            (fontPref match:enc) ifFalse:[
-                "/ look if there is one at all.
-                matchingFonts := Screen current listOfAvailableFonts select:[:f | fontPref match:f encoding].
-                matchingFonts size == 0 ifTrue:[
-                    (Dialog 
-                        confirm:(resources 
-                                    string:'your display does not offer any %1-encoded font.\\Change the language anyway ?\ (texts will probably be unreadable then)'
-                                      with:fontPref) withCRs)
-                    ifFalse:[
-                        switch := false
-                    ]
-                ] ifFalse:[
-                    answer := Dialog 
-                                confirmWithCancel:(resources 
-                                                        string:'menu font is not %1-encoded.\\Change it ?'
-                                                        with:fontPref) withCRs
-                                           labels:(resources
-                                                        array:#('cancel' 'no' 'yes'))
-                                           default:3.
-                    answer isNil ifTrue:[
-                        switch := false
-                    ] ifFalse:[
-                        answer ifTrue:[
-                            switch := (self fontBoxForEncoding:fontPref)
-                        ]
-                    ].
-                ].
-            ].
-
-            switch ifTrue:[
-                transcript showCR:'change language to ' , newLanguage , ' ...'.
-                Smalltalk language:language asSymbol.
-                ResourcePack flushCachedResourcePacks
-            ].
-        ].
-        switch ifTrue:[
-            self reopenLauncher.
-        ]
+	self withWaitCursorDo:[
+	    |fontPref idx language oldLanguage enc answer matchingFonts|
+
+	    idx := translatedLanguages indexOf:newLanguage withoutSeparators.
+	    idx ~~ 0 ifTrue:[
+		language := listOfLanguages at:idx
+	    ] ifFalse:[
+		language := newLanguage
+	    ].
+
+	    "/ check if the new language needs a differently encoded font;
+	    "/ ask user to switch font and allow cancellation.
+	    "/ Otherwise, you are left with unreadable menu & button items ...
+
+	    oldLanguage := Smalltalk language.
+	    Smalltalk language:language asSymbol.
+	    ResourcePack flushCachedResourcePacks.
+	    fontPref := self class classResources at:'PREFERRED_FONT_ENCODING'.
+	    Smalltalk language:oldLanguage.
+
+	    switch := true.
+	    enc := MenuView defaultFont encoding.
+	    (fontPref match:enc) ifFalse:[
+		"/ look if there is one at all.
+		matchingFonts := Screen current listOfAvailableFonts select:[:f | fontPref match:f encoding].
+		matchingFonts size == 0 ifTrue:[
+		    (Dialog 
+			confirm:(resources 
+				    string:'your display does not offer any %1-encoded font.\\Change the language anyway ?\ (texts will probably be unreadable then)'
+				      with:fontPref) withCRs)
+		    ifFalse:[
+			switch := false
+		    ]
+		] ifFalse:[
+		    answer := Dialog 
+				confirmWithCancel:(resources 
+							string:'menu font is not %1-encoded.\\Change it ?'
+							with:fontPref) withCRs
+					   labels:(resources
+							array:#('cancel' 'no' 'yes'))
+					   default:3.
+		    answer isNil ifTrue:[
+			switch := false
+		    ] ifFalse:[
+			answer ifTrue:[
+			    switch := (self fontBoxForEncoding:fontPref)
+			]
+		    ].
+		].
+	    ].
+
+	    switch ifTrue:[
+		transcript showCR:'change language to ' , newLanguage , ' ...'.
+		Smalltalk language:language asSymbol.
+		ResourcePack flushCachedResourcePacks
+	    ].
+	].
+	switch ifTrue:[
+	    self reopenLauncher.
+	]
     ].    
     box
-        addHelpButtonFor:'Launcher/languageSetting.html'.
+	addHelpButtonFor:'Launcher/languageSetting.html'.
     box open.
     box destroy
 
@@ -1843,11 +1847,11 @@
     box addHorizontalLine.
 
     component := box 
-                    addLabelledInputField:(resources string:'size of newSpace:')
-                    adjust:#right
-                    on:nil "/ newSpaceSize 
-                    tabable:true
-                    separateAtX:0.7.
+		    addLabelledInputField:(resources string:'size of newSpace:')
+		    adjust:#right
+		    on:nil "/ newSpaceSize 
+		    tabable:true
+		    separateAtX:0.7.
     component acceptOnLeave:false.
     component converter:(PrintConverter new initForNumber).
     component model:newSpaceSize.
@@ -1857,11 +1861,11 @@
 
 
     component := box 
-                    addLabelledInputField:(resources string:'incremental GC allocation trigger:')
-                    adjust:#right
-                    on:nil "/ igcLimit 
-                    tabable:true
-                    separateAtX:0.7.
+		    addLabelledInputField:(resources string:'incremental GC allocation trigger:')
+		    adjust:#right
+		    on:nil "/ igcLimit 
+		    tabable:true
+		    separateAtX:0.7.
     component acceptOnLeave:false.
     component converter:(PrintConverter new initForNumber).
     component model:igcLimit.
@@ -1871,11 +1875,11 @@
     box addHorizontalLine.
 
     component := box 
-                    addLabelledInputField:(resources string:'incremental GC freespace trigger:')
-                    adjust:#right
-                    on:nil "/ igcFreeLimit 
-                    tabable:true
-                    separateAtX:0.7.
+		    addLabelledInputField:(resources string:'incremental GC freespace trigger:')
+		    adjust:#right
+		    on:nil "/ igcFreeLimit 
+		    tabable:true
+		    separateAtX:0.7.
     component acceptOnLeave:false.
     component converter:(PrintConverter new initForNumber).
     component model:igcFreeLimit.
@@ -1885,11 +1889,11 @@
     box addHorizontalLine.
 
     component := box 
-                    addLabelledInputField:(resources string:'incremental GC amount:')
-                    adjust:#right
-                    on:nil "/ igcFreeAmount 
-                    tabable:true
-                    separateAtX:0.7.
+		    addLabelledInputField:(resources string:'incremental GC amount:')
+		    adjust:#right
+		    on:nil "/ igcFreeAmount 
+		    tabable:true
+		    separateAtX:0.7.
     component acceptOnLeave:false.
     component converter:(PrintConverter new initForNumber).
     component model:igcFreeAmount.
@@ -1899,11 +1903,11 @@
     box addHorizontalLine.
 
     component := box 
-                    addLabelledInputField:(resources string:'oldspace increment:')
-                    adjust:#right
-                    on:nil "/ oldIncr 
-                    tabable:true
-                    separateAtX:0.7.
+		    addLabelledInputField:(resources string:'oldspace increment:')
+		    adjust:#right
+		    on:nil "/ oldIncr 
+		    tabable:true
+		    separateAtX:0.7.
     component acceptOnLeave:false.
     component converter:(PrintConverter new initForNumber).
     component model:oldIncr.
@@ -1913,11 +1917,11 @@
     box addHorizontalLine.
 
     component := box 
-                    addLabelledInputField:(resources string:'oldspace compress limit:')
-                    adjust:#right
-                    on:nil "/ compressLimit 
-                    tabable:true
-                    separateAtX:0.7.
+		    addLabelledInputField:(resources string:'oldspace compress limit:')
+		    adjust:#right
+		    on:nil "/ compressLimit 
+		    tabable:true
+		    separateAtX:0.7.
     component acceptOnLeave:false.
     component converter:(PrintConverter new initForNumber).
     component model:compressLimit.
@@ -1927,11 +1931,11 @@
     box addHorizontalLine.
 
     component := box 
-                    addLabelledInputField:(resources string:'stack limit:')
-                    adjust:#right
-                    on:nil 
-                    tabable:true
-                    separateAtX:0.7.
+		    addLabelledInputField:(resources string:'stack limit:')
+		    adjust:#right
+		    on:nil 
+		    tabable:true
+		    separateAtX:0.7.
     component acceptOnLeave:false.
     component converter:(PrintConverter new initForNumber).
     component model:stackLimit.
@@ -1941,38 +1945,38 @@
     box addHorizontalLine.
 
     ObjectMemory supportsJustInTimeCompilation ifTrue:[
-        component := box 
-                        addLabelledInputField:(resources string:'dynamic code limit:')
-                        adjust:#right
-                        on:nil
-                        tabable:true
-                        separateAtX:0.7.
-        component acceptOnLeave:false.
-        component converter:(PrintConverter new initForNumberOrNil).
-        component model:codeLimit.
-        fields add:component.
-
-        box addTextLabel:'(flush dynamic compiled code to stay within this limit)'.
-        box addHorizontalLine.
-
-        component := box 
-                        addLabelledInputField:(resources string:'dynamic code GC trigger:')
-                        adjust:#right
-                        on:nil
-                        tabable:true
-                        separateAtX:0.7.
-        component acceptOnLeave:false.
-        component converter:(PrintConverter new initForNumberOrNil).
-        component model:codeTrigger.
-        fields add:component.
-
-        box addTextLabel:'(start incremental GC whenever this amount of code has been allocated)'.
-        box addHorizontalLine.
+	component := box 
+			addLabelledInputField:(resources string:'dynamic code limit:')
+			adjust:#right
+			on:nil
+			tabable:true
+			separateAtX:0.7.
+	component acceptOnLeave:false.
+	component converter:(PrintConverter new initForNumberOrNil).
+	component model:codeLimit.
+	fields add:component.
+
+	box addTextLabel:'(flush dynamic compiled code to stay within this limit)'.
+	box addHorizontalLine.
+
+	component := box 
+			addLabelledInputField:(resources string:'dynamic code GC trigger:')
+			adjust:#right
+			on:nil
+			tabable:true
+			separateAtX:0.7.
+	component acceptOnLeave:false.
+	component converter:(PrintConverter new initForNumberOrNil).
+	component model:codeTrigger.
+	fields add:component.
+
+	box addTextLabel:'(start incremental GC whenever this amount of code has been allocated)'.
+	box addHorizontalLine.
     ].
 
     box addAbortButton; addOkButton.
     box
-        addHelpButtonFor:'Launcher/memorySettings.html'.
+	addHelpButtonFor:'Launcher/memorySettings.html'.
 
     "/
     "/ show the box ...
@@ -1983,29 +1987,29 @@
     "/ update system settings
     "/
     box accepted ifTrue:[
-        fields do:[:comp | comp accept].
-
-        igcFreeAmount value ~~ ObjectMemory freeSpaceGCAmount ifTrue:[
-            ObjectMemory freeSpaceGCAmount:igcFreeAmount value.
-        ].
-        igcFreeLimit value ~~ ObjectMemory freeSpaceGCLimit ifTrue:[
-            ObjectMemory freeSpaceGCLimit:igcFreeLimit value.
-        ].
-        igcLimit value ~~ ObjectMemory incrementalGCLimit ifTrue:[
-            ObjectMemory incrementalGCLimit:igcLimit value.
-        ].
-        newSpaceSize value ~~ ObjectMemory newSpaceSize ifTrue:[
-            ObjectMemory newSpaceSize:newSpaceSize value.
-        ].
-        oldIncr value ~~ ObjectMemory oldSpaceIncrement ifTrue:[
-            ObjectMemory oldSpaceIncrement:oldIncr value.
-        ].
-        stackLimit value ~~ Process defaultMaximumStackSize ifTrue:[
-            Process defaultMaximumStackSize:stackLimit value.
-        ].
-        ObjectMemory oldSpaceCompressLimit:compressLimit value.
-        ObjectMemory dynamicCodeLimit:codeLimit value.
-        ObjectMemory dynamicCodeGCTrigger:codeTrigger value.
+	fields do:[:comp | comp accept].
+
+	igcFreeAmount value ~~ ObjectMemory freeSpaceGCAmount ifTrue:[
+	    ObjectMemory freeSpaceGCAmount:igcFreeAmount value.
+	].
+	igcFreeLimit value ~~ ObjectMemory freeSpaceGCLimit ifTrue:[
+	    ObjectMemory freeSpaceGCLimit:igcFreeLimit value.
+	].
+	igcLimit value ~~ ObjectMemory incrementalGCLimit ifTrue:[
+	    ObjectMemory incrementalGCLimit:igcLimit value.
+	].
+	newSpaceSize value ~~ ObjectMemory newSpaceSize ifTrue:[
+	    ObjectMemory newSpaceSize:newSpaceSize value.
+	].
+	oldIncr value ~~ ObjectMemory oldSpaceIncrement ifTrue:[
+	    ObjectMemory oldSpaceIncrement:oldIncr value.
+	].
+	stackLimit value ~~ Process defaultMaximumStackSize ifTrue:[
+	    Process defaultMaximumStackSize:stackLimit value.
+	].
+	ObjectMemory oldSpaceCompressLimit:compressLimit value.
+	ObjectMemory dynamicCodeLimit:codeLimit value.
+	ObjectMemory dynamicCodeGCTrigger:codeTrigger value.
     ].
     box destroy
 
@@ -2037,10 +2041,10 @@
     box open.
 
     box accepted ifTrue:[
-        ObjectMemory infoPrinting:vmInfo value.
-        ObjectMemory debugPrinting:vmErrors value.
-        Object infoPrinting:classInfos value.
-        DeviceWorkstation errorPrinting:displayErrors value.
+	ObjectMemory infoPrinting:vmInfo value.
+	ObjectMemory debugPrinting:vmErrors value.
+	Object infoPrinting:classInfos value.
+	DeviceWorkstation errorPrinting:displayErrors value.
     ].
     box destroy
 
@@ -2082,9 +2086,9 @@
     box addCheckBox:(resources string:'preemptive scheduling') on:preemptive.
 
     box 
-        addHelpButtonFor:'Launcher/miscSettings.html';
-        addAbortButton; 
-        addOkButton.
+	addHelpButtonFor:'Launcher/miscSettings.html';
+	addAbortButton; 
+	addOkButton.
 
     "/
     "/ show the box ...
@@ -2095,18 +2099,18 @@
     "/ update system settings
     "/
     box accepted ifTrue:[
-        PopUpView shadows:shadows value.
-        StandardSystemView includeHostNameInLabel:hostNameInLabel value.
-        StandardSystemView returnFocusWhenClosingModalBoxes:returnFocus value.
-        StandardSystemView takeFocusWhenMapped:takeFocus value.
-        MenuView showAcceleratorKeys:showAccelerators value.
-        Processor isTimeSlicing ~~ preemptive value ifTrue:[
-            preemptive value ifTrue:[
-                Processor startTimeSlicing
-            ] ifFalse:[
-                Processor stopTimeSlicing
-            ]
-        ]
+	PopUpView shadows:shadows value.
+	StandardSystemView includeHostNameInLabel:hostNameInLabel value.
+	StandardSystemView returnFocusWhenClosingModalBoxes:returnFocus value.
+	StandardSystemView takeFocusWhenMapped:takeFocus value.
+	MenuView showAcceleratorKeys:showAccelerators value.
+	Processor isTimeSlicing ~~ preemptive value ifTrue:[
+	    preemptive value ifTrue:[
+		Processor startTimeSlicing
+	    ] ifFalse:[
+		Processor stopTimeSlicing
+	    ]
+	]
     ].
     box destroy
 
@@ -2172,12 +2176,12 @@
 
     commandList := resources at:'PRINT_COMMANDS' ifAbsent:nil.
     commandList isNil ifTrue:[
-        commandList := PrinterStream defaultCommands.
-        commandList isNil ifTrue:[
-            commandList := #('lpr' 
-                             'lp' 
-                            ).
-        ]
+	commandList := PrinterStream defaultCommands.
+	commandList isNil ifTrue:[
+	    commandList := #('lpr' 
+			     'lp' 
+			    ).
+	]
     ].
 
     commandListPop list:commandList.
@@ -2197,24 +2201,24 @@
 
     y := box yPosition.
     box
-        addRow:(1 to:2)
-        fromX:0
-        toX:0.5
-        collect:[:idx | row at:idx]
-        tabable:false
-        horizontalLayout:#leftSpace
-        verticalLayout:#center.
+	addRow:(1 to:2)
+	fromX:0
+	toX:0.5
+	collect:[:idx | row at:idx]
+	tabable:false
+	horizontalLayout:#leftSpace
+	verticalLayout:#center.
     y1 := box yPosition.
     box yPosition:y.
 
     box
-        addRow:(3 to:4)
-        fromX:0.5
-        toX:1.0
-        collect:[:idx | row at:idx]
-        tabable:false
-        horizontalLayout:#leftSpace
-        verticalLayout:#center.
+	addRow:(3 to:4)
+	fromX:0.5
+	toX:1.0
+	collect:[:idx | row at:idx]
+	tabable:false
+	horizontalLayout:#leftSpace
+	verticalLayout:#center.
 
     box yPosition:(box yPosition max:y1).
 
@@ -2228,12 +2232,12 @@
     y := box yPosition.
 
     topMarginComponent := box 
-        addLabelledInputField:(resources string:'top margin:')
-        adjust:#right
-        on:nil "/ topMargin 
-        tabable:true
-        from:0.0 to:0.5
-        separateAtX:0.6.
+	addLabelledInputField:(resources string:'top margin:')
+	adjust:#right
+	on:nil "/ topMargin 
+	tabable:true
+	from:0.0 to:0.5
+	separateAtX:0.6.
     topMarginComponent converter:(PrintConverter new initForNumber).
     topMarginComponent model:topMargin.
     y1 := box yPosition.
@@ -2244,38 +2248,38 @@
 
     component := box addComponent:(PopUpList on:unitList).
     component
-        left:0.6;
-        width:0.3.
+	left:0.6;
+	width:0.3.
 
     box yPosition:y1.
 
     leftMarginComponent := box 
-        addLabelledInputField:(resources string:'left margin:')
-        adjust:#right
-        on:nil "/ leftMargin 
-        tabable:true
-        from:0.0 to:0.5
-        separateAtX:0.6.
+	addLabelledInputField:(resources string:'left margin:')
+	adjust:#right
+	on:nil "/ leftMargin 
+	tabable:true
+	from:0.0 to:0.5
+	separateAtX:0.6.
     leftMarginComponent converter:(PrintConverter new initForNumber).
     leftMarginComponent model:leftMargin.
 
     rightMarginComponent := box 
-        addLabelledInputField:(resources string:'right margin:')
-        adjust:#right
-        on:nil "/ rightMargin 
-        tabable:true
-        from:0.0 to:0.5
-        separateAtX:0.6.
+	addLabelledInputField:(resources string:'right margin:')
+	adjust:#right
+	on:nil "/ rightMargin 
+	tabable:true
+	from:0.0 to:0.5
+	separateAtX:0.6.
     rightMarginComponent converter:(PrintConverter new initForNumber).
     rightMarginComponent model:rightMargin.
 
     bottomMarginComponent := box 
-        addLabelledInputField:(resources string:'bottom margin:')
-        adjust:#right
-        on:nil "/ bottomMargin 
-        tabable:true
-        from:0.0 to:0.5
-        separateAtX:0.6.
+	addLabelledInputField:(resources string:'bottom margin:')
+	adjust:#right
+	on:nil "/ bottomMargin 
+	tabable:true
+	from:0.0 to:0.5
+	separateAtX:0.6.
     bottomMarginComponent converter:(PrintConverter new initForNumber).
     bottomMarginComponent model:bottomMargin.
 
@@ -2285,102 +2289,102 @@
 
     updater := [ |p fg hasPageSize hasMargins|
 
-                       printerType selectionIndex ~~ 0 ifTrue:[
-                           p := possiblePrinters at:(printerType selectionIndex).
-                           hasPageSize := p supportsPageSizes. 
-                           hasMargins := p supportsMargins. 
-                       ] ifFalse:[
-                           hasPageSize := false.
-                           hasMargins := false.
-                       ].
-                       hasPageSize ifTrue:[
-                          fg := Button new foregroundColor.
-                          formatComponent enable.
-                          landscapeComponent enable.
-
-                          formatComponent label:p pageFormat.
-                          pageFormat value:(p pageFormat).
-                          landscape value:(p landscape).
-                       ] ifFalse:[ 
-                          fg := Button new disabledForegroundColor.
-                          formatComponent disable.
-                          landscapeComponent disable.
-
-                          formatComponent label:'unknown'.
-                          landscape value:nil.
-                       ].
-                       hasMargins ifTrue:[
-                          unitList selectionIndex == 2 ifTrue:[
-                              unit := #mm
-                          ] ifFalse:[
-                              unit := #inch
-                          ].
-
-                          topMargin value:(UnitConverter convert:p topMargin from:#inch to:unit).
-                          leftMargin value:(UnitConverter convert:p leftMargin from:#inch to:unit).
-                          rightMargin value:(UnitConverter convert:p rightMargin from:#inch to:unit).
-                          bottomMargin value:(UnitConverter convert:p bottomMargin from:#inch to:unit).
-
-                          topMarginComponent enable.
-                          leftMarginComponent enable.
-                          rightMarginComponent enable.
-                          bottomMarginComponent enable.
-                       ] ifFalse:[ 
-                          topMarginComponent disable.
-                          leftMarginComponent disable.
-                          rightMarginComponent disable.
-                          bottomMarginComponent disable.
-                       ].
-                       formatLabel foregroundColor:fg.
-                       landscapeLabel foregroundColor:fg.
+		       printerType selectionIndex ~~ 0 ifTrue:[
+			   p := possiblePrinters at:(printerType selectionIndex).
+			   hasPageSize := p supportsPageSizes. 
+			   hasMargins := p supportsMargins. 
+		       ] ifFalse:[
+			   hasPageSize := false.
+			   hasMargins := false.
+		       ].
+		       hasPageSize ifTrue:[
+			  fg := Button new foregroundColor.
+			  formatComponent enable.
+			  landscapeComponent enable.
+
+			  formatComponent label:p pageFormat.
+			  pageFormat value:(p pageFormat).
+			  landscape value:(p landscape).
+		       ] ifFalse:[ 
+			  fg := Button new disabledForegroundColor.
+			  formatComponent disable.
+			  landscapeComponent disable.
+
+			  formatComponent label:'unknown'.
+			  landscape value:nil.
+		       ].
+		       hasMargins ifTrue:[
+			  unitList selectionIndex == 2 ifTrue:[
+			      unit := #mm
+			  ] ifFalse:[
+			      unit := #inch
+			  ].
+
+			  topMargin value:(UnitConverter convert:p topMargin from:#inch to:unit).
+			  leftMargin value:(UnitConverter convert:p leftMargin from:#inch to:unit).
+			  rightMargin value:(UnitConverter convert:p rightMargin from:#inch to:unit).
+			  bottomMargin value:(UnitConverter convert:p bottomMargin from:#inch to:unit).
+
+			  topMarginComponent enable.
+			  leftMarginComponent enable.
+			  rightMarginComponent enable.
+			  bottomMarginComponent enable.
+		       ] ifFalse:[ 
+			  topMarginComponent disable.
+			  leftMarginComponent disable.
+			  rightMarginComponent disable.
+			  bottomMarginComponent disable.
+		       ].
+		       formatLabel foregroundColor:fg.
+		       landscapeLabel foregroundColor:fg.
                         
-                       p notNil ifTrue:[ 
-                           commandList := p defaultCommands.
-                           commandList notNil ifTrue:[
-                                commandListPop list:commandList 
-                           ].
-
-                           printCommand value:(p printCommand).
-                       ].
-                       p supportsPostscript ifFalse:[
-                           supportsColorComponent disable.
-                           supportsColor value:false
-                       ] ifTrue:[
-                           supportsColorComponent enable.
-                           supportsColor value:(Printer supportsColor).
-                       ]
-                     ].
+		       p notNil ifTrue:[ 
+			   commandList := p defaultCommands.
+			   commandList notNil ifTrue:[
+				commandListPop list:commandList 
+			   ].
+
+			   printCommand value:(p printCommand).
+		       ].
+		       p supportsPostscript ifFalse:[
+			   supportsColorComponent disable.
+			   supportsColor value:false
+		       ] ifTrue:[
+			   supportsColorComponent enable.
+			   supportsColor value:(Printer supportsColor).
+		       ]
+		     ].
     unitList onChangeSend:#value to:updater.
     printerType onChangeSend:#value to:updater.
     updater value.
 
     box addVerticalSpace;
-        addHelpButtonFor:'Launcher/printerSettings.html';
-        addAbortButton; addOkButton.
+	addHelpButtonFor:'Launcher/printerSettings.html';
+	addAbortButton; addOkButton.
     box open.
 
     box accepted ifTrue:[
-        Printer := possiblePrinters at:(printerType selectionIndex).
-        Printer printCommand:printCommand value.
-
-        Printer supportsPageSizes ifTrue:[
-            Printer pageFormat:(pageFormat selection).
-            Printer landscape:(landscape value).
-        ].
-        Printer supportsMargins ifTrue:[
-            unitList selectionIndex == 2 ifTrue:[
-                unit := #mm
-            ] ifFalse:[
-                unit := #inch
-            ].
-            Printer topMargin:(UnitConverter convert:topMargin value from:unit to:#inch).
-            Printer leftMargin:(UnitConverter convert:leftMargin value from:unit to:#inch).
-            Printer rightMargin:(UnitConverter convert:rightMargin value from:unit to:#inch).
-            Printer bottomMargin:(UnitConverter convert:bottomMargin value from:unit to:#inch).
-        ].
-        Printer supportsPostscript ifTrue:[
-            Printer supportsColor:supportsColor value.
-        ].
+	Printer := possiblePrinters at:(printerType selectionIndex).
+	Printer printCommand:printCommand value.
+
+	Printer supportsPageSizes ifTrue:[
+	    Printer pageFormat:(pageFormat selection).
+	    Printer landscape:(landscape value).
+	].
+	Printer supportsMargins ifTrue:[
+	    unitList selectionIndex == 2 ifTrue:[
+		unit := #mm
+	    ] ifFalse:[
+		unit := #inch
+	    ].
+	    Printer topMargin:(UnitConverter convert:topMargin value from:unit to:#inch).
+	    Printer leftMargin:(UnitConverter convert:leftMargin value from:unit to:#inch).
+	    Printer rightMargin:(UnitConverter convert:rightMargin value from:unit to:#inch).
+	    Printer bottomMargin:(UnitConverter convert:bottomMargin value from:unit to:#inch).
+	].
+	Printer supportsPostscript ifTrue:[
+	    Printer supportsColor:supportsColor value.
+	].
     ].
     box destroy
 
@@ -2397,22 +2401,22 @@
     |fileName|
 
     fileName := Dialog 
-        requestFileName:(resources string:'restore settings from:') 
-        default:'settings.stx'
-        ok:(resources string:'restore') 
-        abort:(resources string:'cancel') 
-        pattern:'*.stx'
-        fromDirectory:nil.
+	requestFileName:(resources string:'restore settings from:') 
+	default:'settings.stx'
+	ok:(resources string:'restore') 
+	abort:(resources string:'cancel') 
+	pattern:'*.stx'
+	fromDirectory:nil.
 
     (fileName isNil or:[fileName isEmpty]) ifTrue:[
-        "/ canceled
-        ^ self
+	"/ canceled
+	^ self
     ].
 
     self withWaitCursorDo:[
-        Smalltalk fileIn:fileName.
-
-        self reopenLauncher.
+	Smalltalk fileIn:fileName.
+
+	self reopenLauncher.
     ].
 
     "Modified: 8.1.1997 / 14:53:52 / cg"
@@ -2427,22 +2431,22 @@
     |s screen fileName|
 
     fileName := Dialog 
-        requestFileName:(resources string:'save settings in:') 
-        default:'settings.stx'
-        ok:(resources string:'save') 
-        abort:(resources string:'cancel') 
-        pattern:'*.stx'
-        fromDirectory:nil.
+	requestFileName:(resources string:'save settings in:') 
+	default:'settings.stx'
+	ok:(resources string:'save') 
+	abort:(resources string:'cancel') 
+	pattern:'*.stx'
+	fromDirectory:nil.
 
     (fileName isNil or:[fileName isEmpty]) ifTrue:[
-        "/ canceled
-        ^ self
+	"/ canceled
+	^ self
     ].
 
     s := fileName asFilename writeStream.
     s isNil ifTrue:[
-        self warn:'cannot write the ''' , fileName , ''' file'.
-        ^ self
+	self warn:'cannot write the ''' , fileName , ''' file'.
+	^ self
     ].
 
     s nextPutLine:'"/ ST/X saved settings';
@@ -2465,12 +2469,12 @@
     s nextPutLine:'Display displayName = ' , (Display displayName storeString) , ' ifTrue:['.
       screen := Screen current.
       screen fixColors notNil ifTrue:[
-        s nextPutLine:'  Image flushDeviceImages.'.
-        s nextPutLine:'  Color colorAllocationFailSignal catch:['.
-        s nextPutLine:'    Color getColorsRed:6 green:6 blue:4 on:Display'.
-        s nextPutLine:'  ].'.
+	s nextPutLine:'  Image flushDeviceImages.'.
+	s nextPutLine:'  Color colorAllocationFailSignal catch:['.
+	s nextPutLine:'    Color getColorsRed:6 green:6 blue:4 on:Display'.
+	s nextPutLine:'  ].'.
       ] ifFalse:[
-        s nextPutLine:'  Display releaseFixColors.'.
+	s nextPutLine:'  Display releaseFixColors.'.
       ].
       s nextPutLine:'  Display hasColors: ' , (screen hasColors storeString) , '.'.
       s nextPutLine:'  Display widthInMillimeter: ' , (screen widthInMillimeter storeString) , '.'.
@@ -2504,14 +2508,14 @@
       nextPutLine:'ObjectMemory fullSingleStepSupport: ' , (ObjectMemory fullSingleStepSupport storeString) , '.'.
 
     HistoryManager isActive ifTrue:[
-        s nextPutLine:'HistoryManager activate.'.
+	s nextPutLine:'HistoryManager activate.'.
     ] ifFalse:[
-        s nextPutLine:'HistoryManager deactivate.'.
+	s nextPutLine:'HistoryManager deactivate.'.
     ].
 
     ObjectFileLoader notNil ifTrue:[
-        s nextPutLine:'ObjectFileLoader searchedLibraries: ' , (ObjectFileLoader searchedLibraries storeString) , '.'.
-        s nextPutLine:'ObjectFileLoader libPath: ' , (ObjectFileLoader libPath storeString) , '.'.
+	s nextPutLine:'ObjectFileLoader searchedLibraries: ' , (ObjectFileLoader searchedLibraries storeString) , '.'.
+	s nextPutLine:'ObjectFileLoader libPath: ' , (ObjectFileLoader libPath storeString) , '.'.
     ].
 
     s nextPutLine:'Class catchMethodRedefinitions: ' , (Class catchMethodRedefinitions storeString) , '.'.
@@ -2546,7 +2550,7 @@
       nextPutLine:'MenuView showAcceleratorKeys: ' , (MenuView showAcceleratorKeys storeString) , '.';
       nextPutLine:'Class tryLocalSourceFirst: ' , (Class tryLocalSourceFirst storeString) , '.'.
     (Exception emergencyHandler == Launcher notifyingEmergencyHandler) ifTrue:[
-        s nextPutLine:'Exception emergencyHandler:(Launcher notifyingEmergencyHandler).'.
+	s nextPutLine:'Exception emergencyHandler:(Launcher notifyingEmergencyHandler).'.
     ].
 
     s cr.
@@ -2557,17 +2561,17 @@
       nextPutLine:'Printer printCommand: ' , (Printer printCommand storeString) , '.'.
 
     Printer supportsPageSizes ifTrue:[
-        s nextPutLine:'Printer pageFormat: ' , (Printer pageFormat storeString) , '.'.
-        s nextPutLine:'Printer landscape: ' , (Printer landscape storeString) , '.'.
+	s nextPutLine:'Printer pageFormat: ' , (Printer pageFormat storeString) , '.'.
+	s nextPutLine:'Printer landscape: ' , (Printer landscape storeString) , '.'.
     ].
     Printer supportsMargins ifTrue:[
-        s nextPutLine:'Printer topMargin: ' , (Printer topMargin storeString) , '.'.
-        s nextPutLine:'Printer leftMargin: ' , (Printer leftMargin storeString) , '.'.
-        s nextPutLine:'Printer rightMargin: ' , (Printer rightMargin storeString) , '.'.
-        s nextPutLine:'Printer bottomMargin: ' , (Printer bottomMargin storeString) , '.'.
+	s nextPutLine:'Printer topMargin: ' , (Printer topMargin storeString) , '.'.
+	s nextPutLine:'Printer leftMargin: ' , (Printer leftMargin storeString) , '.'.
+	s nextPutLine:'Printer rightMargin: ' , (Printer rightMargin storeString) , '.'.
+	s nextPutLine:'Printer bottomMargin: ' , (Printer bottomMargin storeString) , '.'.
     ].
     Printer supportsPostscript ifTrue:[
-        s nextPutLine:'Printer supportsColor: ' , (Printer supportsColor storeString) , '.'.
+	s nextPutLine:'Printer supportsColor: ' , (Printer supportsColor storeString) , '.'.
     ].
 
     s cr.
@@ -2619,20 +2623,20 @@
     changeFileName := ObjectMemory nameForChanges asValue.
 
     hasManager := AbstractSourceCodeManager notNil
-                  and:[AbstractSourceCodeManager isLoaded].
+		  and:[AbstractSourceCodeManager isLoaded].
 
     hasManager ifTrue:[
-        useManager := (manager := Smalltalk at:#SourceCodeManager) notNil asValue.
-        localSourceFirst := Class tryLocalSourceFirst asValue.
-        manager notNil ifTrue:[
-            repository := manager repositoryName.
-            repository notNil ifTrue:[
-                repositoryHolder := repository asValue
-            ]
-        ].
+	useManager := (manager := Smalltalk at:#SourceCodeManager) notNil asValue.
+	localSourceFirst := Class tryLocalSourceFirst asValue.
+	manager notNil ifTrue:[
+	    repository := manager repositoryName.
+	    repository notNil ifTrue:[
+		repositoryHolder := repository asValue
+	    ]
+	].
     ] ifFalse:[
-        useManager := false.
-        localSourceFirst := false
+	useManager := false.
+	localSourceFirst := false
     ].
     showErrorNotifier := (Exception emergencyHandler == Launcher notifyingEmergencyHandler) asValue.
     showVerboseStack := (DebugView defaultVerboseBacktrace ? false) asValue.
@@ -2653,11 +2657,11 @@
     box addCheckBox:(resources string:'log doIts in changes file') on:logDoits.
 
     component := box 
-                    addLabelledInputField:(resources string:'change file name:')
-                    adjust:#right
-                    on:changeFileName 
-                    tabable:true
-                    separateAtX:0.4.
+		    addLabelledInputField:(resources string:'change file name:')
+		    adjust:#right
+		    on:changeFileName 
+		    tabable:true
+		    separateAtX:0.4.
     component immediateAccept:true; acceptOnLeave:false.
 
 "/    y := box yPosition.
@@ -2672,47 +2676,47 @@
     box addCheckBox:(resources string:'lazy compilation when autoloading') on:compileLazy.
     check := box addCheckBox:(resources string:'if present, load binary objects when autoloading') on:loadBinaries.
     ObjectFileLoader isNil ifTrue:[
-        loadBinaries value:false.
-        check disable
+	loadBinaries value:false.
+	check disable
     ].
 
     hasManager ifTrue:[
-        check := box addCheckBox:(resources string:'sourcecode from sourcecode management') on:useManager.
-        oldIndent := box leftIndent.
-        box leftIndent:30.
-
-        repositoryHolder notNil ifTrue:[
-            component := box 
-                            addLabelledInputField:(resources string:'repository:')
-                            adjust:#right
-                            on:repositoryHolder 
-                            tabable:true
-                            separateAtX:0.4.
-            component immediateAccept:true; acceptOnLeave:false.
-        ].
-
-        localCheck := box addCheckBox:(resources string:'if present, use local source (suppress checkout)') on:localSourceFirst.
-        localCheck enableChannel:useManager.
-
-        cacheEntry := box 
-                        addLabelledInputField:(resources string:'source cache dir:')
-                        adjust:#right
-                        on:sourceCacheDir 
-                        tabable:true
-                        separateAtX:0.4.
-        cacheEntry immediateAccept:true; acceptOnLeave:false.
-        box leftIndent:oldIndent.
-        cacheEntry enableChannel:useManager.
-
-        (AbstractSourceCodeManager isNil 
-        or:[AbstractSourceCodeManager defaultManager isNil]) ifTrue:[
-            useManager value:false.
-            cacheEntry disable.
-            check disable.
-            localCheck enable.
-        ] ifFalse:[
-            sourceCacheDir value:(AbstractSourceCodeManager cacheDirectoryName).
-        ].
+	check := box addCheckBox:(resources string:'sourcecode from sourcecode management') on:useManager.
+	oldIndent := box leftIndent.
+	box leftIndent:30.
+
+	repositoryHolder notNil ifTrue:[
+	    component := box 
+			    addLabelledInputField:(resources string:'repository:')
+			    adjust:#right
+			    on:repositoryHolder 
+			    tabable:true
+			    separateAtX:0.4.
+	    component immediateAccept:true; acceptOnLeave:false.
+	].
+
+	localCheck := box addCheckBox:(resources string:'if present, use local source (suppress checkout)') on:localSourceFirst.
+	localCheck enableChannel:useManager.
+
+	cacheEntry := box 
+			addLabelledInputField:(resources string:'source cache dir:')
+			adjust:#right
+			on:sourceCacheDir 
+			tabable:true
+			separateAtX:0.4.
+	cacheEntry immediateAccept:true; acceptOnLeave:false.
+	box leftIndent:oldIndent.
+	cacheEntry enableChannel:useManager.
+
+	(AbstractSourceCodeManager isNil 
+	or:[AbstractSourceCodeManager defaultManager isNil]) ifTrue:[
+	    useManager value:false.
+	    cacheEntry disable.
+	    check disable.
+	    localCheck enable.
+	] ifFalse:[
+	    sourceCacheDir value:(AbstractSourceCodeManager cacheDirectoryName).
+	].
     ].
 
     box addHorizontalLine.
@@ -2721,9 +2725,9 @@
     box addCheckBox:(resources string:'verbose backtrace by default in debugger') on:showVerboseStack.
 
     box 
-        addHelpButtonFor:'Launcher/sourceSettings.html';
-        addAbortButton; 
-        addOkButton.
+	addHelpButtonFor:'Launcher/sourceSettings.html';
+	addAbortButton; 
+	addOkButton.
 
     "/
     "/ show the box ...
@@ -2734,49 +2738,49 @@
     "/ update system settings
     "/
     box accepted ifTrue:[
-        Class keepMethodHistory:keepMethodHistory value.
-        Smalltalk logDoits:logDoits value.
-        Class updateChanges:updChanges value.
-        Autoload compileLazy:compileLazy value.
-        Smalltalk loadBinaries:loadBinaries value.
-        ObjectMemory nameForChanges:changeFileName value.
-
-        (hasManager and:[useManager value]) ifTrue:[
-            manager isNil ifTrue:[
-                Smalltalk at:#SourceCodeManager put:(AbstractSourceCodeManager defaultManager).
-                manager := Smalltalk at:#SourceCodeManager.
-            ].
-            Class tryLocalSourceFirst:(localSourceFirst value).
-            nm := sourceCacheDir value.
-            (fn := nm asFilename) exists ifFalse:[
-                (self confirm:(nm , ' does not exists\create ?' withCRs)) ifTrue:[
-                    fn makeDirectory; 
-                       makeReadableForAll;
-                       makeWritableForAll;
-                       makeExecutableForAll.
-                ]
-            ].
-            (fn exists 
-            and:[fn isDirectory
-            and:[fn isReadable
-            and:[fn isWritable]]]) ifTrue:[
-                AbstractSourceCodeManager cacheDirectoryName:(sourceCacheDir value).
-            ].
-            repositoryHolder notNil ifTrue:[
-                manager repositoryName:repositoryHolder value.
-                manager initialize
-            ].
-
-            showErrorNotifier value ifFalse:[
-                Exception emergencyHandler:nil
-            ] ifTrue:[
-                Exception emergencyHandler:(Launcher notifyingEmergencyHandler)
-            ].
-            DebugView defaultVerboseBacktrace:(showVerboseStack value).
-
-        ] ifFalse:[
-            Smalltalk at:#SourceCodeManager put:nil
-        ]
+	Class keepMethodHistory:keepMethodHistory value.
+	Smalltalk logDoits:logDoits value.
+	Class updateChanges:updChanges value.
+	Autoload compileLazy:compileLazy value.
+	Smalltalk loadBinaries:loadBinaries value.
+	ObjectMemory nameForChanges:changeFileName value.
+
+	(hasManager and:[useManager value]) ifTrue:[
+	    manager isNil ifTrue:[
+		Smalltalk at:#SourceCodeManager put:(AbstractSourceCodeManager defaultManager).
+		manager := Smalltalk at:#SourceCodeManager.
+	    ].
+	    Class tryLocalSourceFirst:(localSourceFirst value).
+	    nm := sourceCacheDir value.
+	    (fn := nm asFilename) exists ifFalse:[
+		(self confirm:(nm , ' does not exists\create ?' withCRs)) ifTrue:[
+		    fn makeDirectory; 
+		       makeReadableForAll;
+		       makeWritableForAll;
+		       makeExecutableForAll.
+		]
+	    ].
+	    (fn exists 
+	    and:[fn isDirectory
+	    and:[fn isReadable
+	    and:[fn isWritable]]]) ifTrue:[
+		AbstractSourceCodeManager cacheDirectoryName:(sourceCacheDir value).
+	    ].
+	    repositoryHolder notNil ifTrue:[
+		manager repositoryName:repositoryHolder value.
+		manager initialize
+	    ].
+
+	    showErrorNotifier value ifFalse:[
+		Exception emergencyHandler:nil
+	    ] ifTrue:[
+		Exception emergencyHandler:(Launcher notifyingEmergencyHandler)
+	    ].
+	    DebugView defaultVerboseBacktrace:(showVerboseStack value).
+
+	] ifFalse:[
+	    Smalltalk at:#SourceCodeManager put:nil
+	]
     ].
     box destroy
 
@@ -2797,8 +2801,8 @@
 
     resourceDir := Smalltalk getSystemFileName:'resources'.
     resourceDir isNil ifTrue:[
-        self warn:'no styles found (missing ''resources'' directory)'.
-        ^ self
+	self warn:'no styles found (missing ''resources'' directory)'.
+	^ self
     ].
     dir := FileDirectory directoryNamed:resourceDir.
 
@@ -2826,12 +2830,12 @@
 "/ new code: build box 'by 'hand'
 "/
     infoForwarder := [
-                        |nm sheet comment|
-                        nm := list selection.
-                        sheet := ViewStyle fromFile:(nm , '.style').
-                        comment := sheet at:#comment ifAbsent:''.
-                        infoLabel label:comment withCRs asStringCollection
-                       ].
+			|nm sheet comment|
+			nm := list selection.
+			sheet := ViewStyle fromFile:(nm , '.style').
+			comment := sheet at:#comment ifAbsent:''.
+			infoLabel label:comment withCRs asStringCollection
+		       ].
 
     list := SelectionInList with:listOfStyles.
     list onChangeSend:#value to:infoForwarder.
@@ -2856,14 +2860,14 @@
     box open.
 
     box accepted ifTrue:[
-        newStyle := list selection.
-        newStyle notNil ifTrue:[
-            self withWaitCursorDo:[
-                transcript showCR:'change style to ' , newStyle , ' ...'.
-                View defaultStyle:newStyle asSymbol.
-            ].
-            self reopenLauncher.
-        ]
+	newStyle := list selection.
+	newStyle notNil ifTrue:[
+	    self withWaitCursorDo:[
+		transcript showCR:'change style to ' , newStyle , ' ...'.
+		View defaultStyle:newStyle asSymbol.
+	    ].
+	    self reopenLauncher.
+	]
     ].
     box destroy
 
@@ -2901,9 +2905,9 @@
     setOfViews addAll:(Project defaultProject views).
 
     setOfViews do:[:aTopView |
-        aTopView device == Screen current ifTrue:[
-            aTopView expand
-        ].
+	aTopView device == Screen current ifTrue:[
+	    aTopView expand
+	].
     ].
 
     "
@@ -2920,7 +2924,7 @@
 
     v := self findWindow.
     v notNil ifTrue:[
-        v destroy.
+	v destroy.
     ].
 
     "Created: 28.10.1996 / 14:39:23 / cg"
@@ -2934,7 +2938,7 @@
 
     v := self findWindow.
     v notNil ifTrue:[
-        v raiseDeiconified.
+	v raiseDeiconified.
     ].
 
     "Modified: 8.1.1997 / 14:54:59 / cg"
@@ -2945,12 +2949,12 @@
      save the contents of the whole screen."
 
     Processor 
-        addTimedBlock:[
-                        self 
-                            saveScreenImage:(Image fromScreen) 
-                            defaultName:'screen'
-                      ] 
-        afterSeconds:1
+	addTimedBlock:[
+			self 
+			    saveScreenImage:(Image fromScreen) 
+			    defaultName:'screen'
+		      ] 
+	afterSeconds:1
 
     "Modified: 23.9.1996 / 14:36:14 / cg"
 !
@@ -2980,9 +2984,9 @@
     setOfViews addAll:(Project defaultProject views).
 
     setOfViews do:[:aTopView |
-        aTopView device == Screen current ifTrue:[
-            aTopView collapse
-        ]
+	aTopView device == Screen current ifTrue:[
+	    aTopView collapse
+	]
     ]
 
     "Created: 1.3.1997 / 20:10:58 / cg"
@@ -3005,15 +3009,15 @@
     |area|
 
     Processor 
-        addTimedBlock:[
-                        [Screen current leftButtonPressed] whileTrue:[Processor yield].
-
-                        area := Rectangle fromUser.
-                        (area width > 0 and:[area height > 0]) ifTrue:[
-                            self saveScreenImage:(Image fromScreen:area) defaultName:'hardcopy'
-                        ]
-                      ] 
-        afterSeconds:1
+	addTimedBlock:[
+			[Screen current leftButtonPressed] whileTrue:[Processor yield].
+
+			area := Rectangle fromUser.
+			(area width > 0 and:[area height > 0]) ifTrue:[
+			    self saveScreenImage:(Image fromScreen:area) defaultName:'hardcopy'
+			]
+		      ] 
+	afterSeconds:1
 
     "Modified: 13.2.1997 / 16:02:35 / cg"
 !
@@ -3038,13 +3042,13 @@
     "open an interruptLatencyMonitor view"
 
     InterruptLatencyMonitor notNil ifTrue:[
-        Autoload autoloadFailedSignal catch:[
-            InterruptLatencyMonitor autoload.
-        ].
-        InterruptLatencyMonitor isLoaded ifTrue:[
-            InterruptLatencyMonitor open.
-            ^ self.
-        ]
+	Autoload autoloadFailedSignal catch:[
+	    InterruptLatencyMonitor autoload.
+	].
+	InterruptLatencyMonitor isLoaded ifTrue:[
+	    InterruptLatencyMonitor open.
+	    ^ self.
+	]
     ].
     self warn:'sorry - the irq latency monitor is only available
 in the full commercial release'.
@@ -3092,14 +3096,14 @@
 
     v := Screen current viewFromUser.
     v notNil ifTrue:[
-        v := v topView.
-        wg := v windowGroup.
-        wg notNil ifTrue:[
-            "/
-            "/ toggle eventTrace in its windowGroup
-            "/
-            wg traceEvents:(wg preEventHook isNil)
-        ]
+	v := v topView.
+	wg := v windowGroup.
+	wg notNil ifTrue:[
+	    "/
+	    "/ toggle eventTrace in its windowGroup
+	    "/
+	    wg traceEvents:(wg preEventHook isNil)
+	]
     ]
 
     "Created: 7.3.1996 / 14:44:22 / cg"
@@ -3113,7 +3117,7 @@
 
     v := self pickAView.
     v notNil ifTrue:[
-        WindowTreeView openOn:v topView
+	WindowTreeView openOn:v topView
     ]
 
     "Modified: 8.1.1997 / 14:55:59 / cg"
@@ -3133,15 +3137,15 @@
     id := device viewIdFromPoint:p.
     v := device viewFromId:id.
     v notNil ifTrue:[
-        v topView destroy.
-        ^ self
+	v topView destroy.
+	^ self
     ].
     id = device rootView id ifTrue:[
-        ^ self
+	^ self
     ].
     (Dialog confirm:'mhmh, this may not a be smalltalk view\(Or I somehow forgot about it).\Destroy anyway ?' withCRs)
     ifTrue:[
-        device destroyView:nil withId:id
+	device destroyView:nil withId:id
     ].
 
     "Modified: 18.9.1995 / 23:13:32 / claus"
@@ -3153,15 +3157,15 @@
      let user specify a view and save its contents."
 
     Processor 
-        addTimedBlock:[
-                        |v|
-
-                        v := Screen current viewFromUser.
-                        v notNil ifTrue:[
-                            self saveScreenImage:(Image fromView:(v topView)) defaultName:'hardcopy'
-                        ]
-                      ] 
-        afterSeconds:1
+	addTimedBlock:[
+			|v|
+
+			v := Screen current viewFromUser.
+			v notNil ifTrue:[
+			    self saveScreenImage:(Image fromView:(v topView)) defaultName:'hardcopy'
+			]
+		      ] 
+	afterSeconds:1
 
     "Modified: 23.9.1996 / 14:36:48 / cg"
 !
@@ -3174,7 +3178,7 @@
     v := self pickAView.
     v notNil ifTrue:[
 "/        v topView inspect
-        v inspect
+	v inspect
     ]
 
 ! !
@@ -3186,8 +3190,8 @@
 
     ((something == #currentProject)
     or:[changedObject == Project]) ifTrue:[
-        self changed:#info.
-        ^ self
+	self changed:#info.
+	^ self
     ].
 
     "Modified: 8.1.1997 / 14:57:07 / cg"
@@ -3200,8 +3204,8 @@
      and open a fileBrowser ..."
 
     anObjectOrCollection isCollection ifTrue:[
-        anObjectOrCollection size ~~ 1 ifTrue:[^ false].
-        ^ anObjectOrCollection first isFileObject
+	anObjectOrCollection size ~~ 1 ifTrue:[^ false].
+	^ anObjectOrCollection first isFileObject
     ].
     ^ anObjectOrCollection isFileObject
 
@@ -3214,18 +3218,18 @@
     |singleDropObject|
 
     anObjectOrCollection isCollection ifTrue:[
-        anObjectOrCollection size == 1 ifTrue:[
-            singleDropObject := anObjectOrCollection first.
-        ] ifFalse:[
-            Transcript showCR:'can only drop single objects'.
-            ^ self
-        ].
+	anObjectOrCollection size == 1 ifTrue:[
+	    singleDropObject := anObjectOrCollection first.
+	] ifFalse:[
+	    Transcript showCR:'can only drop single objects'.
+	    ^ self
+	].
     ] ifFalse:[
-        singleDropObject := anObjectOrCollection
+	singleDropObject := anObjectOrCollection
     ].
 
     singleDropObject isFileObject ifTrue:[
-        FileBrowser openOnFileNamed:(singleDropObject theObject pathName)
+	FileBrowser openOnFileNamed:(singleDropObject theObject pathName)
     ].
 
     "Modified: 6.4.1997 / 15:00:23 / cg"
@@ -3255,9 +3259,9 @@
 
      launcher := Transcript topView application.
      launcher 
-        addMenu:'misc' 
-        withItems:#('foo' 'bar')
-        actions:actionBlocks
+	addMenu:'misc' 
+	withItems:#('foo' 'bar')
+	actions:actionBlocks
     "
 
     "
@@ -3269,9 +3273,9 @@
                 
      launcher := Transcript topView application.
      launcher 
-        addMenu:'misc' 
-        withItems:#('start rdoit server' 'stop rdoit server')
-        actions:actionBlocks
+	addMenu:'misc' 
+	withItems:#('start rdoit server' 'stop rdoit server')
+	actions:actionBlocks
     "
 
     "Modified: 5.7.1996 / 11:45:19 / cg"
@@ -3288,8 +3292,8 @@
      launcher := Transcript topView application.
      demoMenu := launcher menuAt:#demos.
      demoMenu
-        addLabels:#('-' 'fooBar')
-        selectors:#(nil fooBar).
+	addLabels:#('-' 'fooBar')
+	selectors:#(nil fooBar).
      demoMenu actionAt:#fooBar put:[Transcript showCR:'fooBar']
     "
 
@@ -3313,9 +3317,9 @@
 
      launcher := Transcript topView application.
      launcher 
-        addMenu:'misc' 
-        withItems:#('foo' 'bar')
-        actions:actionBlocks.
+	addMenu:'misc' 
+	withItems:#('foo' 'bar')
+	actions:actionBlocks.
 
      Delay waitForSeconds:10.
 
@@ -3334,29 +3338,29 @@
     |sel s buttons|
 
     aComponent == transcript ifTrue:[
-        s := 'TRANSCRIPT_HELP'
+	s := 'TRANSCRIPT_HELP'
     ].
 
     aComponent == infoView ifTrue:[
-        s := 'INFOVIEW_HELP'
+	s := 'INFOVIEW_HELP'
     ].
 
     buttons := buttonPanel subViews.
     (buttons notNil and:[buttons includes:aComponent]) ifTrue:[
-        "kludge: look for its change selector"
-        sel := aComponent changeMessage.
-        sel == #startSystemBrowser ifTrue:[
-            s := 'SBROWSER_BUTTON_HELP'
-        ].
-        sel == #startFileBrowser ifTrue:[
-            s := 'FBROWSER_BUTTON_HELP'
-        ].
-        sel == #startChangesBrowser ifTrue:[
-            s := 'CBROWSER_BUTTON_HELP'
-        ].
+	"kludge: look for its change selector"
+	sel := aComponent changeMessage.
+	sel == #startSystemBrowser ifTrue:[
+	    s := 'SBROWSER_BUTTON_HELP'
+	].
+	sel == #startFileBrowser ifTrue:[
+	    s := 'FBROWSER_BUTTON_HELP'
+	].
+	sel == #startChangesBrowser ifTrue:[
+	    s := 'CBROWSER_BUTTON_HELP'
+	].
     ].
     s notNil ifTrue:[
-        ^ resources string:s
+	^ resources string:s
     ].
     ^ nil
 
@@ -3371,32 +3375,32 @@
     |project projectName projectDir packageName defNameSpace msg args|
 
     (Project isNil or:[(project := Project current) isNil]) ifTrue:[
-        projectName := '* none *'.
-        projectDir := '.'.
-        packageName := '* none *'.
+	projectName := '* none *'.
+	projectDir := '.'.
+	packageName := '* none *'.
     ] ifFalse:[
-        projectName := project name.
-        projectDir := project directory.
-        packageName := project packageName.
-        defNameSpace := project defaultNameSpace.
+	projectName := project name.
+	projectDir := project directory.
+	packageName := project packageName.
+	defNameSpace := project defaultNameSpace.
     ].
     defNameSpace isNil ifTrue:[
-        defNameSpace := Smalltalk.
+	defNameSpace := Smalltalk.
     ].
 
     defNameSpace == Smalltalk ifTrue:[
-        msg := 'project: ''%1''  fileOut to: ''%3''  package: ''%2'''.
-        args := Array 
-                    with:projectName
-                    with:packageName 
-                    with:(projectDir contractTo:30).
+	msg := 'project: ''%1''  fileOut to: ''%3''  package: ''%2'''.
+	args := Array 
+		    with:projectName
+		    with:packageName 
+		    with:(projectDir contractTo:30).
     ] ifFalse:[
-        msg := 'project: ''%1''  fileOut to: ''%3''  package: ''%2''  nameSpace: %4'.
-        args := Array 
-                        with:projectName
-                        with:packageName 
-                        with:(projectDir contractTo:30)
-                        with:defNameSpace name.
+	msg := 'project: ''%1''  fileOut to: ''%3''  package: ''%2''  nameSpace: %4'.
+	args := Array 
+			with:projectName
+			with:packageName 
+			with:(projectDir contractTo:30)
+			with:defNameSpace name.
     ].
         
     ^ resources string:msg withArgs:args
@@ -3423,9 +3427,9 @@
      be performed on the main screen."
 
     isMainLauncher ifFalse:[
-        (myMenu menuAt:#file) disableAll:#(snapshot snapshotAndExit objectModuleDialog exit).
-        (myMenu menuAt:#projects) disableAll.
-        (myMenu menuAt:#settings) disableAll.
+	(myMenu menuAt:#file) disableAll:#(snapshot snapshotAndExit objectModuleDialog exit).
+	(myMenu menuAt:#projects) disableAll.
+	(myMenu menuAt:#settings) disableAll.
     ].
 
     "Created: 5.7.1996 / 17:00:50 / cg"
@@ -3436,17 +3440,17 @@
     "setup the about- pulldown menu"
 
     myMenu at:#about 
-           putLabels:(resources array:#(
-                                        'about Smalltalk/X ...'
-                                        '-'
-                                        'licence conditions'
-                                       ))
-           selectors:#(
-                                        #about 
-                                        nil
-                                        #showLicenceConditions 
-                      )
-           receiver:self.
+	   putLabels:(resources array:#(
+					'about Smalltalk/X ...'
+					'-'
+					'licence conditions'
+				       ))
+	   selectors:#(
+					#about 
+					nil
+					#showLicenceConditions 
+		      )
+	   receiver:self.
 
     "Created: 8.1.1997 / 14:03:20 / cg"
     "Modified: 8.1.1997 / 14:04:19 / cg"
@@ -3456,39 +3460,39 @@
     "setup the classes- pulldown menu"
 
     myMenu at:#classes 
-           putLabels:(resources array:#(
-                                        'system browser'
-                                        'class browser ...'
-                                        'full class browser ...'
-                                        'class hierarchy browser ...'
-                                        'class tree'
-                                        '-'
-                                        'implementors ...'
-                                        'senders ...'
-                                        'resource ...'
-                                        '-'
-                                        'change browser'
-                                        ))
-           selectors:#(
-                                        #startSystemBrowser 
-                                        #startClassBrowser 
-                                        #startFullClassBrowser 
-                                        #startClassHierarchyBrowser 
-                                        #startClassTreeView 
-                                        nil
-                                        #browseImplementors 
-                                        #browseSenders 
-                                        #browseResources
-                                        nil
-                                        #startChangesBrowser 
-                      )
-           receiver:self.
+	   putLabels:(resources array:#(
+					'system browser'
+					'class browser ...'
+					'full class browser ...'
+					'class hierarchy browser ...'
+					'class tree'
+					'-'
+					'implementors ...'
+					'senders ...'
+					'resource ...'
+					'-'
+					'change browser'
+					))
+	   selectors:#(
+					#startSystemBrowser 
+					#startClassBrowser 
+					#startFullClassBrowser 
+					#startClassHierarchyBrowser 
+					#startClassTreeView 
+					nil
+					#browseImplementors 
+					#browseSenders 
+					#browseResources
+					nil
+					#startChangesBrowser 
+		      )
+	   receiver:self.
 
     JavaBrowser notNil ifTrue:[
-        (myMenu subMenuAt:#classes)
-            addLabels:(resources array:#('-' 'java browser'))
-            selectors:#(nil startJavaBrowser)
-            after:#startClassTreeView
+	(myMenu subMenuAt:#classes)
+	    addLabels:(resources array:#('-' 'java browser'))
+	    selectors:#(nil startJavaBrowser)
+	    after:#startClassTreeView
     ].
 
     "Created: 8.1.1997 / 14:05:44 / cg"
@@ -3503,23 +3507,23 @@
     |m|
 
     myMenu at:#demos 
-           putLabels:(resources array:#(
-                                        'goodies'
-                                        'games'
-                                        'geometric designs'
-                                        'simple animations'
-                                        '3D graphics'
-                                        'graphic editors'
-                                       ))
-           selectors:#(
-                                        goodies
-                                        games
-                                        geometricDesigns
-                                        simpleAnimations
-                                        #'3Dgraphics'
-                                        #graphicEditors
-                      )
-           receiver:self.
+	   putLabels:(resources array:#(
+					'goodies'
+					'games'
+					'geometric designs'
+					'simple animations'
+					'3D graphics'
+					'graphic editors'
+				       ))
+	   selectors:#(
+					goodies
+					games
+					geometricDesigns
+					simpleAnimations
+					#'3Dgraphics'
+					#graphicEditors
+		      )
+	   receiver:self.
 
     "
      only to show two different ways of defining a popUpMenu,
@@ -3528,136 +3532,136 @@
     m := myMenu menuAt:#demos.
     m subMenuAt:#games
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'Tetris'
-                                           'Tic Tac Toe'
-                                           'Tic Tac Toe (2 players)'
-                                         ))
-                selectors:#(
-                                           startTetris
-                                           startTicTacToe
-                                           startTicTacToe2
-                           )
-                receiver:self).
+		labels:(resources array:#(
+					   'Tetris'
+					   'Tic Tac Toe'
+					   'Tic Tac Toe (2 players)'
+					 ))
+		selectors:#(
+					   startTetris
+					   startTicTacToe
+					   startTicTacToe2
+			   )
+		receiver:self).
 
     "
      and labels:selector:args:receiver: here:
     "
     m subMenuAt:#geometricDesigns
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'Pen demo'
-                                           'Commander demo'
-                                           '-'     
-                                           'Fractal plants demo'
-                                           'Fractal patterns demo'
-                                           'more fractal patterns demo'
-                                         ))
-                selector:#openDemo:
-                args:#(
-                                           PenDemo
-                                           CommanderDemo
-                                           nil
-                                           FractalPlantsDemo
-                                           FractalPatternsDemo
-                                           ArmchairUniverseDemo
-                      )
-                receiver:self).
+		labels:(resources array:#(
+					   'Pen demo'
+					   'Commander demo'
+					   '-'     
+					   'Fractal plants demo'
+					   'Fractal patterns demo'
+					   'more fractal patterns demo'
+					 ))
+		selector:#openDemo:
+		args:#(
+					   PenDemo
+					   CommanderDemo
+					   nil
+					   FractalPlantsDemo
+					   FractalPatternsDemo
+					   ArmchairUniverseDemo
+		      )
+		receiver:self).
 
     m subMenuAt:#simpleAnimations 
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'Animation'
-                                           'Globe demo'
-                                         ))
-                selector:#openDemo:
-                args:#(
-                                           Animation
-                                           GlobeDemo
-                      )
-                receiver:self).
+		labels:(resources array:#(
+					   'Animation'
+					   'Globe demo'
+					 ))
+		selector:#openDemo:
+		args:#(
+					   Animation
+					   GlobeDemo
+		      )
+		receiver:self).
 
     m subMenuAt:#'3Dgraphics' 
       put:(PopUpMenu
-                labels:(resources 
-                            array:#(
-                                'plane'
-                                'tetra'
-                                'cube (wireframe)'
-                                'cube (solid)'
-                                'sphere (wireframe)'
-                                'doughnut (wireframe)'
-                                'planet'
-                                'teapot'
-                                'logo'
-                                'rubics cube'
-                                'x/y graph'
-                                '-'
-                                'cube (light)'
-                                'cube (light & texture)'
-                                'sphere (light)'
-                                'colored octahedron'
-                             ))
-                selector:#openDemo:
-                args:#(
-                                GLPlaneDemoView2
-                                GLTetraDemoView
-                                GLWireCubeDemoView
-                                GLCubeDemoView
-                                GLWireSphereDemoView
-                                GLDoughnutDemoView
-                                GLPlanetDemoView
-                                GLTeapotDemo
-                                Logo3DView1
-                                RubicsCubeView
-                                GLXYGraph
-                                nil
-                                GLCubeDemoView2
-                                GLBrickCubeDemoView
-                                GLSphereDemoView2
-                                GLOctaHedronDemoView
-                      )
-                receiver:self).
+		labels:(resources 
+			    array:#(
+				'plane'
+				'tetra'
+				'cube (wireframe)'
+				'cube (solid)'
+				'sphere (wireframe)'
+				'doughnut (wireframe)'
+				'planet'
+				'teapot'
+				'logo'
+				'rubics cube'
+				'x/y graph'
+				'-'
+				'cube (light)'
+				'cube (light & texture)'
+				'sphere (light)'
+				'colored octahedron'
+			     ))
+		selector:#openDemo:
+		args:#(
+				GLPlaneDemoView2
+				GLTetraDemoView
+				GLWireCubeDemoView
+				GLCubeDemoView
+				GLWireSphereDemoView
+				GLDoughnutDemoView
+				GLPlanetDemoView
+				GLTeapotDemo
+				Logo3DView1
+				RubicsCubeView
+				GLXYGraph
+				nil
+				GLCubeDemoView2
+				GLBrickCubeDemoView
+				GLSphereDemoView2
+				GLOctaHedronDemoView
+		      )
+		receiver:self).
 
     m subMenuAt:#graphicEditors 
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'DrawTool'
-                                           'LogicTool'
-                                           'Paint Demo'
-                                         ))
-                selector:#openDemo:
-                args:#(
-                                           DrawTool
-                                           LogicTool
-                                           ColorDrawDemo3
-                      )
-                receiver:self).
+		labels:(resources array:#(
+					   'DrawTool'
+					   'LogicTool'
+					   'Paint Demo'
+					 ))
+		selector:#openDemo:
+		args:#(
+					   DrawTool
+					   LogicTool
+					   ColorDrawDemo3
+		      )
+		receiver:self).
 
     m subMenuAt:#goodies 
       put:(PopUpMenu
-                labels:(resources array:#(
-                                        'clock'
-                                        'digital clock'
-                                        'calendar'
-                                        'calculator'
-                                        '-'
-                                        'mail tool'
-                                        'news tool'
-                                        'ftp tool'
-                                        ))
-                selector:#openDemo:
-                args:#(
-                                        Clock 
-                                        DigitalClockView 
-                                        Calendar
-                                        CalculatorView
-                                        nil
-                                        MailView 
-                                        NewsView
-                                        FTPTool
-                      )
-                receiver:self).
+		labels:(resources array:#(
+					'clock'
+					'digital clock'
+					'calendar'
+					'calculator'
+					'-'
+					'mail tool'
+					'news tool'
+					'ftp tool'
+					))
+		selector:#openDemo:
+		args:#(
+					Clock 
+					DigitalClockView 
+					Calendar
+					CalculatorView
+					nil
+					MailView 
+					NewsView
+					FTPTool
+		      )
+		receiver:self).
 
     "Modified: 28.3.1997 / 22:45:12 / cg"
 !
@@ -3668,28 +3672,28 @@
     |l s|
 
     l := #(
-                'file browser'
-                '-'
-                'modules ...'
-                '-'
-                'snapshot ...'
-                'snapshot & exit ...'
-                'exit smalltalk ...'
-         ).
+		'file browser'
+		'-'
+		'modules ...'
+		'-'
+		'snapshot ...'
+		'snapshot & exit ...'
+		'exit smalltalk ...'
+	 ).
     s := #(
-                #startFileBrowser
-                nil
-                #objectModuleDialog 
-                nil
-                #snapshot
-                #snapshotAndExit
-                #exit
-         ).
+		#startFileBrowser
+		nil
+		#objectModuleDialog 
+		nil
+		#snapshot
+		#snapshotAndExit
+		#exit
+	 ).
 
     myMenu at:#file
-           putLabels:(resources array:l)
-           selectors:s
-           receiver:self.
+	   putLabels:(resources array:l)
+	   selectors:s
+	   receiver:self.
 
     "Created: 8.1.1997 / 14:04:15 / cg"
 !
@@ -3700,57 +3704,57 @@
     |l s|
 
     ActiveHelp notNil ifTrue:[
-        l := #(
-                'what''s new'
-                'index'
-                '-'
-                'ST/X online documentation'
-                'class documentation'
-                '-'
-                'print documentation ...'
-                '-'
-                'active help \c'
-              ).
-        s := #(
-                #startWhatsNewDocumentation
-                #startDocumentationIndex
-                nil
-                #startDocumentationTool
-                #startClassDocumentation
-                nil
-                #showBookPrintDocument
-                nil
-                #toggleActiveHelp:
-              )
+	l := #(
+		'what''s new'
+		'index'
+		'-'
+		'ST/X online documentation'
+		'class documentation'
+		'-'
+		'print documentation ...'
+		'-'
+		'active help \c'
+	      ).
+	s := #(
+		#startWhatsNewDocumentation
+		#startDocumentationIndex
+		nil
+		#startDocumentationTool
+		#startClassDocumentation
+		nil
+		#showBookPrintDocument
+		nil
+		#toggleActiveHelp:
+	      )
     ] ifFalse:[
-        l := #(
-                'what''s new'
-                'index'
-                '-'
-                'ST/X online documentation'
-                'class documentation'
-                '-'
-                'print documentation ...'
-              ).
-        s := #(
-                #startWhatsNewDocumentation
-                #startDocumentationIndex
-                nil
-                #startDocumentationTool
-                #startClassDocumentation
-                nil
-                #showBookPrintDocument
-              )
+	l := #(
+		'what''s new'
+		'index'
+		'-'
+		'ST/X online documentation'
+		'class documentation'
+		'-'
+		'print documentation ...'
+	      ).
+	s := #(
+		#startWhatsNewDocumentation
+		#startDocumentationIndex
+		nil
+		#startDocumentationTool
+		#startClassDocumentation
+		nil
+		#showBookPrintDocument
+	      )
     ].
 
     myMenu at:#help 
-           putLabels:(resources array:l)
-           selectors:s
-           receiver:self.
+	   putLabels:(resources array:l)
+	   selectors:s
+	   receiver:self.
 
     (ActiveHelp notNil
     and:[ActiveHelp isActive]) ifTrue:[
-        (myMenu menuAt:#help) checkToggleAt:#toggleActiveHelp: put:true
+	(myMenu menuAt:#help) checkToggleAt:#toggleActiveHelp: put:true
     ].
 
     "Created: 8.1.1997 / 14:08:09 / cg"
@@ -3764,33 +3768,33 @@
     |l s icon|
 
     myMenu labels:(resources array:#(
-                                     about
-                                     file
-                                     classes
-                                     tools
-                                     projects
-                                     settings
-                                     demos
-                                     help)).
+				     about
+				     file
+				     classes
+				     tools
+				     projects
+				     settings
+				     demos
+				     help)).
     "
      if there is a bitmap, change 'about' to the ST/X icon
     "
     icon := self class smallAboutIcon.
     icon notNil ifTrue:[
 "/        icon := icon on:device.
-        myMenu labels at:1 put:icon.
-        myMenu height:(myMenu height max:(icon height + (View viewSpacing * 2)))
+	myMenu labels at:1 put:icon.
+	myMenu height:(myMenu height max:(icon height + (View viewSpacing * 2)))
     ].
 
     myMenu selectors:#(
-                                     #about
-                                     #file
-                                     #classes 
-                                     #tools 
-                                     #projects 
-                                     #settings
-                                     #demos
-                                     #help).
+				     #about
+				     #file
+				     #classes 
+				     #tools 
+				     #projects 
+				     #settings
+				     #demos
+				     #help).
 
     "Created: 8.1.1997 / 13:58:50 / cg"
     "Modified: 13.1.1997 / 23:33:09 / cg"
@@ -3806,36 +3810,36 @@
     mainItems := myMenu selectors.
 
     (mainItems includes:#about) ifTrue:[
-        "/ if not redefined without an about-menu ...
-        self setupAboutMenu
+	"/ if not redefined without an about-menu ...
+	self setupAboutMenu
     ].
     (mainItems includes:#file) ifTrue:[
-        "/ if not redefined without a file-menu ...
-        self setupFileMenu
+	"/ if not redefined without a file-menu ...
+	self setupFileMenu
     ].
     (mainItems includes:#classes) ifTrue:[
-        "/ if not redefined without a classes-menu ...
-        self setupClassesMenu
+	"/ if not redefined without a classes-menu ...
+	self setupClassesMenu
     ].
     (mainItems includes:#projects) ifTrue:[
-        "/ if not redefined without a projects-menu ...
-        self setupProjectsMenu
+	"/ if not redefined without a projects-menu ...
+	self setupProjectsMenu
     ].
     (mainItems includes:#settings) ifTrue:[
-        "/ if not redefined without a settings-menu ...
-        self setupSettingsMenu
+	"/ if not redefined without a settings-menu ...
+	self setupSettingsMenu
     ].
     (mainItems includes:#tools) ifTrue:[
-        "/ if not redefined without a tools-menu ...
-        self setupToolsMenu
+	"/ if not redefined without a tools-menu ...
+	self setupToolsMenu
     ].
     (mainItems includes:#demos) ifTrue:[
-        "/ if not redefined without a demos-menu ...
-        self setupDemoMenu
+	"/ if not redefined without a demos-menu ...
+	self setupDemoMenu
     ].
     (mainItems includes:#help) ifTrue:[
-        "/ if not redefined without a help-menu ...
-        self setupHelpMenu
+	"/ if not redefined without a help-menu ...
+	self setupHelpMenu
     ].
 
     self disableDangerousMenuItemsInRemoteLauncher
@@ -3847,17 +3851,17 @@
     "setup the projects- pulldown menu"
 
     myMenu at:#projects 
-           putLabels:(resources array:#(
-                                        'new project'
-                                        '-'
-                                        'select project ...'
-                                        ))
-           selectors:#(
-                                        #newProject 
-                                        nil
-                                        #selectProject 
-                      )
-           receiver:self.
+	   putLabels:(resources array:#(
+					'new project'
+					'-'
+					'select project ...'
+					))
+	   selectors:#(
+					#newProject 
+					nil
+					#selectProject 
+		      )
+	   receiver:self.
 
     "Created: 8.1.1997 / 14:06:18 / cg"
 !
@@ -3866,39 +3870,39 @@
     "setup the settings- pulldown menu"
 
     myMenu at:#settings 
-           putLabels:(resources array:#(
-                                        'language ...'
-                                        'show keyboard mappings ...'
-                                        'view style ...'
-                                        'fonts ...'
-                                        'printer ...'
-                                        'messages ...'
-                                        'compilation ...'
-                                        'source & debugger ...'
-                                        'object memory ...'
-                                        'screen ...'
-                                        'misc ...'
-                                        '='
-                                        'save settings ...'
-                                        'restore settings ...'
-                                        ))
-           selectors:#(
-                                        #languageSetting 
-                                        #keyboardSetting 
-                                        #viewStyleSetting 
-                                        #fontSettings 
-                                        #printerSettings 
-                                        #messageSettings 
-                                        #compilerSettings 
-                                        #sourceAndDebuggerSettings 
-                                        #memorySettings 
-                                        #displaySettings 
-                                        #miscSettings
-                                        nil
-                                        #saveSettings 
-                                        #restoreSettings 
-                      )
-           receiver:self.
+	   putLabels:(resources array:#(
+					'language ...'
+					'show keyboard mappings ...'
+					'view style ...'
+					'fonts ...'
+					'printer ...'
+					'messages ...'
+					'compilation ...'
+					'source & debugger ...'
+					'object memory ...'
+					'screen ...'
+					'misc ...'
+					'='
+					'save settings ...'
+					'restore settings ...'
+					))
+	   selectors:#(
+					#languageSetting 
+					#keyboardSetting 
+					#viewStyleSetting 
+					#fontSettings 
+					#printerSettings 
+					#messageSettings 
+					#compilerSettings 
+					#sourceAndDebuggerSettings 
+					#memorySettings 
+					#displaySettings 
+					#miscSettings
+					nil
+					#saveSettings 
+					#restoreSettings 
+		      )
+	   receiver:self.
 
     "Created: 8.1.1997 / 14:07:00 / cg"
     "Modified: 17.1.1997 / 17:40:00 / cg"
@@ -3912,119 +3916,119 @@
     |m|
 
     myMenu at:#tools 
-           putLabels:(resources array:#(
-                                        'workspace'
-                                        '-'
-                                        'monitors'
-                                        '-'
-                                        'views'
-                                        '-'
-                                        'hardcopy'
-                                        '-'
-                                        'misc'
-                                        ))
-           selectors:#(
-                                        #startWorkspace 
-                                        nil
-                                        #monitors
-                                        nil
-                                        #views
-                                        nil
-                                        #hardcopy 
-                                        nil
-                                        #misc 
-                      )
-           receiver:self.
+	   putLabels:(resources array:#(
+					'workspace'
+					'-'
+					'monitors'
+					'-'
+					'views'
+					'-'
+					'hardcopy'
+					'-'
+					'misc'
+					))
+	   selectors:#(
+					#startWorkspace 
+					nil
+					#monitors
+					nil
+					#views
+					nil
+					#hardcopy 
+					nil
+					#misc 
+		      )
+	   receiver:self.
 
 
     m := myMenu menuAt:#tools.
     m subMenuAt:#monitors 
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'process'
-                                           'semaphores'
-                                           'memory'
-                                           'irq latency'
-                                           'event view'
-                                           'event trace'
-                                           '-'
-                                           'memory usage'
-                                         ))
-                selectors:#(
-                                        #startProcessMonitor
-                                        #startSemaphoreMonitor 
-                                        #startMemoryMonitor 
-                                        #startLatencyMonitor 
-                                        #startEventMonitor 
-                                        #startStopEventTrace
-                                        nil
-                                        #startMemoryUsageView 
-                           )
-                receiver:self).
+		labels:(resources array:#(
+					   'process'
+					   'semaphores'
+					   'memory'
+					   'irq latency'
+					   'event view'
+					   'event trace'
+					   '-'
+					   'memory usage'
+					 ))
+		selectors:#(
+					#startProcessMonitor
+					#startSemaphoreMonitor 
+					#startMemoryMonitor 
+					#startLatencyMonitor 
+					#startEventMonitor 
+					#startStopEventTrace
+					nil
+					#startMemoryUsageView 
+			   )
+		receiver:self).
 
     m subMenuAt:#views 
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'iconify all'
-                                           'de-iconify all'
-                                           '-'
-                                           'find & raise ...'
-                                           '-'
-                                           'view tree (all views)'
-                                           'view tree'
-                                           '-'
-                                           'select & inspect view'
-                                           '-'
-                                           'select & destroy view'
-                                           'find & destroy ...'
-                                         ))
-                selectors:#(
-                                        #iconifyAllWindows
-                                        #deIconifyAllWindows
-                                        nil
-                                        #findAndRaiseWindow 
-                                        nil
-                                        #startFullWindowTreeView 
-                                        #startWindowTreeView 
-                                        nil
-                                        #viewInspect 
-                                        nil
-                                        #viewDestroy 
-                                        #findAndDestroyWindow 
-                           )
-                receiver:self).
+		labels:(resources array:#(
+					   'iconify all'
+					   'de-iconify all'
+					   '-'
+					   'find & raise ...'
+					   '-'
+					   'view tree (all views)'
+					   'view tree'
+					   '-'
+					   'select & inspect view'
+					   '-'
+					   'select & destroy view'
+					   'find & destroy ...'
+					 ))
+		selectors:#(
+					#iconifyAllWindows
+					#deIconifyAllWindows
+					nil
+					#findAndRaiseWindow 
+					nil
+					#startFullWindowTreeView 
+					#startWindowTreeView 
+					nil
+					#viewInspect 
+					nil
+					#viewDestroy 
+					#findAndDestroyWindow 
+			   )
+		receiver:self).
 
     m subMenuAt:#misc 
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'garbage collect'
-                                           'garbage collect & compress'
-                                           '-'
-                                           'find all break/trace points'
-                                           'remove all break/trace points'
-                                         ))
-                selectors:#(
-                                        #garbageCollect
-                                        #compressingGarbageCollect
-                                        nil
-                                        #browseAllBreakAndTracePoints                                        
-                                        #removeAllBreakAndTracePoints                                        
-                           )
-                receiver:self).
+		labels:(resources array:#(
+					   'garbage collect'
+					   'garbage collect & compress'
+					   '-'
+					   'find all break/trace points'
+					   'remove all break/trace points'
+					 ))
+		selectors:#(
+					#garbageCollect
+					#compressingGarbageCollect
+					nil
+					#browseAllBreakAndTracePoints                                        
+					#removeAllBreakAndTracePoints                                        
+			   )
+		receiver:self).
 
     m subMenuAt:#hardcopy 
       put:(PopUpMenu
-                labels:(resources array:#(
-                                           'screen'
-                                           'area'
-                                           'view'
-                                         ))
-                selectors:#(
-                                        #fullScreenHardcopy
-                                        #screenHardcopy
-                                        #viewHardcopy
-                           )
-                receiver:self).
+		labels:(resources array:#(
+					   'screen'
+					   'area'
+					   'view'
+					 ))
+		selectors:#(
+					#fullScreenHardcopy
+					#screenHardcopy
+					#viewHardcopy
+			   )
+		receiver:self).
 
     "Modified: 1.3.1997 / 20:25:30 / cg"
 ! !
@@ -4043,11 +4047,11 @@
      nil selectors are taken as separators (see setupButtonPanel)"
 
     ^ #(
-        #(startSystemBrowser 'SBrowser32x32.xbm')
-        #(startFileBrowser   'FBrowser32x32.xbm')
+	#(startSystemBrowser 'SBrowser32x32.xbm')
+	#(startFileBrowser   'FBrowser32x32.xbm')
 "/        #(startWorkspace      'Workspace32x32.xbm')
-        #(nil nil)
-        #(startChangesBrowser 'CBrowser32x32.xbm')
+	#(nil nil)
+	#(startChangesBrowser 'CBrowser32x32.xbm')
 "/        #(nil nil)
 "/        #(nil nil)
 "/        #(startDocumentationTool 'book11.ico')
@@ -4067,7 +4071,7 @@
 
 closeRequest
     (self confirm:(resources string:'really close %1 ?' with:self class name)) ifTrue:[
-        super closeRequest
+	super closeRequest
     ]
 !
 
@@ -4087,13 +4091,13 @@
     "/ I am a slave launcher with limited functionality.
 
     Transcript notNil ifTrue:[
-        Transcript ~~ Stderr ifTrue:[
-            isMainLauncher := (Transcript graphicsDevice == device).
-        ] ifFalse:[
-            isMainLauncher := true
-        ]
+	Transcript ~~ Stderr ifTrue:[
+	    isMainLauncher := (Transcript graphicsDevice == device).
+	] ifFalse:[
+	    isMainLauncher := true
+	]
     ] ifFalse:[
-        isMainLauncher := true
+	isMainLauncher := true
     ].
 
     top := StandardSystemView onDevice:device.
@@ -4102,17 +4106,17 @@
 
     icn := self class aboutIcon.
     icn notNil ifTrue:[
-        icn := icn magnifiedTo:(sz := device preferredIconSize).
+	icn := icn magnifiedTo:(sz := device preferredIconSize).
     ].
 
     (device supportsDeepIcons not
     and:[device supportsIconViews
     and:[device depth > 1]]) ifTrue:[    
-        w := View extent:sz. 
-        w viewBackground:icn.
-        top iconView:w
+	w := View extent:sz. 
+	w viewBackground:icn.
+	top iconView:w
     ] ifFalse:[
-        top icon:icn.
+	top icon:icn.
     ].
 
 "/    device supportsDeepIcons ifTrue:[
@@ -4146,7 +4150,7 @@
     top openWithPriority:(Processor userSchedulingPriority + 1).
 
     OpenLaunchers isNil ifTrue:[
-        OpenLaunchers := OrderedCollection new.
+	OpenLaunchers := OrderedCollection new.
     ].
     OpenLaunchers add:self.
 
@@ -4155,8 +4159,8 @@
 
 release
     infoProcess notNil ifTrue:[
-        infoProcess terminate.
-        infoProcess := nil.
+	infoProcess terminate.
+	infoProcess := nil.
     ].
     OpenLaunchers removeIdentical:self ifAbsent:nil.
     super release
@@ -4213,50 +4217,50 @@
     "/   #( nil )
     "/
     self buttonPanelSpec do:[:entry |
-        |sel b sep img iconSpec v|
-
-        sel := entry at:1.
-        sel isNil ifTrue:[
-            sep := View in:buttonPanel.
-            sep extent:32@1; borderWidth:0.
-        ] ifFalse:[
-            iconSpec := entry at:2.
-            iconSpec isArray ifTrue:[
-                img := (Smalltalk classNamed:(iconSpec at:1)) perform:(iconSpec at:2).
-            ] ifFalse:[
-                img := Image fromFile:iconSpec.
-            ].
-            (img notNil and:[buttonSize notNil]) ifTrue:[
-                img extent ~= buttonSize ifTrue:[
-                    img := img magnifiedTo:buttonSize       
-                ]
-            ].
-
-            b := Button new.
-            b form:img.
-            b model:self; changeMessage:sel.
-
-            b styleSheet name = 'win95' ifTrue:[
-                v := View in:buttonPanel.
-                v addSubView:b.
-                v level:-1.
-                b passiveLevel:1; activeLevel:-1.
-                v extent:(b preferredExtent 
-                          + b borderWidth + b borderWidth 
-                          + b margin + b margin 
-                          + v margin + v margin).
-                v preferredExtent:v extent.
-                b origin:(v margin asPoint).
-                b enteredBackgroundColor:(Color grey:80).
-            ] ifFalse:[
-                buttonPanel addSubView:b.
-            ].
-        ]
+	|sel b sep img iconSpec v|
+
+	sel := entry at:1.
+	sel isNil ifTrue:[
+	    sep := View in:buttonPanel.
+	    sep extent:32@1; borderWidth:0.
+	] ifFalse:[
+	    iconSpec := entry at:2.
+	    iconSpec isArray ifTrue:[
+		img := (Smalltalk classNamed:(iconSpec at:1)) perform:(iconSpec at:2).
+	    ] ifFalse:[
+		img := Image fromFile:iconSpec.
+	    ].
+	    (img notNil and:[buttonSize notNil]) ifTrue:[
+		img extent ~= buttonSize ifTrue:[
+		    img := img magnifiedTo:buttonSize       
+		]
+	    ].
+
+	    b := Button new.
+	    b form:img.
+	    b model:self; changeMessage:sel.
+
+	    b styleSheet name = 'win95' ifTrue:[
+		v := View in:buttonPanel.
+		v addSubView:b.
+		v level:-1.
+		b passiveLevel:1; activeLevel:-1.
+		v extent:(b preferredExtent 
+			  + b borderWidth + b borderWidth 
+			  + b margin + b margin 
+			  + v margin + v margin).
+		v preferredExtent:v extent.
+		b origin:(v margin asPoint).
+		b enteredBackgroundColor:(Color grey:80).
+	    ] ifFalse:[
+		buttonPanel addSubView:b.
+	    ].
+	]
     ].
 
     mh := myMenu height.
     buttonPanel origin:0.0 @ (mh + spc)
-                corner:(1.0 @ (mh + spc + buttonPanel preferredExtent y)).
+		corner:(1.0 @ (mh + spc + buttonPanel preferredExtent y)).
 
     buttonPanel leftInset:spc; rightInset:spc.
 
@@ -4275,19 +4279,19 @@
     transcript superView bottomInset:(infoView height + spc).
 
     infoView is3D ifTrue:[
-        halfSpc := spc // 2.
+	halfSpc := spc // 2.
     ] ifFalse:[
-        halfSpc := 0
+	halfSpc := 0
     ].
     infoView topInset:(infoView height negated - spc + transcript borderWidth);
-             bottomInset:halfSpc;
-             leftInset:halfSpc; 
-             rightInset:halfSpc.
+	     bottomInset:halfSpc;
+	     leftInset:halfSpc; 
+	     rightInset:halfSpc.
     infoView origin:0.0 @ 1.0 corner:1.0 @ 1.0.
     infoView model:self; aspect:#info; labelMessage:#info.
 
     Project notNil ifTrue:[
-        Project addDependent:self.
+	Project addDependent:self.
     ]
 
     "
@@ -4331,38 +4335,38 @@
     "/ if so, do not close the real launcher.
 
     (Transcript notNil and:[Transcript ~~ Stderr]) ifTrue:[
-        isMainLauncher ifTrue:[
-            launcher := Transcript topView application
-        ] ifFalse:[
-            launcher := self class current.
-        ].
-        launcher notNil ifTrue:[
-            launcher window graphicsDevice == device ifTrue:[
-                OpenLaunchers removeIdentical:launcher ifAbsent:nil.
-                launcher window destroy.
-            ]
-        ]
+	isMainLauncher ifTrue:[
+	    launcher := Transcript topView application
+	] ifFalse:[
+	    launcher := self class current.
+	].
+	launcher notNil ifTrue:[
+	    launcher window graphicsDevice == device ifTrue:[
+		OpenLaunchers removeIdentical:launcher ifAbsent:nil.
+		launcher window destroy.
+	    ]
+	]
     ].
 
     v := HVScrollableView 
-                for:TextCollector
-                miniScrollerH:true 
-                miniScrollerV:false 
-                in:aView.
+		for:TextCollector
+		miniScrollerH:true 
+		miniScrollerV:false 
+		in:aView.
 
     v origin:(0.0 @ (buttonPanel corner y + View viewSpacing)) 
       corner:(1.0 @ 1.0).
     transcript := v scrolledView.
 
     isMainLauncher ifTrue:[
-        transcript beTranscript.
+	transcript beTranscript.
     ] ifFalse:[
-        transcript showCR:'**************** Notice ***********************'.
-        transcript showCR:'**       this is NOT the Transcript          **'.
-        transcript showCR:'** The real Transcript is on the main screen **'.
-        transcript showCR:'**                                           **'.
-        transcript showCR:'** Menus affecting common state are disabled **'.
-        transcript showCR:'***********************************************'.
+	transcript showCR:'**************** Notice ***********************'.
+	transcript showCR:'**       this is NOT the Transcript          **'.
+	transcript showCR:'** The real Transcript is on the main screen **'.
+	transcript showCR:'**                                           **'.
+	transcript showCR:'** Menus affecting common state are disabled **'.
+	transcript showCR:'***********************************************'.
     ]
 
     "Modified: 1.2.1997 / 12:08:01 / cg"
@@ -4386,8 +4390,8 @@
 
     tFont := transcript font.
     topView extent:(((tFont widthOf:'3')*60) max:myMenu preferredExtent x)
-                    @ 
-                    ((tFont height) * 20).
+		    @ 
+		    ((tFont height) * 20).
 
     "
      Launcher open
@@ -4406,43 +4410,43 @@
 
     knownTopViews := IdentitySet new.
     Screen allScreens do:[:aScreen |
-        aScreen knownViews do:[:aView |
-            aView notNil ifTrue:[
-                knownTopViews add:aView topView
-            ]
-        ]
+	aScreen knownViews do:[:aView |
+	    aView notNil ifTrue:[
+		knownTopViews add:aView topView
+	    ]
+	]
     ].
 
     knownTopViews := knownTopViews select:[:aView |
-                        |wg|
-
-                        (aView isKindOf:DebugView) ifTrue:[
-                            "/ although modal, show it.
-                            aView realized
-                        ] ifFalse:[
-                            wg := aView windowGroup.
-                            (wg notNil and:[wg isModal not]).
-                        ]
-                     ].
+			|wg|
+
+			(aView isKindOf:DebugView) ifTrue:[
+			    "/ although modal, show it.
+			    aView realized
+			] ifFalse:[
+			    wg := aView windowGroup.
+			    (wg notNil and:[wg isModal not]).
+			]
+		     ].
 
     knownTopViews := knownTopViews asOrderedCollection.
     knownTopViews sort:[:v1 :v2 | |l1 l2|
-                                l1 := v1 label ? 'aView'.
-                                l2 := v2 label ? 'aView'.
-                                l1 < l2
-                       ].
+				l1 := v1 label ? 'aView'.
+				l2 := v2 label ? 'aView'.
+				l1 < l2
+		       ].
     nameList := knownTopViews collect:[:v | 
-                                        |isDead wg p l|
-
-                                        l := v label ? 'aView'.
-                                        ((wg := v windowGroup) notNil
-                                        and:[(p := wg process) notNil
-                                        and:[p state ~~ #dead]]) ifTrue:[
-                                            l  
-                                        ] ifFalse:[
-                                            l , ' (dead ?)'
-                                        ]
-                                      ].
+					|isDead wg p l|
+
+					l := v label ? 'aView'.
+					((wg := v windowGroup) notNil
+					and:[(p := wg process) notNil
+					and:[p state ~~ #dead]]) ifTrue:[
+					    l  
+					] ifFalse:[
+					    l , ' (dead ?)'
+					]
+				      ].
 
     box := ListSelectionBox new.
     box noEnterField.
@@ -4450,11 +4454,11 @@
     box label:(resources string:'view selection').
     box title:(resources string:'select a view to raise deiconified:') withCRs.
     box action:[:selection |
-        |v|
-
-        v := knownTopViews at:box selectionIndex.
-        box destroy.
-        ^ v
+	|v|
+
+	v := knownTopViews at:box selectionIndex.
+	box destroy.
+	^ v
     ].
     box extent:400@300.
     box showAtPointer.
@@ -4473,8 +4477,8 @@
      models labels allOfThem filter|
 
     encodingMatch notNil ifTrue:[
-        filter := [:f | f encoding notNil 
-                        and:[encodingMatch match:f encoding]].
+	filter := [:f | f encoding notNil 
+			and:[encodingMatch match:f encoding]].
     ].
         
     models := OrderedCollection new.
@@ -4493,85 +4497,85 @@
     models
     with:(resources array:#('all' 'labels' 'buttons' 'lists' 'menus' 'edit text'))
     do:[:model :title |
-        |y2 lbl f i|
-
-        f := model value.
-
-        (box addTextLabel:title) adjust:#left.
-
-        y := box yPosition.
-        b := box addComponent:(Button label:(resources string:'change ...')) tabable:true.
-        b relativeExtent:nil; extent:(b preferredExtent).
-        y2 := box yPosition.
-        box yPosition:y.
-        i := box leftIndent.
-        box leftIndent:(b widthIncludingBorder + View viewSpacing).
-        (lbl := box addTextLabel:'')
-            adjust:#left;
-            font:(model value);
-            labelChannel:(BlockValue 
-                            with:[:v | |f|
-                                f := v value.
-                                f isNil ifTrue:[
-                                    ''
-                                ] ifFalse:[
-                                    f userFriendlyName
-                                ]
-                            ]
-                            argument:model).
-        labels add:lbl.
-
-        box leftIndent:i.
-        box yPosition:(box yPosition max:y2).
-        box addVerticalSpace.
-        box addHorizontalLine.
-        box addVerticalSpace.
-
-        b action:[
-            |f|
-
-            f := FontPanel 
-                fontFromUserInitial:(model value) 
-                              title:(resources string:'font for %1' with:title)
-                             filter:filter.
-            f notNil ifTrue:[
-                model == allOfThem ifTrue:[
-                    models do:[:m | m value:f].
-                    labels do:[:l | l font:f]
-                ] ifFalse:[
-                    model value:f.
-                    lbl font:f.
-                ].
-            ]
-        ].
-        model == allOfThem ifTrue:[
-            box addVerticalSpace
-        ]
+	|y2 lbl f i|
+
+	f := model value.
+
+	(box addTextLabel:title) adjust:#left.
+
+	y := box yPosition.
+	b := box addComponent:(Button label:(resources string:'change ...')) tabable:true.
+	b relativeExtent:nil; extent:(b preferredExtent).
+	y2 := box yPosition.
+	box yPosition:y.
+	i := box leftIndent.
+	box leftIndent:(b widthIncludingBorder + View viewSpacing).
+	(lbl := box addTextLabel:'')
+	    adjust:#left;
+	    font:(model value);
+	    labelChannel:(BlockValue 
+			    with:[:v | |f|
+				f := v value.
+				f isNil ifTrue:[
+				    ''
+				] ifFalse:[
+				    f userFriendlyName
+				]
+			    ]
+			    argument:model).
+	labels add:lbl.
+
+	box leftIndent:i.
+	box yPosition:(box yPosition max:y2).
+	box addVerticalSpace.
+	box addHorizontalLine.
+	box addVerticalSpace.
+
+	b action:[
+	    |f|
+
+	    f := FontPanel 
+		fontFromUserInitial:(model value) 
+			      title:(resources string:'font for %1' with:title)
+			     filter:filter.
+	    f notNil ifTrue:[
+		model == allOfThem ifTrue:[
+		    models do:[:m | m value:f].
+		    labels do:[:l | l font:f]
+		] ifFalse:[
+		    model value:f.
+		    lbl font:f.
+		].
+	    ]
+	].
+	model == allOfThem ifTrue:[
+	    box addVerticalSpace
+	]
     ].
 
     box addAbortButton; addOkButton.
     (box addButton:(Button label:(resources string:'defaults')) before:nil)
-        action:[
-            "/ fetch defaults
-            View updateAllStyleCaches.
-            labelDef value: Label defaultFont.
-            buttonDef value: Button defaultFont.
-            listDef value: SelectionInListView defaultFont.
-            menuDef value: MenuView defaultFont.
-            textDef value: TextView defaultFont.
-        ].
+	action:[
+	    "/ fetch defaults
+	    View updateAllStyleCaches.
+	    labelDef value: Label defaultFont.
+	    buttonDef value: Button defaultFont.
+	    listDef value: SelectionInListView defaultFont.
+	    menuDef value: MenuView defaultFont.
+	    textDef value: TextView defaultFont.
+	].
 
     box open.
     box accepted ifTrue:[
-        Label defaultFont:labelDef value.
-        Button defaultFont:buttonDef value.
-        Toggle defaultFont:buttonDef value.
-        SelectionInListView defaultFont:listDef value.
-        MenuView defaultFont:menuDef value.
-        PullDownMenu defaultFont:menuDef value.
-        TextView defaultFont:textDef value.
-        EditTextView defaultFont:textDef value.
-        CodeView defaultFont:textDef value.
+	Label defaultFont:labelDef value.
+	Button defaultFont:buttonDef value.
+	Toggle defaultFont:buttonDef value.
+	SelectionInListView defaultFont:listDef value.
+	MenuView defaultFont:menuDef value.
+	PullDownMenu defaultFont:menuDef value.
+	TextView defaultFont:textDef value.
+	EditTextView defaultFont:textDef value.
+	CodeView defaultFont:textDef value.
     ].
     box destroy.
     ^ box accepted
@@ -4598,20 +4602,20 @@
 
     cls := Smalltalk at:className asSymbol.
     cls isNil ifTrue:[
-        "/ look if its in the nameSpace
-        aNameSpace notNil ifTrue:[
-            cls := aNameSpace at:className asSymbol
-        ]
+	"/ look if its in the nameSpace
+	aNameSpace notNil ifTrue:[
+	    cls := aNameSpace at:className asSymbol
+	]
     ].
 
     cls isNil ifTrue:[
-        self warn:(resources string:'sorry, the %1 class is not available.' with:className).
+	self warn:(resources string:'sorry, the %1 class is not available.' with:className).
     ] ifFalse:[
-        Autoload autoloadFailedSignal handle:[:ex |
-            self warn:(resources string:'sorry, the %1 class seems to be not available.' with:className)
-        ] do:[
-            cls perform:aSelector
-        ]
+	Autoload autoloadFailedSignal handle:[:ex |
+	    self warn:(resources string:'sorry, the %1 class seems to be not available.' with:className)
+	] do:[
+	    cls perform:aSelector
+	]
     ]
 
     "Created: 8.1.1997 / 12:52:13 / cg"
@@ -4626,8 +4630,8 @@
     (Delay forSeconds:1) wait.
     v := Screen current viewFromUser.
     v isNil ifTrue:[
-        self warn:'sorry, this is not a smalltalk view'.
-        ^ nil
+	self warn:'sorry, this is not a smalltalk view'.
+	^ nil
     ].
     ^ v
 
@@ -4676,14 +4680,14 @@
     |fileName|
 
     fileName := Dialog
-                    requestFileName:(resources string:'save image in:')
-                    default:(defaultName , '.tiff')
-                    ok:(resources string:'save')
-                    abort:(resources string:'cancel')
-                    pattern:'*.tiff'.
+		    requestFileName:(resources string:'save image in:')
+		    default:(defaultName , '.tiff')
+		    ok:(resources string:'save')
+		    abort:(resources string:'cancel')
+		    pattern:'*.tiff'.
 
     fileName notNil ifTrue:[
-        anImage saveOn:fileName
+	anImage saveOn:fileName
     ].
 
     "Modified: 21.2.1996 / 13:09:28 / cg"
@@ -4708,5 +4712,5 @@
 !Launcher class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Launcher.st,v 1.266 1997-04-10 18:30:55 ah Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Launcher.st,v 1.267 1997-04-10 19:00:11 cg Exp $'
 ! !