MemoryUsageView.st
changeset 9887 6b439788a66b
parent 9387 c5f99e84ed65
child 9924 d4cd990abf99
--- a/MemoryUsageView.st	Tue May 03 18:35:40 2011 +0200
+++ b/MemoryUsageView.st	Thu May 05 17:28:32 2011 +0200
@@ -12,12 +12,22 @@
 "{ Package: 'stx:libtool' }"
 
 StandardSystemView subclass:#MemoryUsageView
-	instanceVariableNames:'rawInfo info list sortBlock titleLabel'
+	instanceVariableNames:'rawInfo info list sortBlock titleLabel prevRawInfo
+		autoUpdateProcess autoUpdateInterval'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Monitors-ST/X'
 !
 
+Object subclass:#StatisticEntry
+	instanceVariableNames:'classNameOrSymbol overallByteSize minByteSize maxByteSize
+		averageSize instanceCount instanceAllocationRate
+		memoryAllocationRate'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:MemoryUsageView
+!
+
 !MemoryUsageView class methodsFor:'documentation'!
 
 copyright
@@ -38,11 +48,14 @@
 "
     this view shows an overview over the memory usage of the system.
     usage:
-	MemoryUsageView new open
+        MemoryUsageView new open
 
     Since scanning all memory takes some time, this is not done
     automatically, but upon request. See the middlebuttonmenu-'update'
     function.
+
+    This is a very old application - definitely needs some pimping to look better...
+    ... any maybe a nice menu, graphical display etc.
 "
 ! !
 
@@ -54,6 +67,63 @@
     "Created: / 10.8.1998 / 16:02:59 / cg"
 ! !
 
+!MemoryUsageView methodsFor:'auto update'!
+
+autoUpdate
+    self pushEvent:#update
+
+    "Created: / 05-05-2011 / 17:20:52 / cg"
+!
+
+autoUpdateInterval
+    ^ autoUpdateInterval ? 30 seconds
+
+    "Created: / 05-05-2011 / 17:20:49 / cg"
+!
+
+autoUpdateLoop
+    [true] whileTrue:[
+        self autoUpdate.
+        Delay waitFor:self autoUpdateInterval
+    ].
+
+    "Created: / 05-05-2011 / 17:20:44 / cg"
+!
+
+openAutoUpdateIntervalDialog
+    |s|
+
+    s := Dialog request:'Update interval [smh]:' initialAnswer:self autoUpdateInterval printString.
+    s isEmptyOrNil ifTrue:[^ self].
+
+    autoUpdateInterval := TimeDuration readFrom:s.
+
+    "Created: / 05-05-2011 / 17:24:48 / cg"
+!
+
+startAutoUpdateProcess
+    autoUpdateProcess notNil ifTrue:[
+        self stopAutoUpdateProcess.
+    ].
+    autoUpdateProcess :=
+        [
+            self autoUpdateLoop
+        ] fork
+
+    "Created: / 05-05-2011 / 17:19:00 / cg"
+!
+
+stopAutoUpdateProcess
+    |p|
+
+    (p := autoUpdateProcess) notNil ifTrue:[
+        autoUpdateProcess := nil.
+        p terminate.
+    ].
+
+    "Created: / 05-05-2011 / 17:19:03 / cg"
+! !
+
 !MemoryUsageView methodsFor:'initialization'!
 
 initialize
@@ -62,8 +132,8 @@
     super initialize.
     self label:'Memory Usage'.
 
-    headLine := ' Class' paddedTo:50 with:Character space.
-    headLine := headLine , '# of Insts  Avg sz   Max sz   Bytes   %Mem  %Accum.'.
+    headLine := ' Class' paddedTo:47 with:Character space.
+    headLine := headLine , '# of Insts     Bytes   Avg sz   Max sz   %Mem  %Accum. +Insts    +Bytes'.
 
     titleLabel := Label in:self.
     titleLabel origin:(0.0 @ 0.0) corner:(1.0 @ titleLabel height).
@@ -71,8 +141,6 @@
     titleLabel label:headLine.
     titleLabel adjust:#left.
 
