extracted common stuff into a superclass
authorClaus Gittinger <cg@exept.de>
Thu, 23 Jan 1997 03:23:09 +0100
changeset 979 c1e318bee326
parent 978 007c5b8c75b5
child 980 f0f5b1c4007e
extracted common stuff into a superclass
ProcMonitor.st
ProcessMonitor.st
--- a/ProcMonitor.st	Thu Jan 23 02:41:39 1997 +0100
+++ b/ProcMonitor.st	Thu Jan 23 03:23:09 1997 +0100
@@ -10,10 +10,9 @@
  hereby transferred.
 "
 
-SimpleView subclass:#ProcessMonitor
-	instanceVariableNames:'listView processes listUpdateDelay updateDelay updateBlock
-		listUpdateBlock updateProcess hideDead runColor suspendedColor
-		waitColor cpuUsages showDetail'
+STXStatusMonitor subclass:#ProcessMonitor
+	instanceVariableNames:'processes hideDead runColor suspendedColor waitColor cpuUsages
+		showDetail'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Interface-Tools'
@@ -43,24 +42,34 @@
     doing.
 
     The information shown is:
-	id         - the numeric id of the process
-	name       - the name (if any) of the process
-		     (the name has no semantic meaning; it exists for the processMonitor only)
-	state      - what is it doing;
-			wait      - waiting on a semaphore
-			eventWait - waiting on a view-event semaphore
-			ioWait    - waiting on an io-semaphore
-			timeWait  - waiting for a time-semaphore
-			run       - run, but currently not scheduled
-			active    - really running (this info is useless, since at
-				    update time, its always the update process which is
-				    running)
-			suspended - suspended; not waiting on a semaphore
-			light     - not yet started (i.e. has no stack yet)
+        id         - the numeric id of the process
+        name       - the name (if any) of the process
+                     (the name has no semantic meaning; it exists for the processMonitor only)
+        state      - what is it doing;
+                        wait      - waiting on a semaphore
+                        eventWait - waiting on a view-event semaphore
+                        ioWait    - waiting on an io-semaphore
+                        timeWait  - waiting for a time-semaphore
+                        run       - run, but currently not scheduled
+                        active    - really running (this info is useless, since at
+                                    update time, its always the update process which is
+                                    running)
+                        suspended - suspended; not waiting on a semaphore
+                        light     - not yet started (i.e. has no stack yet)
         
-	prio       - the processes priority (1..30)
-	usedStack  - the current stack use
-	totalStack - the stack currently allocated (i.e. the maximum ever needed)
+        prio       - the processes priority (1..30)
+        usedStack  - the current stack use
+        totalStack - the stack currently allocated (i.e. the maximum ever needed)
+
+    [see also:]
+        Process ProcessorScheduler
+        WindowGroup
+
+    [author:]
+        Claus Gittinger
+
+    [start with:]
+        ProcessMonitor open
 "
 ! !
 
@@ -71,42 +80,15 @@
 
     i := Image fromFile:'ProcMon.xbm'.
     i notNil ifTrue:[^ i].
-    ^ StandardSystemView defaultIcon
+    ^ super defaultIcon
+
+    "Modified: 23.1.1997 / 02:52:31 / cg"
 !
 
 defaultLabel
     ^ 'Process Monitor'
 ! !
 
-!ProcessMonitor class methodsFor:'startup'!
-
-open
-    |top monitor|
-
-    top := StandardSystemView new.
-    monitor := self origin:0.0@0.0 corner:1.0@1.0 in:top.
-    top extent:monitor preferredExtent.
-    top label:self defaultLabel.
-    top icon:self defaultIcon.
-    top open
-
-    "
-     ProcessMonitor open
-    "
-! !
-
-!ProcessMonitor methodsFor:'destroying'!
-
-destroy
-    updateBlock notNil ifTrue:[
-	Processor removeTimedBlock:updateBlock.
-	Processor removeTimedBlock:listUpdateBlock.
-    ] ifFalse:[
-	updateProcess notNil ifTrue:[updateProcess terminate]
-    ].
-    super destroy
-! !
-
 !ProcessMonitor methodsFor:'drawing'!
 
 titleLine
