now the dead processes are gone if collect garbage will pressed in
authorpenk
Thu, 20 Feb 2003 15:28:28 +0100
changeset 4576 4423626f9dfe
parent 4575 c7cd0dfec11e
child 4577 52c443045ead
now the dead processes are gone if collect garbage will pressed in Launcher, some dead Processes not gone but that is because of the window group any where
ProcessMonitorV2.st
--- a/ProcessMonitorV2.st	Thu Feb 20 13:48:59 2003 +0100
+++ b/ProcessMonitorV2.st	Thu Feb 20 15:28:28 2003 +0100
@@ -2,12 +2,10 @@
 
 ApplicationModel subclass:#ProcessMonitorV2
 	instanceVariableNames:'processList tableColumns selectedProcesses updateSema showDetail
-		hasSelection selctionRestartable showProcessId showGroup
-		showState showPrio showUsedStack showTotalStack
-		showCurrentSegment showSwitch showWhere currentSortOrder
-		processTable processes showDead sortBlock selectionRestartable
-		updateListDelayTime increaseupdateListDelayTime
-		decreaseupdateListDelayTime updateContentsDelayTime
+		hasSelection showProcessId showGroup showState showPrio
+		showUsedStack showTotalStack showCurrentSegment showSwitch
+		showWhere currentSortOrder processTable showDead sortBlock
+		selectionRestartable updateListDelayTime updateContentsDelayTime
 		enableDecreaseListDelayTime enableDecreaseContentsDelayTime
 		enableIncreaseListDelayTime enableIncreaseContentsDelayTime
 		listUpdateDelay updateDelay updateBlock listUpdateBlock
@@ -18,9 +16,11 @@
 !
 
 Object subclass:#ProcessItem
-	instanceVariableNames:'processId processGroup processName processState processPrio
-		processUsedStack processTotalStack processWhere processInstance
-		processCurrentSegment processSwitch prioVal idVal groupVal'
+	instanceVariableNames:'processId processGroup processName processActive processState
+		processPrio processUsedStack processTotalStack processWhere
+		processInstance weakArrayWithProcesses
+		processInstanceIndexInWeakArray processCurrentSegment
+		processSwitch prioVal idVal groupVal'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:ProcessMonitorV2
@@ -1098,7 +1098,6 @@
             #label: '-'
           )
          #(#MenuItem
-            #enabled: false
             #label: 'Show dead Processes'
             #translateLabel: true
             #indication: #showDead
@@ -1174,6 +1173,19 @@
          #showColSeparator: false
        )
       #(#DataSetColumnSpec
+         #label: ''
+         #id: #active
+         #labelButtonType: #Button
+         #labelActionSelector: #sortProcessListBy:
+         #labelActionArgument: 'processActive'
+         #width: 10
+         #height: 5
+         #model: #processActive
+         #canSelect: false
+         #showRowSeparator: false
+         #showColSeparator: false
+       )
+      #(#DataSetColumnSpec
          #label: 'State'
          #id: #state
          #labelAlignment: #left
@@ -1269,7 +1281,6 @@
          #showColSeparator: false
        )
       )
-    
 ! !
 
 !ProcessMonitorV2 methodsFor:'accessing'!
@@ -1304,12 +1315,12 @@
     ].
 !
 