-    self extent:((font widthOf:headLine) + (device horizontalPixelPerMillimeter * 15) rounded) @ self height.
-
     helpView := ScrollableView for:SelectionInListView in:self.
     helpView origin:(0.0 @ titleLabel height) corner:1.0 @ 1.0.
 
@@ -84,14 +152,23 @@
     titleLabel font:(EditTextView defaultFont).
     list menuHolder:self; menuPerformer:self; menuMessage:#usageMenu.
 
+    self extent:((list font widthOf:headLine) + (device horizontalPixelPerMillimeter * 15) rounded) @ self height.
+
     "
      MemoryUsageView open
     "
 
-    "Modified: 14.10.1997 / 21:30:23 / cg"
+    "Modified: / 05-05-2011 / 17:09:12 / cg"
+!
+
+release
+    self stopAutoUpdateProcess.
+    super release.
+
+    "Created: / 05-05-2011 / 17:26:24 / cg"
 ! !
 
-!MemoryUsageView methodsFor:'menu actions'!
+!MemoryUsageView methodsFor:'menu-actions'!
 
 browseClass
     |class|
@@ -344,95 +421,6 @@
     "Modified: 15.10.1996 / 22:09:29 / cg"
 !
 
-sortByAverageSize
-    self label:'Memory usage; by average size'.
-"/    sortBlock := [:a :b | ((a at:3)/(a at:2)) > ((b at:3)/(b at:2))].
-    sortBlock := [:a :b | |n1 n2 m1 m2|
-			   n1 := ((a at:3)/(a at:2)).
-			   n2 := ((b at:3)/(b at:2)).
-			   n1 > n2 
-			   or:[n1 == n2
-			       and:[(a at:1) displayString < (b at:1) displayString]]].
-    self updateDisplay
-
-
-!
-
-sortByClass
-    self label:'Memory usage; by class'.
-    sortBlock := [:a :b | |c1 c2 s1 s2|
-
-                          c1 := (a at:1).
-                          c2 := (b at:1).
-
-                          s1 := c1 isBehavior ifTrue:[ c1 name] ifFalse:[ c1 displayString ].
-                          s2 := c2 isBehavior ifTrue:[ c2 name ] ifFalse:[ c2 displayString ].
-                          s1 < s2].
-    self updateDisplay
-
-    "Modified: 28.6.1996 / 14:32:38 / cg"
-!
-
-sortByClassNameWithoutPrefix
-    self label:'Memory usage; by className without prefix'.
-    sortBlock := [:a :b | |c1 c2 s1 s2|
-
-                          c1 := (a at:1).
-                          c2 := (b at:1).
-
-                          s1 := c1 isBehavior ifTrue:[ c1 nameWithoutPrefix ] ifFalse:[ c1 displayString ].
-                          s2 := c2 isBehavior ifTrue:[ c2 nameWithoutPrefix ] ifFalse:[ c2 displayString ].
-                          s1 < s2].
-    self updateDisplay
-
-
-
-
-
-
-
-!
-
-sortByInstCount
-    self label:'Memory usage; by instance count'.
-"/    sortBlock := [:a :b | (a at:2) > (b at:2) ].
-    sortBlock := [:a :b | |n1 n2|
-			   n1 := (a at:2).
-			   n2 := (b at:2).
-			   n1 > n2 
-			   or:[n1 == n2
-			       and:[(a at:1) displayString < (b at:1) displayString]]].
-    self updateDisplay
-!
-
-sortByMaxSize
-    self label:'Memory usage; by maximum size'.
-"/    sortBlock := [:a :b | (a at:4) > (b at:4)].
-    sortBlock := [:a :b | |n1 n2 m1 m2|
-			   n1 := (a at:4).
-			   n2 := (b at:4).
-			   n1 > n2 
-			   or:[n1 == n2
-			       and:[(a at:1) displayString < (b at:1) displayString]]].
-    self updateDisplay
-
-
-!
-
-sortByMemoryUsage
-    self label:'Memory usage; by memory usage'.
-"/    sortBlock := [:a :b | (a at:3) > (b at:3)].
-    sortBlock := [:a :b | |n1 n2|
-			   n1 := (a at:3).
-			   n2 := (b at:3).
-			   n1 > n2 
-			   or:[n1 == n2
-			       and:[(a at:1) displayString < (b at:1) displayString]]].
-    self updateDisplay
-
-
-!
-
 update
     self updateInfo.
     self updateDisplay