@@ -338,144 +320,38 @@
 
     "Modified: 3.7.1996 / 13:56:01 / stefan"
     "Modified: 18.7.1996 / 20:19:59 / cg"
-!
-
-updateView
-    self updateList.
-    self updateStatus
-! !
-
-!ProcessMonitor methodsFor:'events'!
-
-canHandle:key
-    ^ key == #InspectIt
-!
-
-keyPress:key x:x y:y
-    <resource: #keyboard ( #InspectIt ) >
-
-    key == #InspectIt ifTrue:[
-	^ self inspectProcess.
-    ].
-    ^ super keyPress:key x:x y:y
 ! !
 
 !ProcessMonitor methodsFor:'initialization'!
 
 initialize
-    |v|
-
     super initialize.
 
     hideDead := true.
     showDetail := Smalltalk at:#SystemDebugging ifAbsent:false.
 
-    v := HVScrollableView for:SelectionInListView miniScrollerH:true in:self.
-    v origin:0.0@0.0 corner:1.0@1.0.
-
-"/    self extent:(font widthOf:self titleLine) + v scrollBar width @ 100.
-
-    listView := v scrolledView.
-    listView font:font.
-    listView menuHolder:self; menuPerformer:self; menuMessage:#processMenu. 
-
-    listView multipleSelectOk:true.
-    listView delegate:(KeyboardForwarder toView:self).
-    listView doubleClickAction:[:line | self debugProcess].
-
-    updateDelay := 0.5.
-    listUpdateDelay := 5.
-
-    "/ event mode is no longer used;
-    "/ this event support may vanish
-    Processor isPureEventDriven ifTrue:[
-        updateBlock := [self updateStatus].
-        listUpdateBlock := [self updateList].
-    ].
-
     device hasColors ifTrue:[
         runColor := Color green.
         suspendedColor := Color yellow.
         waitColor := Color red.
     ] ifFalse:[
         runColor := suspendedColor := waitColor := Color black
-    ]
+    ].
 
     "
      ProcessMonitor open
     "
 
-    "Modified: 13.4.1996 / 20:34:25 / cg"
-!
-
-mapped
-    super mapped.
-    self updateStatus.
-    self updateList.
+    "Modified: 23.1.1997 / 02:51:38 / cg"
 !
 
 realize
-    super realize.
     waitColor := waitColor on:device.
     runColor := runColor on:device.
     suspendedColor := suspendedColor on:device.
-
-    self startUpdateProcess.
-!
-
-reinitialize
-    updateProcess := nil.
-    super reinitialize.
-    self startUpdateProcess.
-
-    "Created: 22.12.1995 / 22:48:37 / cg"
-    "Modified: 22.12.1995 / 22:51:14 / cg"
-!
-
-startUpdateProcess
-    updateBlock notNil ifTrue:[
-        Processor addTimedBlock:updateBlock afterSeconds:updateDelay.
-        Processor addTimedBlock:listUpdateBlock afterSeconds:listUpdateDelay.
-    ] ifFalse:[
-        updateProcess := [
-            [
-                |id cnt|
+    super realize.
 
-                "
-                 every 20ms, we look which process runs;
-                 every half second, the status is updated.
-                 every 5 seconds, the list of processes is
-                 built up again
-                "
-                [true] whileTrue:[
-                    1 to:9 do:[:i |
-"/                        cpuUsages := IdentityDictionary new.
-"/                        1 to:25 do:[:i |
-"/                            (Delay forSeconds:0.02) wait.
-"/                            id := Processor interruptedProcess id.
-"/                            cnt := cpuUsages at:id ifAbsent:[0].
-"/                            cpuUsages at:id put:cnt + 1.
-"/                        ].
-                        Delay waitForSeconds:0.5.
-                        self updateStatus.
-                    ].
-                    Delay waitForSeconds:0.5.
-                    self updateList.
-                ]
-            ] valueOnUnwindDo:[
-                updateProcess := nil
-            ]
-        ]  forkAt:(Processor userSchedulingPriority + 1).
-        updateProcess name:'monitor [' , 
-                           Processor activeProcess id printString ,
-                           '] update'.
-        "
-         raise my own priority
-        "
-        Processor activeProcess priority:(Processor userSchedulingPriority + 2)
-    ].
-
-    "Modified: 12.6.1996 / 19:53:13 / cg"
+    "Modified: 23.1.1997 / 02:30:37 / cg"
 ! !
 
 !ProcessMonitor methodsFor:'menu actions'!