-changeSelectionToProcess:aProcessList
+changeSelectionToProcesses:aProcessList
 
     aProcessList notNil ifTrue:[
         | newSelection |
         newSelection := OrderedCollection new.
-        aProcessList do:[:aProcess |
+        aProcessList do:[:aProcess |                       
             | index | 
             index := processList findFirst:[:anItem | (anItem processInstance == aProcess)].
             index ~~ 0 ifTrue:[
@@ -1375,13 +1386,16 @@
 !
 
 selectedProcessesDo:aBlock
-    | sel|
+    | sel proc|
 
     sel := self selectedProcesses value.
     sel isNil ifTrue:[^ self].
 
     sel do:[:processItem |
-       aBlock value:(processItem processInstance).
+        proc := processItem processInstance.
+        proc notNil ifTrue:[
+            aBlock value:proc.
+        ].
     ]
 !
 
@@ -1493,9 +1507,14 @@
 sortBlock
 
     sortBlock isNil ifTrue:[
+        | curSortOrder defaultSortInstance|
+        defaultSortInstance := #idVal.
         sortBlock := [:a :b |
-            a idVal < b idVal
+            ((a perform:defaultSortInstance) < (b perform:defaultSortInstance))
         ].
+        curSortOrder := self currentSortOrder value.
+        curSortOrder at:#column put:defaultSortInstance.
+        curSortOrder at:#reverse put:true.
     ].
     ^ sortBlock
 !
@@ -1667,7 +1686,9 @@
     sel notNil ifTrue:[
         oldSelection := OrderedCollection new.
         sel do:[:proItem|
-            oldSelection add:(proItem processInstance)    
+            proItem processInstance notNil ifTrue:[
+                oldSelection add:(proItem processInstance)    
+            ].
         ].
     ].
 "/    Transcript showCR:'oldSelection on catch in viewedColumnsChanged', (oldSelection isNil ifTrue:['nil'] ifFalse:[oldSelection first printString]).
@@ -1689,48 +1710,28 @@
                 icon := currentSortOrderReverse ifTrue:[self class detailsMenuIconDown] ifFalse:[self class detailsMenuIconUp].
                 col label:(LabelAndIcon label:label icon:icon).
             ].
-            (id == #id and:[self showProcessId value not]) ifTrue:[
-                columns remove:col. 
-            ] ifFalse:[
-                (id == #group and:[self showGroup value not]) ifTrue:[
+            #(
+                ( #id             #showProcessId)
+                ( #group          #showGroup)
+                ( #prio           #showPrio)
+                ( #currentSegment #showCurrentSegment)
+                ( #state          #showState)
+                ( #switch         #showSwitch)
+                ( #totalStack     #showTotalStack)
+                ( #usedStack      #showUsedStack)
+                ( #where          #showWhere)
+            ) pairsDo:[:colName :holderAccessorSelector |
+                (id == colName and:[(self perform:holderAccessorSelector) value not]) ifTrue:[
                     columns remove:col. 
-                ] ifFalse:[
-                    (id == #prio and:[self showPrio value not]) ifTrue:[
-                        columns remove:col.
-                    ] ifFalse:[
-                        (id == #currentSegment and:[self showCurrentSegment value not]) ifTrue:[
-                            columns remove:col.
-                        ] ifFalse:[
-                            (id == #state and:[self showState value not]) ifTrue:[
-                                columns remove:col.
-                            ] ifFalse:[
-                                (id == #switch and:[self showSwitch value not]) ifTrue:[
-                                    columns remove:col.
-                                ] ifFalse:[
-                                    (id == #totalStack and:[self showTotalStack value not]) ifTrue:[
-                                        columns remove:col.
-                                    ] ifFalse:[
-                                        (id == #usedStack and:[self showUsedStack value not]) ifTrue:[
-                                            columns remove:col.
-                                        ] ifFalse:[
-                                            (id == #where and:[self showWhere value not]) ifTrue:[
-                                                columns remove:col.
-                                            ]
-                                        ]
-                                    ] 
-                                ]
-                            ]
-                        ]
-                    ]
                 ]
             ]
         ]
     ].
-    self tableColumns value:columns.
-    self updateTable:nil.
     updateSema critical:[
+        self tableColumns value:columns.
+"/        self updateTable:nil.
 "/        Transcript showCR:'oldSelection on set in viewedColumnsChanged', (oldSelection isNil ifTrue:['nil'] ifFalse:[oldSelection first printString]).
-        self changeSelectionToProcess:oldSelection.
+        self changeSelectionToProcesses:oldSelection.
     ].
 ! !
 
@@ -1900,35 +1901,70 @@
 
 printProcessList
 
-    |stream|
-
-    stream := WriteStream on:''.
-    ('ProcessList for user ', 
-    OperatingSystem getLoginName, 
-    ' on ' ,
-    OperatingSystem getHostName,
-    ' at ',
-    (AbsoluteTime now printStringFormat:'%(day)-%(monthName)-%(year) %h:%m:%s')
-    ) printOn:stream.
-    stream cr.
-    ('Id' leftPaddedTo:7) printOn:stream.
-    ('Group' leftPaddedTo:7) printOn:stream.
-    ('Name' leftPaddedTo:30) printOn:stream.
-    ('State' leftPaddedTo:12) printOn:stream.
-    ('Prio' leftPaddedTo:10) printOn:stream.
-    ('Where' leftPaddedTo:40) printOn:stream.
-    stream cr.
-    self processList do:[:aProcessItem |
-        (aProcessItem processId printString leftPaddedTo:7) printOn:stream.
-        (aProcessItem processGroup printString leftPaddedTo:7) printOn:stream.
-        (aProcessItem processName leftPaddedTo:30) printOn:stream.
-        (aProcessItem processState leftPaddedTo:12) printOn:stream.
-        (aProcessItem processPrio leftPaddedTo:10) printOn:stream.
-        stream space.
-        (aProcessItem processWhere leftPaddedTo:40) printOn:stream.
-        stream cr.
+    |view image printer gc device origin corner extent y x scaleX scaleY|
+
+    Printer == PostscriptPrinterStream ifFalse:[
+        ^ self warn:'kein Postscript Drucker'.
     ].
-    self printStringToPrinter:(stream contents).
+
+    view := builder window.
+    view raise.
+    view device sync.
+    view allSubViewsDo:[:v|v shown ifTrue:[v invalidateRepairNow:true]].
+
+    device := view graphicsDevice.
+    origin := device translatePoint:(0@0) from:(view id) to:device rootWindowId.
+
+    corner := origin + (view extent).
+    extent := Screen current rootView extent.
+
+    corner x > extent x ifTrue:[corner x:(extent x)].
+    corner y > extent y ifTrue:[corner y:(extent y)].
+
+    self withExecuteCursorDo:[
+        image := Image fromScreen:(origin corner:corner) on:device grab:true.
+        [
+            printer := Printer newNative.
+            gc := PSGraphicsContext on:printer. "/  extent:(1.0 @ 1.0).
+
+            gc pageEndAction:[:pageNr||title font|
+                title := view label, '  ', (Time now asAbsoluteTime printString).
+                font  := gc titleFont.
+
+                y := (gc bottomMargin + font height + font ascent) // 2.
+                y := (10 + font height + font ascent) // 2.
+                y := font height + font ascent.
+                x := (gc width) - (font widthOf:title) - (gc rightMargin).
+
+                gc displayString:title x:(gc transformX:x) y:y.
+            ].
+
+            x := gc width - gc rightMargin.
+            y := gc height - gc bottomMargin - gc topMargin.
+
+            (x < image width and:[x >= image height]) ifTrue:[
+                image := image rotated:90.
+            ].
+            y < image height ifTrue:[
+                scaleY := (y / (image height)) asFloat
+            ] ifFalse:[
+                scaleY := 1
+            ].
+
+            x < image width ifTrue:[
+                scaleX := (x / (image width)) asFloat
+            ] ifFalse:[
+                scaleX := 1
+            ].
+
+            gc scale:(scaleX@scaleY).
+            gc displayImage:image at:(0@(gc topMargin)).
+            gc flush.
+
+        ] ensure:[
+            gc close.
+        ].
+    ].
 !
 
 printStringToPrinter:aString
@@ -2009,13 +2045,28 @@
 "/      self showTotalStack value or:[
 "/      self showCurrentSegment value or:[
 "/      self showSwitch value]]])
-!
-
-showDetail
 ! !
 
 !ProcessMonitorV2 methodsFor:'queries - table string'!
 
+getActiveStringFor:aProcess running:isRunning
+
+    | stateCharacter |
+
+   isRunning ifTrue:[
+        stateCharacter := '*'.
+    ] ifFalse:[
+        [
+            (Processor scheduledProcesses includes:aProcess) ifTrue:[
+                stateCharacter := '+'
+            ] ifFalse:[
+                stateCharacter := ''.
+            ].
+        ] valueUninterruptably.
+    ].
+    ^ stateCharacter.
+!
+
 getCurrentSegmentStringFor:con
 
     con notNil ifTrue:[
@@ -2065,25 +2116,6 @@
     ^ ''
 !
 
-getStateStringFor:aProcess running:isRunning
-
-    |st stateCharacter |
-
-    st := aProcess state.
-    isRunning ifTrue:[
-        stateCharacter := '* '.
-    ] ifFalse:[
-        [
-            (Processor scheduledProcesses includes:aProcess) ifTrue:[
-                stateCharacter := '+ '
-            ] ifFalse:[
-                stateCharacter := '  '.
-            ].
-        ] valueUninterruptably.
-    ].
-    ^ stateCharacter, (st asString).
-!
-
 getTotalStackStringFor:aProcess
 
 
@@ -2240,7 +2272,7 @@
             entry1 := (a perform:aSymbol) ? 0.
             entry2 := (b perform:aSymbol) ? 0.
             entry1 = entry2 ifTrue:[
-                a idVal < 0 ifTrue:[
+                (a idVal < 0 and:[b idVal < 0]) ifTrue:[
                     "/ two dead ones (take anything which remains constant)
                     a processName ~= b processName ifTrue:[
                         a processName < b processName 
@@ -2259,12 +2291,103 @@
 
 !ProcessMonitorV2 methodsFor:'update process'!
 
-redrawChangedItems:oldItem newItem:newItem on:index
+fillItemInformationIn:processItem 
+
+    | running con aProcess|
+
+    aProcess := processItem processInstance.
+    aProcess isNil ifTrue:[
+        ^ self.
+    ].
+
+    processItem processId:aProcess id.
+    processItem idVal:aProcess id ? -1.
+
+    processItem processGroup:(self getGroupStringFor:aProcess).
+    processItem groupVal:(processItem processGroup isNumber ifTrue:[processItem processGroup] ifFalse:[-1]).
+
+    processItem processName:aProcess name ? ''.
+
+    running := (aProcess state == #run and:[aProcess == Processor interruptedProcess]).
+
+    processItem processState:(aProcess state asString).
+    processItem processActive:(self getActiveStringFor:aProcess running:running).
+
+    processItem prioVal:(aProcess priority).
+    processItem processPrio:(self getPrioStringFor:aProcess).
+
+    processItem processUsedStack:aProcess usedStackSize.
+
+    processItem processTotalStack:(self getTotalStackStringFor:aProcess).
+
+    con := aProcess suspendedContext.
+    con isNil ifTrue:[
+        aProcess == Processor activeProcess ifTrue:[
+            con := thisContext
+        ]
+    ].
+
+    processItem processCurrentSegment:(self getCurrentSegmentStringFor:con).
+
+    processItem processSwitch:(aProcess numberOfStackBoundaryHits).
+
+    processItem processWhere:(self getWhereStringFor:con running:running).
+!
+
+fillItemInformationIn:processItem with:aProcess inArray:weakArrayWithProcesses atIndex:processInstanceIndexInWeakArray
+
+    processItem weakArrayWithProcesses:weakArrayWithProcesses.
+    processItem processInstanceIndexInWeakArray:processInstanceIndexInWeakArray.
+    self fillItemInformationIn:processItem
+!
+
+startUpdateProcess
+    updateBlock notNil ifTrue:[
+        Processor addTimedBlock:updateBlock afterSeconds:self scaledUpdateContentsDelayTime.
+        Processor addTimedBlock:listUpdateBlock afterSeconds:self scaledUpdateListDelayTime.
+    ] ifFalse:[
+        updateProcess := [
+            [
+                |id cnt myDelay|
+
+                myDelay := Delay forSeconds:self scaledUpdateContentsDelayTime.
+
+                "
+                 every updateDelay (0.5), we look which process runs;
+                 every half second, the status is updated.
+                 every listUpdateDelay (5s), the list of processes is
+                 built up again
+                "
+                [true] whileTrue:[
+                    ((self scaledUpdateListDelayTime // self scaledUpdateContentsDelayTime) max:2) - 1 timesRepeat:[
+                        myDelay wait.
+                        self updateStatus:nil.
+                    ].
+                    myDelay wait.
+                    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)
+    ].
+!
+
+updateChangedItem:oldItem newItem:newItem atIndex:index
 
     | colIdx |
     colIdx := 1.
 
-    oldItem processInstance:newItem processInstance.
+    oldItem weakArrayWithProcesses:newItem weakArrayWithProcesses.
+    oldItem processInstanceIndexInWeakArray:newItem processInstanceIndexInWeakArray.
+
     "/ ID
     oldItem processId ~= newItem processId ifTrue:[
         oldItem processId:newItem processId.
@@ -2284,12 +2407,18 @@
         oldItem processName:newItem processName.
         processTable invalidateRowAt:index colAt:colIdx.
     ].
+    "/ ACTIVE
+    colIdx := colIdx + 1.
+    oldItem processActive ~= newItem processActive ifTrue:[
+        oldItem processActive:newItem processActive.
+        (processTable columnAt:colIdx).
+        processTable invalidateRowAt:index colAt:colIdx.
+    ].
     "/ STATE
     self showState value ifTrue:[
         colIdx := colIdx + 1.
         oldItem processState ~= newItem processState ifTrue:[
             oldItem processState:newItem processState.
-"/            self halt.
             (processTable columnAt:colIdx).
             processTable invalidateRowAt:index colAt:colIdx.
         ].
@@ -2344,45 +2473,6 @@
     ].
 !
 
-startUpdateProcess
-    updateBlock notNil ifTrue:[
-        Processor addTimedBlock:updateBlock afterSeconds:self scaledUpdateContentsDelayTime.
-        Processor addTimedBlock:listUpdateBlock afterSeconds:self scaledUpdateListDelayTime.
-    ] ifFalse:[
-        updateProcess := [
-            [
-                |id cnt myDelay|
-
-                myDelay := Delay forSeconds:self scaledUpdateContentsDelayTime.
-
-                "
-                 every updateDelay (0.5), we look which process runs;
-                 every half second, the status is updated.
-                 every listUpdateDelay (5s), the list of processes is
-                 built up again
-                "
-                [true] whileTrue:[
-                    ((self scaledUpdateListDelayTime // self scaledUpdateContentsDelayTime) max:2) - 1 timesRepeat:[
-                        myDelay wait.
-                        self updateStatus:nil.
-                    ].
-                    myDelay wait.
-                    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)
-    ].
-!
-
 updateList
 
     |newList|
@@ -2392,7 +2482,7 @@
         visibleBlock notNil ifTrue:[
             newList := newList select:[:aProc|visibleBlock value:aProc]
         ].
-        self updateStatus:newList
+        self updateStatus:newList.
     ].
     updateBlock notNil ifTrue:[
         Processor removeTimedBlock:listUpdateBlock.
@@ -2406,7 +2496,9 @@
 
 
     startTime := AbsoluteTime now.
-    self updateTable:newProcessList.
+    updateSema critical:[
+        self updateTable:newProcessList.
+    ].
 
     endTime := AbsoluteTime now.
     deltaT := (endTime millisecondDeltaFrom:startTime) / 1000.0.
@@ -2432,113 +2524,64 @@
 
 updateTable:newProcessList
 
-    | oldSelection newList locNewProcs sel diff|
+    | oldSelection newList sel diff weakProcessList|
 
 
     processTable shown ifTrue:[
 "/        Transcript showCR:('update the table', AbsoluteTime now printString, 'with new list:', newProcessList notNil asString).
-        updateSema critical:[
-            sel := self selectedProcesses value.
-            sel notNil ifTrue:[
-                oldSelection := OrderedCollection new.
-                sel do:[:proItem|
+        sel := self selectedProcesses value.
+        sel notNil ifTrue:[
+            oldSelection := OrderedCollection new.
+            sel do:[:proItem|
+                proItem processInstance notNil ifTrue:[
                     oldSelection add:(proItem processInstance)    
                 ].
             ].
+        ].
 "/            Transcript showCR:'oldSelection on catch in updateTable: ', (oldSelection isEmptyOrNil ifTrue:['nil'] ifFalse:[oldSelection first printString]).
-            newProcessList isNil ifTrue:[
-                newList := OrderedCollection new.
-                processList do:[:oldItem |
-                    | newItem |
-                    (self showDead value not and:[oldItem processInstance isDead]) ifFalse:[
-                        newItem := oldItem copy.
-                        self validateItem:newItem.
-                        newList add:newItem.
-                    ]
-                ].
-            ]ifFalse:[
-                "/ remove dead processes if not shown
-                self showDead value ifTrue:[
-                    locNewProcs := newProcessList.
-                ] ifFalse:[
-                    locNewProcs := OrderedCollection new.
-                    newProcessList do:[:proc |
-                        proc isDead not ifTrue:[
-                            locNewProcs add:proc
-                        ]
-                    ]
-                ].
-                newList := OrderedCollection new.
-                locNewProcs do:[:process|
-                    | processItem |
-                    processItem := ProcessItem new.
-                    self validateItem:processItem with:process.
-                    newList add:processItem.
-                ].
-            ].
-            newList sort:self sortBlock.
-            newList doWithIndex:[:newItem :index|
-                | oldItem |
-                oldItem := (processList at:index ifAbsent:nil).
-                oldItem isNil ifTrue:[
-                    processList add:newItem beforeIndex:(index)
-                ] ifFalse:[
-                    self redrawChangedItems:oldItem newItem:newItem on:index
+        newProcessList isNil ifTrue:[
+            newList := OrderedCollection new.
+            processList do:[:oldItem |
+                | newItem |
+                (self showDead value not and:[oldItem processInstance isNil or:[oldItem processInstance isDead]]) ifFalse:[
+                    newItem := oldItem copy.
+                    self fillItemInformationIn:newItem.
+                    newList add:newItem.
                 ]
             ].
-            diff := processList size - newList size.
-            diff > 0 ifTrue:[
-                processList removeLast:diff
+        ]ifFalse:[
+            "/ remove dead processes if not shown
+            newList := OrderedCollection new.
+            weakProcessList := WeakArray withAll:newProcessList.
+            weakProcessList keysAndValuesDo:[:indexInWeakArray :procOrNilOrZero |
+                "/ in a weakarray, dead entries are 0
+                (procOrNilOrZero notNil and:[procOrNilOrZero ~~ 0]) ifTrue:[
+                    (procOrNilOrZero isDead not or:[self showDead value]) ifTrue:[
+                        | processItem |
+                        processItem := ProcessItem new.
+                        self fillItemInformationIn:processItem with:procOrNilOrZero inArray:weakProcessList atIndex:indexInWeakArray.
+                        newList add:processItem.
+                    ]
+                ]
             ].
+        ].
+        newList sort:self sortBlock.
+        newList doWithIndex:[:newItem :index|
+            | oldItem |
+            oldItem := (processList at:index ifAbsent:nil).
+            oldItem isNil ifTrue:[
+                processList add:newItem beforeIndex:(index)
+            ] ifFalse:[
+                self updateChangedItem:oldItem newItem:newItem atIndex:index
+            ]
+        ].
+        diff := processList size - newList size.
+        diff > 0 ifTrue:[
+            processList removeLast:diff
+        ].
 "/            Transcript showCR:'oldSelection on set in updateTable: ', (oldSelection isEmptyOrNil ifTrue:['nil'] ifFalse:[oldSelection first printString]).
-            self changeSelectionToProcess:oldSelection.
-        ]
+        self changeSelectionToProcesses:oldSelection.
     ].
-!
-
-validateItem:processItem 
-
-    | running con aProcess|
-
-    aProcess := processItem processInstance.
-
-    processItem processId:aProcess id.
-    processItem idVal:aProcess id ? -1.
-
-    processItem processGroup:(self getGroupStringFor:aProcess).
-    processItem groupVal:(processItem processGroup isNumber ifTrue:[processItem processGroup] ifFalse:[-1]).
-
-    processItem processName:aProcess name ? ''.
-
-    running := (aProcess state == #run and:[aProcess == Processor interruptedProcess]).
-
-    processItem processState:(self getStateStringFor:aProcess running:running).
-
-    processItem prioVal:(aProcess priority).
-    processItem processPrio:(self getPrioStringFor:aProcess).
-
-    processItem processUsedStack:aProcess usedStackSize.
-
-    processItem processTotalStack:(self getTotalStackStringFor:aProcess).
-
-    con := aProcess suspendedContext.
-    con isNil ifTrue:[
-        aProcess == Processor activeProcess ifTrue:[
-            con := thisContext
-        ]
-    ].
-
-    processItem processCurrentSegment:(self getCurrentSegmentStringFor:con).
-
-    processItem processSwitch:(aProcess numberOfStackBoundaryHits).
-
-    processItem processWhere:(self getWhereStringFor:con running:running).
-!
-
-validateItem:processItem with:aProcess
-
-    processItem processInstance:aProcess.
-    self validateItem:processItem
 ! !
 
 !ProcessMonitorV2::ProcessItem methodsFor:'accessing'!
@@ -2579,6 +2622,18 @@
     prioVal := something.
 !
 
+processActive
+    "return the value of the instance variable 'processActive' (automatically generated)"
+
+    ^ processActive
+!
+
+processActive:something
+    "set the value of the instance variable 'processActive' (automatically generated)"
+
+    processActive := something.
+!
+
 processCurrentSegment
     "return the value of the instance variable 'processCurrentSegment' (automatically generated)"
 
@@ -2618,7 +2673,11 @@
 processInstance
     "return the value of the instance variable 'processInstance' (automatically generated)"
 
-    ^ processInstance
+    |procOrNilOrZero|
+
+    procOrNilOrZero := weakArrayWithProcesses at:processInstanceIndexInWeakArray.
+    procOrNilOrZero == 0 ifTrue:[^ nil].
+    ^ procOrNilOrZero
 !
 
 processInstance:something
@@ -2627,6 +2686,18 @@
     processInstance := something.
 !
 
+processInstanceIndexInWeakArray
+    "return the value of the instance variable 'processInstanceIndexInWeakArray' (automatically generated)"
+
+    ^ processInstanceIndexInWeakArray
+!
+
+processInstanceIndexInWeakArray:something
+    "set the value of the instance variable 'processInstanceIndexInWeakArray' (automatically generated)"
+
+    processInstanceIndexInWeakArray := something.
+!
+
 processName
     "return the value of the instance variable 'processName' (automatically generated)"
 
@@ -2709,22 +2780,34 @@
     "set the value of the instance variable 'processWhere' (automatically generated)"
 
     processWhere := something.
+!
+
+weakArrayWithProcesses
+    "return the value of the instance variable 'weakArrayWithProcesses' (automatically generated)"
+
+    ^ weakArrayWithProcesses
+!
+
+weakArrayWithProcesses:something
+    "set the value of the instance variable 'weakArrayWithProcesses' (automatically generated)"
+
+    weakArrayWithProcesses := something.
 ! !
 
 !ProcessMonitorV2::ProcessItem methodsFor:'printing'!
 
 displayString
 
-    ^ self processName, '[', self processId asString, ']'
+    ^ self printString
 !
 
 printString
 
-    ^ self processName, '[', self processId asString, ']'
+    ^ self processName ? '' , '[', self processId ? '' asString, ']'
 ! !
 
 !ProcessMonitorV2 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/ProcessMonitorV2.st,v 1.11 2003-02-19 18:06:17 penk Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ProcessMonitorV2.st,v 1.12 2003-02-20 14:28:28 penk Exp $'
 ! !