@@ -451,28 +439,178 @@
                      ('Sort by Memory Usage'            sortByMemoryUsage                       )
                      ('Sort by Average Size'            sortByAverageSize                       )
                      ('Sort by Maximum Size'            sortByMaxSize                           )
+                     ('Sort by Inst Allocation Rate'    sortByInstanceAllocationRate            )
+                     ('Sort by Byte Allocation Rate'    sortByMemoryAllocationRate              )
                      ('-')
                      ('Inspect Instances'               inspectInstances                        )
                      ('Inspect with Search'             inspectInstancesWithSearch              )
                      ('Inspect Owners'                  inspectOwners                           )
+                     ('-')
                      ('Ref Chains'                      displayGlobalRefChainsToInsts           )
                      ('Clear (nil) Instances'           nilInstances                            )
                      ('-')
-                     ('Browse Class'                    browseClass                           )
+                     ('Browse Class'                    browseClass                             )
                      ('-')
                      ('Update'                          update                                  )
+                     ('Start Autoupdate'                startAutoUpdateProcess                  )
+                     ('Autoupdate Interval'             openAutoUpdateIntervalDialog            )
                      ('Collect Garbage & Update'        collectGarbageAndUpdate                 )
                  )
                 resources:resources.
 
-    list hasSelection ifFalse:[
+    (list hasSelection not or:[list selection < 3]) ifTrue:[
         m disableAll:#(inspectInstances inspectInstancesWithSearch
                        inspectOwners 
-                       displayGlobalRefChainsToInsts).
+                       displayGlobalRefChainsToInsts
+                       nilInstances browseClass).
     ].
+    autoUpdateProcess notNil ifTrue:[
+        m labelAt:#startAutoUpdate put:'Stop Autoupdate'.
+        m selectorAt:#startAutoUpdate put:#stopAutoUpdateProcess
+    ].
+
     ^ m
 