@@ -496,19 +372,20 @@
     ]
 !
 
-detail
-    showDetail := showDetail not.
-    self updateView
+hideDead:aBoolean
+    "turn on/off hiding of dead (already terminated) processes"
+
+    hideDead := aBoolean
+
+    "Modified: 23.1.1997 / 02:34:01 / cg"
 !
 
-hideDead:aBoolean
-    hideDead := aBoolean
-!
-
-inspectProcess
+inspectSelection
     "open an inspector on the selected process"
 
     self selectedProcessesSend:#inspect
+
+    "Created: 23.1.1997 / 02:27:33 / cg"
 !
 
 lowerPrio
@@ -519,89 +396,6 @@
     ]
 !
 
-processMenu
-    |labels selectors m sel allRestartable|
-
-    device ctrlDown ifTrue:[
-        labels := resources array:#(
-                        '\c detail'
-                      ).
-        selectors := #(
-                        detail
-                      ).
-    ] ifFalse:[
-        labels := resources array:#(
-                             'inspect' 
-                             'debug'  
-                             '-'  
-                             'resume'  
-                             'suspend'  
-                             'stop'  
-                             'abort'
-                             'terminate'
-                             'terminate group'
-                             'restart'
-                             '-'  
-                             'raise prio'  
-                             'lower prio'  
-                            ).
-        selectors := #(
-                             inspectProcess  
-                             debugProcess  
-                             nil  
-                             resumeProcess  
-                             suspendProcess  
-                             stopProcess  
-                             abortProcess
-                             terminateProcess
-                             terminateProcessGroup
-                             restartProcess
-                             nil  
-                             raisePrio
-                             lowerPrio
-                            ).
-        updateProcess isNil ifTrue:[
-            labels := (resources array:#('update' '-')) , labels.
-            selectors := #(updateView nil) , selectors
-        ].
-    ].
-
-    m := PopUpMenu labels:labels
-                   selectors:selectors.
-
-
-    (sel := listView selection) isNil ifTrue:[
-        m disableAll:#(
-                             inspectProcess  
-                             debugProcess  
-                             nil  
-                             resumeProcess  
-                             suspendProcess  
-                             stopProcess  
-                             restartProcess
-                             abortProcess
-                             terminateProcess
-                             terminateProcessGroup
-                             nil  
-                             raisePrio
-                             lowerPrio
-                      )
-    ] ifFalse:[
-        allRestartable := true.
-        self selectedProcessesDo:[:p |
-            p isRestartable ifFalse:[
-                allRestartable := false
-            ].
-        ].
-        allRestartable ifFalse:[
-            m disable:#restartProcess
-        ].
-    ].
-
-    m checkToggleAt:#detail put:showDetail.
-    ^ m
-!
-
 raisePrio
     "raise the selected processes priority"
 
@@ -624,6 +418,92 @@
     self selectedProcessesSend:#resume
 !
 
+statusMenu
+    "return a popUpMenu"
+
+    |labels selectors m sel allRestartable|
+
+    device ctrlDown ifTrue:[
+        labels := resources array:#(
+                        '\c detail'
+                      ).
+        selectors := #(
+                        tiggleDetail
+                      ).
+    ] ifFalse:[
+        labels := resources array:#(
+                             'inspect' 
+                             'debug'  
+                             '-'  
+                             'resume'  
+                             'suspend'  
+                             'stop'  
+                             'abort'
+                             'terminate'
+                             'terminate group'
+                             'restart'
+                             '-'  
+                             'raise prio'  
+                             'lower prio'  
+                            ).
+        selectors := #(
+                             inspectSelection
+                             debugProcess  
+                             nil  
+                             resumeProcess  
+                             suspendProcess  
+                             stopProcess  
+                             abortProcess
+                             terminateProcess
+                             terminateProcessGroup
+                             restartProcess
+                             nil  
+                             raisePrio
+                             lowerPrio
+                            ).
+        updateProcess isNil ifTrue:[
+            labels := (resources array:#('update' '-')) , labels.
+            selectors := #(updateView nil) , selectors
+        ].
+    ].
+
+    m := PopUpMenu labels:labels
+                   selectors:selectors.
+
+
+    listView hasSelection ifFalse:[
+        m disableAll:#(
+                             inspectSelection
+                             debugProcess  
+                             resumeProcess  
+                             suspendProcess  
+                             stopProcess  
+                             restartProcess
+                             abortProcess
+                             terminateProcess
+                             terminateProcessGroup
+                             raisePrio
+                             lowerPrio
+                      )
+    ] ifTrue:[
+        allRestartable := true.
+        self selectedProcessesDo:[:p |
+            p isRestartable ifFalse:[
+                allRestartable := false
+            ].
+        ].
+        allRestartable ifFalse:[
+            m disable:#restartProcess
+        ].
+    ].
+
+    m checkToggleAt:#toggleDetail put:showDetail.
+    ^ m
+
+    "Created: 23.1.1997 / 03:05:54 / cg"
+    "Modified: 23.1.1997 / 03:10:09 / cg"
+!
+
 stopProcess
     "stop the selected process - not even interrupts will wake it up"
 
@@ -646,54 +526,77 @@
     "terminate the selected process with all of its subprocesses"
 
     self selectedProcessesSend:#terminateGroup
+!
+
+toggleDetail
+    "toggle detail"
+
+    showDetail := showDetail not.
+    self updateView
+
+    "Modified: 23.1.1997 / 02:33:03 / cg"
+    "Created: 23.1.1997 / 02:33:30 / cg"
 ! !
 
 !ProcessMonitor methodsFor:'private'!
 
 selectedProcessesDo:aBlock
+    "evaluate aBlock on all selected processes"
+
     |p nr sel|
 
     sel := listView selection.
     sel isNil ifTrue:[^ self].
+
     (sel isKindOf:Collection) ifTrue:[
-	sel do:[:n |
-	    nr := n - 2.   "for headlines"
-	    nr notNil ifTrue:[
-		nr > 0 ifTrue:[
-		    p := processes at:nr.
-		    (p notNil and:[p ~~ 0]) ifTrue:[
-		       aBlock value:p
-		    ]
-		]
-	    ]
-	]
+        sel do:[:n |
+            nr := n - 2.   "for headlines"
+            nr notNil ifTrue:[
+                nr > 0 ifTrue:[
+                    p := processes at:nr.
+                    (p notNil and:[p ~~ 0]) ifTrue:[
+                       aBlock value:p
+                    ]
+                ]
+            ]
+        ]
     ] ifFalse:[
-	nr := sel - 2.     "for headlines"
-	nr notNil ifTrue:[
-	    nr > 0 ifTrue:[
-		p := processes at:nr.
-		(p notNil and:[p ~~ 0]) ifTrue:[
-		   aBlock value:p
-		]
-	    ]
-	]
+        nr := sel - 2.     "for headlines"
+        nr notNil ifTrue:[
+            nr > 0 ifTrue:[
+                p := processes at:nr.
+                (p notNil and:[p ~~ 0]) ifTrue:[
+                   aBlock value:p
+                ]
+            ]
+        ]
     ].
+
+    "Modified: 23.1.1997 / 03:10:53 / cg"
 !
 
 selectedProcessesSend:aSelector
+    "send a message to all selected processes"
+
     self selectedProcessesDo:[:p |
-	p perform:aSelector
+        p perform:aSelector
     ].
     self updateView.
+
+    "Modified: 23.1.1997 / 02:34:49 / cg"
 ! !
 
-!ProcessMonitor methodsFor:'queries'!
+!ProcessMonitor methodsFor:'user actions'!
 
-preferredExtent
-    ^ (font widthOf:self titleLine) + 40 @ 100
+doubleClicked
+    "open a debugger on the selected process"
+
+    self debugProcess
+
+    "Created: 23.1.1997 / 03:21:30 / cg"
 ! !
 
 !ProcessMonitor class methodsFor:'documentation'!
 
 version