-    "Modified: / 3.2.1998 / 00:04:16 / cg"
+    "Modified: / 05-05-2011 / 17:23:53 / cg"
+! !
+
+!MemoryUsageView methodsFor:'menu-sorting'!
+
+sortByAverageSize
+    self label:'Memory usage; by average size'.
+
+    sortBlock := [:a :b | 
+        |n1 n2 m1 m2|
+
+       n1 := a averageSize.
+       n2 := b averageSize.
+       n1 > n2 
+            or:[n1 == n2 
+                and:[a classNameOrSymbol displayString < b classNameOrSymbol displayString]]
+    ].
+    self updateDisplay
+
+    "Modified: / 05-05-2011 / 16:11:24 / cg"
+!
+
+sortByClass
+    self label:'Memory usage; by class'.
+
+    sortBlock := [:a :b | 
+        |c1 c2 s1 s2|
+
+        c1 := a classNameOrSymbol.
+        c2 := b classNameOrSymbol.
+
+        s1 := c1 isBehavior ifTrue:[ c1 name] ifFalse:[ c1 displayString ].
+        s2 := c2 isBehavior ifTrue:[ c2 name ] ifFalse:[ c2 displayString ].
+        s1 < s2
+    ].
+    self updateDisplay
+
+    "Modified: / 05-05-2011 / 16:11:53 / cg"
+!
+
+sortByClassNameWithoutPrefix
+    self label:'Memory usage; by className without prefix'.
+
+    sortBlock := [:a :b | 
+        |c1 c2 s1 s2|
+
+        c1 := a classNameOrSymbol.
+        c2 := b classNameOrSymbol.
+
+        s1 := c1 isBehavior ifTrue:[ c1 nameWithoutPrefix ] ifFalse:[ c1 displayString ].
+        s2 := c2 isBehavior ifTrue:[ c2 nameWithoutPrefix ] ifFalse:[ c2 displayString ].
+        s1 < s2
+    ].
+    self updateDisplay
+
+    "Modified: / 05-05-2011 / 16:12:10 / cg"
+!
+
+sortByInstCount
+    self label:'Memory usage; by instance count'.
+
+    sortBlock := [:a :b | 
+        |n1 n2|
+        n1 := a instanceCount.
+        n2 := b instanceCount.
+        n1 > n2 
+        or:[n1 == n2
+            and:[(a classNameOrSymbol) displayString < (b classNameOrSymbol) displayString]]
+    ].
+    self updateDisplay
+
+    "Modified: / 05-05-2011 / 16:47:26 / cg"
+!
+
+sortByInstanceAllocationRate
+    self label:'Memory usage; by inst allocation rate'.
+
+    sortBlock := [:a :b | 
+        |n1 n2 m1 m2|
+
+       n1 := a instanceAllocationRate.
+       n2 := b instanceAllocationRate.
+       n1 > n2 
+            or:[n1 == n2 
+                and:[a classNameOrSymbol displayString < b classNameOrSymbol displayString]]
+    ].
+    self updateDisplay
+
+    "Created: / 05-05-2011 / 16:14:56 / cg"
+!
+
+sortByMaxSize
+    self label:'Memory usage; by maximum size'.
+
+    sortBlock := [:a :b | 
+        |n1 n2 m1 m2|
+
+         n1 := a maxByteSize.
+         n2 := b maxByteSize.
+         n1 > n2 
+         or:[n1 == n2
+             and:[(a classNameOrSymbol) displayString < (b classNameOrSymbol) displayString]]
+    ].
+    self updateDisplay
+
+    "Modified: / 05-05-2011 / 16:13:20 / cg"
+!
+
+sortByMemoryAllocationRate
+    self label:'Memory usage; by inst allocation rate'.
+
+    sortBlock := [:a :b | 
+        |n1 n2 m1 m2|
+
+       n1 := a memoryAllocationRate.
+       n2 := b memoryAllocationRate.
+       n1 > n2 
+            or:[n1 == n2 
+                and:[a classNameOrSymbol displayString < b classNameOrSymbol displayString]]
+    ].
+    self updateDisplay
+
+    "Created: / 05-05-2011 / 16:15:17 / cg"
+!
+
+sortByMemoryUsage
+    self label:'Memory usage; by memory usage'.
+
+    sortBlock := [:a :b | 
+        |n1 n2|
+
+        n1 := a overallByteSize.
+        n2 := b overallByteSize.
+        n1 > n2 
+        or:[n1 == n2
+            and:[(a classNameOrSymbol) displayString < (b classNameOrSymbol) displayString]]
+    ].
+    self updateDisplay
+
+    "Modified: / 05-05-2011 / 16:13:58 / cg"
 ! !
 
 !MemoryUsageView methodsFor:'private'!
@@ -480,104 +618,97 @@
 updateDisplay
     "update the displayed list"
 