-^ '$Header: /cvs/stx/stx/libtool/Attic/ProcMonitor.st,v 1.43 1996-10-28 20:13:31 cg Exp $'! !
+^ '$Header: /cvs/stx/stx/libtool/Attic/ProcMonitor.st,v 1.44 1997-01-23 02:23:09 cg Exp $'! !
--- a/ProcessMonitor.st	Thu Jan 23 02:41:39 1997 +0100
+++ b/ProcessMonitor.st	Thu Jan 23 03:23:09 1997 +0100
@@ -10,10 +10,9 @@
  hereby transferred.
 "
 
-SimpleView subclass:#ProcessMonitor
-	instanceVariableNames:'listView processes listUpdateDelay updateDelay updateBlock
-		listUpdateBlock updateProcess hideDead runColor suspendedColor
-		waitColor cpuUsages showDetail'
+STXStatusMonitor subclass:#ProcessMonitor
+	instanceVariableNames:'processes hideDead runColor suspendedColor waitColor cpuUsages
+		showDetail'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Interface-Tools'
@@ -43,24 +42,34 @@
     doing.
 
     The information shown is:
-	id         - the numeric id of the process
-	name       - the name (if any) of the process
-		     (the name has no semantic meaning; it exists for the processMonitor only)
-	state      - what is it doing;
-			wait      - waiting on a semaphore
-			eventWait - waiting on a view-event semaphore
-			ioWait    - waiting on an io-semaphore
-			timeWait  - waiting for a time-semaphore
-			run       - run, but currently not scheduled
-			active    - really running (this info is useless, since at
-				    update time, its always the update process which is
-				    running)
-			suspended - suspended; not waiting on a semaphore
-			light     - not yet started (i.e. has no stack yet)
+        id         - the numeric id of the process
+        name       - the name (if any) of the process
+                     (the name has no semantic meaning; it exists for the processMonitor only)
+        state      - what is it doing;
+                        wait      - waiting on a semaphore
+                        eventWait - waiting on a view-event semaphore
+                        ioWait    - waiting on an io-semaphore
+                        timeWait  - waiting for a time-semaphore
+                        run       - run, but currently not scheduled
+                        active    - really running (this info is useless, since at
+                                    update time, its always the update process which is
+                                    running)
+                        suspended - suspended; not waiting on a semaphore
+                        light     - not yet started (i.e. has no stack yet)
         
-	prio       - the processes priority (1..30)
-	usedStack  - the current stack use
-	totalStack - the stack currently allocated (i.e. the maximum ever needed)
+        prio       - the processes priority (1..30)
+        usedStack  - the current stack use
+        totalStack - the stack currently allocated (i.e. the maximum ever needed)
+
+    [see also:]
+        Process ProcessorScheduler
+        WindowGroup
+
+    [author:]
+        Claus Gittinger
+
+    [start with:]
+        ProcessMonitor open
 "
 ! !
 
@@ -71,42 +80,15 @@
 
     i := Image fromFile:'ProcMon.xbm'.
     i notNil ifTrue:[^ i].
-    ^ StandardSystemView defaultIcon
+    ^ super defaultIcon
+
+    "Modified: 23.1.1997 / 02:52:31 / cg"
 !
 
 defaultLabel
     ^ 'Process Monitor'
 ! !
 
-!ProcessMonitor class methodsFor:'startup'!
-
-open
-    |top monitor|
-
-    top := StandardSystemView new.
-    monitor := self origin:0.0@0.0 corner:1.0@1.0 in:top.
-    top extent:monitor preferredExtent.
-    top label:self defaultLabel.
-    top icon:self defaultIcon.
-    top open
-
-    "
-     ProcessMonitor open
-    "
-! !
-
-!ProcessMonitor methodsFor:'destroying'!
-
-destroy
-    updateBlock notNil ifTrue:[
-	Processor removeTimedBlock:updateBlock.
-	Processor removeTimedBlock:listUpdateBlock.
-    ] ifFalse:[
-	updateProcess notNil ifTrue:[updateProcess terminate]
-    ].
-    super destroy
-! !
-
 !ProcessMonitor methodsFor:'drawing'!
 
 titleLine
@@ -338,144 +320,38 @@
 
     "Modified: 3.7.1996 / 13:56:01 / stefan"
     "Modified: 18.7.1996 / 20:19:59 / cg"
-!
-
-updateView
-    self updateList.
-    self updateStatus
-! !
-
-!ProcessMonitor methodsFor:'events'!
-
-canHandle:key
-    ^ key == #InspectIt
-!
-
-keyPress:key x:x y:y
-    <resource: #keyboard ( #InspectIt ) >
-
-    key == #InspectIt ifTrue:[
-	^ self inspectProcess.
-    ].
-    ^ super keyPress:key x:x y:y
 ! !
 
 !ProcessMonitor methodsFor:'initialization'!
 
 initialize
-    |v|
-
     super initialize.
 
     hideDead := true.
     showDetail := Smalltalk at:#SystemDebugging ifAbsent:false.
 
-    v := HVScrollableView for:SelectionInListView miniScrollerH:true in:self.
-    v origin:0.0@0.0 corner:1.0@1.0.
-
-"/    self extent:(font widthOf:self titleLine) + v scrollBar width @ 100.
-
-    listView := v scrolledView.
-    listView font:font.
-    listView menuHolder:self; menuPerformer:self; menuMessage:#processMenu. 
-
-    listView multipleSelectOk:true.
-    listView delegate:(KeyboardForwarder toView:self).
-    listView doubleClickAction:[:line | self debugProcess].
-
-    updateDelay := 0.5.
-    listUpdateDelay := 5.
-
-    "/ event mode is no longer used;
-    "/ this event support may vanish
-    Processor isPureEventDriven ifTrue:[
-        updateBlock := [self updateStatus].
-        listUpdateBlock := [self updateList].
-    ].
-
     device hasColors ifTrue:[
         runColor := Color green.
         suspendedColor := Color yellow.
         waitColor := Color red.
     ] ifFalse:[
         runColor := suspendedColor := waitColor := Color black
-    ]
+    ].
 
     "
      ProcessMonitor open
     "
 
-    "Modified: 13.4.1996 / 20:34:25 / cg"
-!
-
-mapped
-    super mapped.
-    self updateStatus.
-    self updateList.
+    "Modified: 23.1.1997 / 02:51:38 / cg"
 !
 
 realize
-    super realize.
     waitColor := waitColor on:device.
     runColor := runColor on:device.
     suspendedColor := suspendedColor on:device.
-
-    self startUpdateProcess.
-!
-
-reinitialize
-    updateProcess := nil.
-    super reinitialize.
-    self startUpdateProcess.
-
-    "Created: 22.12.1995 / 22:48:37 / cg"
-    "Modified: 22.12.1995 / 22:51:14 / cg"
-!
-
-startUpdateProcess
-    updateBlock notNil ifTrue:[
-        Processor addTimedBlock:updateBlock afterSeconds:updateDelay.
-        Processor addTimedBlock:listUpdateBlock afterSeconds:listUpdateDelay.
-    ] ifFalse:[
-        updateProcess := [
-            [
-                |id cnt|
+    super realize.
 
-                "
-                 every 20ms, we look which process runs;
-                 every half second, the status is updated.
-                 every 5 seconds, the list of processes is
-                 built up again
-                "
-                [true] whileTrue:[
-                    1 to:9 do:[:i |
-"/                        cpuUsages := IdentityDictionary new.
-"/                        1 to:25 do:[:i |
-"/                            (Delay forSeconds:0.02) wait.
-"/                            id := Processor interruptedProcess id.
-"/                            cnt := cpuUsages at:id ifAbsent:[0].
-"/                            cpuUsages at:id put:cnt + 1.
-"/                        ].
-                        Delay waitForSeconds:0.5.
-                        self updateStatus.
-                    ].
-                    Delay waitForSeconds:0.5.
-                    self updateList.
-                ]
-            ] valueOnUnwindDo:[
-                updateProcess := nil
-            ]
-        ]  forkAt:(Processor userSchedulingPriority + 1).
-        updateProcess name:'monitor [' , 
-                           Processor activeProcess id printString ,
-                           '] update'.
-        "
-         raise my own priority
-        "
-        Processor activeProcess priority:(Processor userSchedulingPriority + 2)
-    ].
-
-    "Modified: 12.6.1996 / 19:53:13 / cg"
+    "Modified: 23.1.1997 / 02:30:37 / cg"
 ! !
 
 !ProcessMonitor methodsFor:'menu actions'!