+    |nameLen countLen bytesUsedSize avgSizeLen maxSizeLen accumMemoryUseLen|
+
+    nameLen := 50.
+    countLen := 7.
+    bytesUsedSize := 10.
+    avgSizeLen := 10.
+    maxSizeLen := 8.
+    accumMemoryUseLen := 7.
+
     windowGroup withCursor:Cursor wait do:[
         |classNames counts sumSizes maxSizes percents avgSizes 
          l line allMemory 
          overAllCount overAllAvgSize overAllMaxSize 
          lastP sumPercent|
 
+        prevRawInfo notNil ifTrue:[
+            rawInfo keysAndValuesDo:[:key :entry |
+                |prevEntry deltaInstCount deltaInstBytes prevInstCount prevInstBytes| 
+
+                prevEntry := prevRawInfo at:key ifAbsent:nil.
+                prevInstCount :=  prevEntry notNil ifTrue:[prevEntry instanceCount] ifFalse:[0].
+                prevInstBytes :=  prevEntry notNil ifTrue:[prevEntry overallByteSize] ifFalse:0.
+                deltaInstCount := entry instanceCount - prevInstCount.
+                deltaInstBytes := entry overallByteSize - prevInstBytes.
+
+                entry instanceAllocationRate:deltaInstCount.
+                entry memoryAllocationRate:deltaInstBytes.
+            ].
+        ].
+        
         info := rawInfo asSortedCollection:sortBlock.
 
-        classNames := info collect:[:infoArray | 
-            |cls|
-
-            cls := infoArray at:1.
-            cls == #Class ifTrue:[
-                '<all classes>'
-            ] ifFalse:[
-                cls == #Metaclass ifTrue:[
-                    '<all metaclasses>'
-                ] ifFalse:[
-                    cls == #PrivateMetaclass ifTrue:[
-                        '<all private meta classes>'
-                    ] ifFalse:[
-                        cls == #PrivateClass ifTrue:[
-                            '<all private classes>'
-                        ] ifFalse:[
-                            cls == #ObsoleteClass ifTrue:[
-                                '<all obsolete classes>'
-                            ] ifFalse:[
-                                cls == #NameSpace ifTrue:[
-                                    '<all namespaces>'
-                                ] ifFalse:[
-                                    cls isJavaClass ifTrue:[
-                                        cls fullName asString copyReplaceAll:$/ with:$.
-                                    ] ifFalse:[
-                                        cls isObsolete ifTrue:[
-                                            cls name,' (obsolete)'
-                                        ] ifFalse:[
-                                            cls "displayString" name
-                                        ]
-                                    ]
-                                ]
-                            ]
-                        ]
-                    ]
-                ] 
-            ] 
-        ].
-
-        counts := info collect:[:infoArray | (infoArray at:2) ].
-        sumSizes := info collect:[:infoArray | (infoArray at:3) ].
-        maxSizes := info collect:[:infoArray | (infoArray at:4) ].
-        allMemory := sumSizes inject:0 into:[:sum :this | sum + this].
-        "/ allMemory := ObjectMemory bytesUsed.
+        sumSizes := info collect:[:infoEntry | infoEntry overallByteSize ].
+        allMemory := sumSizes sum.
         percents := sumSizes collect:[:sz | (sz asFloat / allMemory * 100)].
-        avgSizes := (1 to:sumSizes size) collect:[:i | (((sumSizes at:i) / (counts at:i)) * 10) rounded / 10.0].
         sumPercent := 0.
 
+        overAllMaxSize := overAllCount := 0.
+
         l := OrderedCollection new.
-        1 to:classNames size do:[:i |
-            |line avgSz maxSz percent|
+        info doWithIndex:[:entry :i |
+            |line avgSz avgSzString maxSz instCount percent|
 
-            avgSz := avgSizes at:i.
-            maxSz := maxSizes at:i.
+            maxSz := entry maxByteSize.
+            avgSz := entry averageSize asFixedPoint:1.
             avgSz = maxSz ifTrue:[
-                avgSz := avgSz asInteger printString , '  '.
+                avgSzString := avgSz asInteger printString , '  '.
+            ] ifFalse:[
+                avgSzString := avgSz printString.
             ].
-            line := (classNames at:i) printStringPaddedTo:50 with:Character space.
-            line := line contractTo:50.
-            line := line , ((counts at:i) printStringLeftPaddedTo:7).
-            line := line , (avgSz printStringLeftPaddedTo:10).
-            line := line , (maxSz printStringLeftPaddedTo:8).
-            line := line , ((sumSizes at:i) printStringLeftPaddedTo:10).
+            instCount := entry instanceCount.
+
+            line := entry classNameStringInList printStringPaddedTo:nameLen.
+            line := line contractTo:nameLen.
+
+            line := line , (instCount printStringLeftPaddedTo:countLen).
+            line := line , (entry overallByteSize printStringLeftPaddedTo:bytesUsedSize).
+            line := line , (avgSzString leftPaddedTo:avgSizeLen).
+            line := line , (maxSz printStringLeftPaddedTo:maxSizeLen).
             percent := (percents at:i).
 "/ percent < 0.0 ifTrue:[self halt].
-            line := line , ((percent asFixedPoint:1) printStringLeftPaddedTo:7).
+            line := line , ((percent asFixedPoint:1) printStringLeftPaddedTo:accumMemoryUseLen).
             lastP := sumPercent := ((sumPercent + percent) min:100.0).
-            line := line , ((sumPercent asFixedPoint:1) printStringLeftPaddedTo:7).
-            l add:line
+            line := line , ((sumPercent asFixedPoint:1) printStringLeftPaddedTo:accumMemoryUseLen).
+
+            line := line , (entry instanceAllocationRate printStringLeftPaddedTo:countLen).
+            line := line , (entry memoryAllocationRate printStringLeftPaddedTo:bytesUsedSize).
+
+            l add:line.
+
+            overAllMaxSize := overAllMaxSize max:entry maxByteSize.
+            overAllCount := overAllCount + instCount.
         ].
 "/ (((lastP asFixedPoint:1) printStringLeftPaddedTo:7) startsWith:'99.') ifTrue:[self halt].
         "add summary line"
-        overAllCount := counts inject:0 into:[:sum :this | sum + this].
         overAllAvgSize := ((allMemory / overAllCount) * 10) rounded / 10.0.
-        overAllMaxSize := maxSizes max.
 
-        l add:''.
-        line := 'all objects' printStringPaddedTo:33 with:Character space.
-        line := line , (overAllCount printStringLeftPaddedTo:7).
-        line := line , (overAllAvgSize printStringLeftPaddedTo:10).
-        line := line , (overAllMaxSize printStringLeftPaddedTo:8).
-        line := line , (allMemory printStringLeftPaddedTo:10).
-        line := line , (100.0 printStringLeftPaddedTo:7).
-        l add:line.
+        l addFirst:''.
+        line := 'all objects' printStringPaddedTo:nameLen.
+        line := line , (overAllCount printStringLeftPaddedTo:countLen).
+        line := line , (allMemory printStringLeftPaddedTo:bytesUsedSize).
+        line := line , (overAllAvgSize printStringLeftPaddedTo:avgSizeLen).
+        line := line , (overAllMaxSize printStringLeftPaddedTo:maxSizeLen).
+        line := line , (100.0 printStringLeftPaddedTo:accumMemoryUseLen).
+        l addFirst:line.
 
         list list:l.
     ]
 
-    "Created: / 19.9.1995 / 15:30:47 / claus"
-    "Modified: / 19.7.1998 / 00:47:08 / cg"
+    "Created: / 19-09-1995 / 15:30:47 / claus"
+    "Modified: / 05-05-2011 / 17:15:29 / cg"
 !
 
 updateInfo
@@ -594,6 +725,7 @@
         myProcess := Processor activeProcess.
         myPriority := myProcess priority.
         myProcess priority:(Processor userBackgroundPriority).
+        prevRawInfo := rawInfo.
 
         rawInfo := IdentityDictionary new:600.
 
@@ -602,7 +734,7 @@
             behaviorFlag := Behavior flagBehavior.
 
             ObjectMemory allObjectsDo:[:o |
-                |infoArray class bytes flags|
+                |infoEntry class flags|
 
 "/              o isBehavior ifTrue:[
                 class := o class.
@@ -640,20 +772,12 @@
                     ].
                 ].
 
-                bytes := ObjectMemory sizeOf:o.
-                infoArray := rawInfo at:class ifAbsent:[].
-                infoArray isNil ifTrue:[
-                    infoArray := Array 
-                            with:class 
-                            with:1 
-                            with:bytes
-                            with:bytes.
-                    rawInfo at:class put:infoArray.
-                ] ifFalse:[
-                    infoArray at:2 put:((infoArray at:2) + 1).
-                    infoArray at:3 put:((infoArray at:3) + bytes).
-                    infoArray at:4 put:((infoArray at:4) max: bytes).
-                ]
+                infoEntry := rawInfo at:class ifAbsent:nil.
+                infoEntry isNil ifTrue:[
+                    infoEntry := StatisticEntry new.
+                    rawInfo at:class put:infoEntry. 
+                ].
+                infoEntry addStatisticForInstance:o class:class.
             ].
         ] valueNowOrOnUnwindDo:[
             myProcess priority:myPriority.
@@ -661,11 +785,17 @@
     ]
 
     "Modified: / 19-09-1995 / 15:29:10 / claus"