@@ -496,19 +372,20 @@
     ]
 !
 
-detail
-    showDetail := showDetail not.
-    self updateView
+hideDead:aBoolean
+    "turn on/off hiding of dead (already terminated) processes"
+
+    hideDead := aBoolean
+
+    "Modified: 23.1.1997 / 02:34:01 / cg"
 !
 
-hideDead:aBoolean
-    hideDead := aBoolean
-!
-
-inspectProcess
+inspectSelection
     "open an inspector on the selected process"
 
     self selectedProcessesSend:#inspect
+
+    "Created: 23.1.1997 / 02:27:33 / cg"
 !
 
 lowerPrio
@@ -519,89 +396,6 @@
     ]
 !
 
-processMenu
-    |labels selectors m sel allRestartable|
-
-    device ctrlDown ifTrue:[
-        labels := resources array:#(
-                        '\c detail'
-                      ).
-        selectors := #(
-                        detail
-                      ).
-    ] ifFalse:[
-        labels := resources array:#(
-                             'inspect' 
-                             'debug'  
-                             '-'  
-                             'resume'  
-                             'suspend'  
-                             'stop'  
-                             'abort'
-                             'terminate'
-                             'terminate group'
-                             'restart'
-                             '-'  
-                             'raise prio'  
-                             'lower prio'  
-                            ).
-        selectors := #(
-                             inspectProcess  
-                             debugProcess  
-                             nil  
-                             resumeProcess  
-                             suspendProcess  
-                             stopProcess  
-                             abortProcess
-                             terminateProcess
-                             terminateProcessGroup
-                             restartProcess
-                             nil  
-                             raisePrio
-                             lowerPrio
-                            ).
-        updateProcess isNil ifTrue:[
-            labels := (resources array:#('update' '-')) , labels.
-            selectors := #(updateView nil) , selectors
-        ].
-    ].
-
-    m := PopUpMenu labels:labels
-                   selectors:selectors.
-
-
-    (sel := listView selection) isNil ifTrue:[
-        m disableAll:#(
-                             inspectProcess  
-                             debugProcess  
-                             nil  
-                             resumeProcess  
-                             suspendProcess  
-                             stopProcess  
-                             restartProcess
-                             abortProcess
-                             terminateProcess
-                             terminateProcessGroup
-                             nil  
-                             raisePrio
-                             lowerPrio
-                      )
-    ] ifFalse:[
-        allRestartable := true.
-        self selectedProcessesDo:[:p |
-            p isRestartable ifFalse:[
-                allRestartable := false
-            ].
-        ].
-        allRestartable ifFalse:[
-            m disable:#restartProcess
-        ].
-    ].
-
-    m checkToggleAt:#detail put:showDetail.
-    ^ m
-!
-
 raisePrio
     "raise the selected processes priority"
 
@@ -624,6 +418,92 @@
     self selectedProcessesSend:#resume
 !
 
+statusMenu
+    "return a popUpMenu"
+
+    |labels selectors m sel allRestartable|
+
+    device ctrlDown ifTrue:[
+        labels := resources array:#(
+                        '\c detail'
+                      ).
+        selectors := #(
+                        tiggleDetail
+                      ).
+    ] ifFalse:[
+        labels := resources array:#(
+                             'inspect' 
+                             'debug'  
+                             '-'  
+                             'resume'  
+                             'suspend'  
+                             'stop'  
+                             'abort'
+                             'terminate'
+                             'terminate group'
+                             'restart'
+                             '-'  
+                             'raise prio'  
+                             'lower prio'  
+                            ).
+        selectors := #(
+                             inspectSelection
+                             debugProcess  
+                             nil  
+                             resumeProcess  
+                             suspendProcess  
+                             stopProcess  
+                             abortProcess
+                             terminateProcess
+                             terminateProcessGroup
+                             restartProcess
+                             nil  
+                             raisePrio
+                             lowerPrio
+                            ).
+        updateProcess isNil ifTrue:[
+            labels := (resources array:#('update' '-')) , labels.
+            selectors := #(updateView nil) , selectors
+        ].
+    ].
+
+    m := PopUpMenu labels:labels
+                   selectors:selectors.
+
+
+    listView hasSelection ifFalse:[
+        m disableAll:#(
+                             inspectSelection
+                             debugProcess  
+                             resumeProcess  
+                             suspendProcess  
+                             stopProcess  
+                             restartProcess
+                             abortProcess
+                             terminateProcess
+                             terminateProcessGroup
+                             raisePrio
+                             lowerPrio
+                      )
+    ] ifTrue:[
+        allRestartable := true.
+        self selectedProcessesDo:[:p |
+            p isRestartable ifFalse:[
+                allRestartable := false
+            ].
+        ].
+        allRestartable ifFalse:[
+            m disable:#restartProcess
+        ].
+    ].
+
+    m checkToggleAt:#toggleDetail put:showDetail.
+    ^ m
+
+    "Created: 23.1.1997 / 03:05:54 / cg"
+    "Modified: 23.1.1997 / 03:10:09 / cg"
+!
+
 stopProcess
     "stop the selected process - not even interrupts will wake it up"
 