-    "Modified: / 11-10-2007 / 14:46:55 / cg"
+    "Modified: / 05-05-2011 / 16:29:53 / cg"
 ! !
 
 !MemoryUsageView methodsFor:'realization'!
 
+pixelOrigin:a extent:b
+    super pixelOrigin:a extent:b
+
+    "Created: / 05-05-2011 / 17:01:06 / cg"
+!
+
 realize
     super realize.
     titleLabel origin:(list originRelativeTo:self) x @ 0.0.
@@ -675,12 +805,115 @@
     "Modified: 14.10.1997 / 21:03:52 / cg"
 ! !
 
+!MemoryUsageView::StatisticEntry methodsFor:'accessing'!
+
+averageSize
+    averageSize isNil ifTrue:[
+        averageSize := overallByteSize / instanceCount
+    ].
+    ^ averageSize.
+
+    "Created: / 05-05-2011 / 16:09:35 / cg"
+!
+
+classNameOrSymbol
+    ^ classNameOrSymbol
+!
+
+classNameStringInList
+    classNameOrSymbol == #Class ifTrue:[
+        ^ '<all classes>'
+    ].
+    classNameOrSymbol == #Metaclass ifTrue:[
+        ^ '<all metaclasses>'
+    ].
+    classNameOrSymbol == #PrivateMetaclass ifTrue:[
+        ^ '<all private meta classes>'
+    ].
+    classNameOrSymbol == #PrivateClass ifTrue:[
+        ^ '<all private classes>'
+    ].
+    classNameOrSymbol == #ObsoleteClass ifTrue:[
+        ^ '<all obsolete classes>'
+    ].
+    classNameOrSymbol == #NameSpace ifTrue:[
+        ^ '<all namespaces>'
+    ].
+    classNameOrSymbol isJavaClass ifTrue:[
+        ^ classNameOrSymbol fullName asString copyReplaceAll:$/ with:$.
+    ].
+    classNameOrSymbol isObsolete ifTrue:[
+        ^ classNameOrSymbol name , ' (obsolete)'
+    ].
+    ^ classNameOrSymbol "displayString" name
+
+    "Created: / 05-05-2011 / 16:32:58 / cg"
+!
+
+instanceAllocationRate
+    ^ instanceAllocationRate ? 0
+
+    "Modified: / 05-05-2011 / 17:10:50 / cg"
+!
+
+instanceAllocationRate:something
+    instanceAllocationRate := something.
+!
+
+instanceCount
+    ^ instanceCount
+!
+
+maxByteSize
+    ^ maxByteSize
+!
+
+memoryAllocationRate
+    ^ memoryAllocationRate ? 0
+
+    "Modified: / 05-05-2011 / 17:10:56 / cg"
+!
+
+memoryAllocationRate:something
+    memoryAllocationRate := something.
+!
+
+minByteSize
+    ^ minByteSize
+!
+
+overallByteSize
+    ^ overallByteSize
+! !
+
+!MemoryUsageView::StatisticEntry methodsFor:'updating'!
+
+addStatisticForInstance:o class:classNameOrSymbolArg
+    |bytes|
+
+    bytes := ObjectMemory sizeOf:o.
+    instanceCount isNil ifTrue:[
+        classNameOrSymbol := classNameOrSymbolArg.
+        overallByteSize := bytes.
+        minByteSize := maxByteSize := bytes.
+        instanceCount := 1.
+    ] ifFalse:[
+        overallByteSize := overallByteSize + bytes.
+        minByteSize := minByteSize min:bytes.
+        maxByteSize := maxByteSize max:bytes.
+        instanceCount := instanceCount + 1.
+    ].
+    averageSize := nil.
+
+    "Created: / 05-05-2011 / 16:04:42 / cg"
+! !
+
 !MemoryUsageView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/MemoryUsageView.st,v 1.53 2010-03-09 14:44:55 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/MemoryUsageView.st,v 1.54 2011-05-05 15:28:32 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/MemoryUsageView.st,v 1.53 2010-03-09 14:44:55 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/MemoryUsageView.st,v 1.54 2011-05-05 15:28:32 cg Exp $'
 ! !