@@ -646,54 +526,77 @@
     "terminate the selected process with all of its subprocesses"
 
     self selectedProcessesSend:#terminateGroup
+!
+
+toggleDetail
+    "toggle detail"
+
+    showDetail := showDetail not.
+    self updateView
+
+    "Modified: 23.1.1997 / 02:33:03 / cg"
+    "Created: 23.1.1997 / 02:33:30 / cg"
 ! !
 
 !ProcessMonitor methodsFor:'private'!
 
 selectedProcessesDo:aBlock
+    "evaluate aBlock on all selected processes"
+
     |p nr sel|
 
     sel := listView selection.
     sel isNil ifTrue:[^ self].
+
     (sel isKindOf:Collection) ifTrue:[
-	sel do:[:n |
-	    nr := n - 2.   "for headlines"
-	    nr notNil ifTrue:[
-		nr > 0 ifTrue:[
-		    p := processes at:nr.
-		    (p notNil and:[p ~~ 0]) ifTrue:[
-		       aBlock value:p
-		    ]
-		]
-	    ]
-	]
+        sel do:[:n |
+            nr := n - 2.   "for headlines"
+            nr notNil ifTrue:[
+                nr > 0 ifTrue:[
+                    p := processes at:nr.
+                    (p notNil and:[p ~~ 0]) ifTrue:[
+                       aBlock value:p
+                    ]
+                ]
+            ]
+        ]
     ] ifFalse:[
-	nr := sel - 2.     "for headlines"
-	nr notNil ifTrue:[
-	    nr > 0 ifTrue:[
-		p := processes at:nr.
-		(p notNil and:[p ~~ 0]) ifTrue:[
-		   aBlock value:p
-		]
-	    ]
-	]
+        nr := sel - 2.     "for headlines"
+        nr notNil ifTrue:[
+            nr > 0 ifTrue:[
+                p := processes at:nr.
+                (p notNil and:[p ~~ 0]) ifTrue:[
+                   aBlock value:p
+                ]
+            ]
+        ]
     ].
+
+    "Modified: 23.1.1997 / 03:10:53 / cg"
 !
 
 selectedProcessesSend:aSelector
+    "send a message to all selected processes"
+
     self selectedProcessesDo:[:p |
-	p perform:aSelector
+        p perform:aSelector
     ].
     self updateView.
+
+    "Modified: 23.1.1997 / 02:34:49 / cg"
 ! !
 
-!ProcessMonitor methodsFor:'queries'!
+!ProcessMonitor methodsFor:'user actions'!
 
-preferredExtent
-    ^ (font widthOf:self titleLine) + 40 @ 100
+doubleClicked
+    "open a debugger on the selected process"
+
+    self debugProcess
+
+    "Created: 23.1.1997 / 03:21:30 / cg"
 ! !
 
 !ProcessMonitor class methodsFor:'documentation'!
 
 version
-^ '$Header: /cvs/stx/stx/libtool/ProcessMonitor.st,v 1.43 1996-10-28 20:13:31 cg Exp $'! !
+^ '$Header: /cvs/stx/stx/libtool/ProcessMonitor.st,v 1.44 1997-01-23 02:23:09 cg Exp $'! !