The Trunk: System-ar.337.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: System-ar.337.mcz

commits-2
Andreas Raab uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-ar.337.mcz

==================== Summary ====================

Name: System-ar.337
Author: ar
Time: 14 June 2010, 10:11:02.785 pm
UUID: 8b2d2b21-0966-5943-a985-a8c9b8e019e9
Ancestors: System-nice.336

Remove positively ancient j3 support that hasn't been used in too many years.

=============== Diff against System-nice.336 ===============

Item was changed:
  ----- Method: SmalltalkImage>>vmStatisticsReportString (in category 'vm statistics') -----
  vmStatisticsReportString
  "StringHolderView open: (StringHolder new contents:
  SmalltalkImage current vmStatisticsReportString) label: 'VM Statistics'"
 
+ | params oldSpaceEnd youngSpaceEnd memoryEnd fullGCs fullGCTime incrGCs incrGCTime tenureCount upTime upTime2 fullGCs2 fullGCTime2 incrGCs2 incrGCTime2 tenureCount2 str |
- | params oldSpaceEnd youngSpaceEnd memoryEnd fullGCs fullGCTime incrGCs incrGCTime tenureCount mcMisses mcHits icHits upTime sendCount tms tmSize upTime2 fullGCs2 fullGCTime2 incrGCs2 incrGCTime2 tenureCount2 str |
  params := self getVMParameters.
  oldSpaceEnd := params at: 1.
  youngSpaceEnd := params at: 2.
  memoryEnd := params at: 3.
  fullGCs := params at: 7.
  fullGCTime := params at: 8.
  incrGCs := params at: 9.
  incrGCTime := params at: 10.
  tenureCount := params at: 11.
- mcMisses := params at: 15.
- mcHits := params at: 16.
- icHits := params at: 17.
  upTime := Time millisecondClockValue.
- sendCount := mcMisses + mcHits + icHits.
- tms := TranslatedMethod allSubInstances.
- tmSize := tms inject: 0 into: [:sum :tm | sum + (tm size * 4)].
 
  str := WriteStream on: (String new: 1000).
  str nextPutAll: 'uptime ';
  print: (upTime / 1000 / 60 // 60); nextPut: $h;
  print: (upTime / 1000 / 60 \\ 60) asInteger; nextPut: $m;
  print: (upTime / 1000 \\ 60) asInteger; nextPut: $s; cr.
 
  str nextPutAll: 'memory ';
  nextPutAll: memoryEnd asStringWithCommas; nextPutAll: ' bytes'; cr.
  str nextPutAll: ' old ';
  nextPutAll: oldSpaceEnd asStringWithCommas; nextPutAll: ' bytes (';
  print: ((oldSpaceEnd / memoryEnd * 100) roundTo: 0.1); nextPutAll: '%)'; cr.
  str nextPutAll: ' young ';
  nextPutAll: (youngSpaceEnd - oldSpaceEnd) asStringWithCommas; nextPutAll: ' bytes (';
  print: ((youngSpaceEnd - oldSpaceEnd / memoryEnd * 100) roundTo: 0.1); nextPutAll: '%)'; cr.
  str nextPutAll: ' used ';
  nextPutAll: youngSpaceEnd asStringWithCommas; nextPutAll: ' bytes (';
  print: ((youngSpaceEnd / memoryEnd * 100) roundTo: 0.1); nextPutAll: '%)'; cr.
  str nextPutAll: ' free ';
  nextPutAll: (memoryEnd - youngSpaceEnd) asStringWithCommas; nextPutAll: ' bytes (';
  print: ((memoryEnd - youngSpaceEnd / memoryEnd * 100) roundTo: 0.1); nextPutAll: '%)'; cr.
 
  str nextPutAll: 'GCs ';
  nextPutAll: (fullGCs + incrGCs) asStringWithCommas.
  fullGCs + incrGCs > 0 ifTrue: [
  str
  nextPutAll: ' (';
  print: ((upTime / (fullGCs + incrGCs)) roundTo: 1);
  nextPutAll: 'ms between GCs)'
  ].
  str cr.
  str nextPutAll: ' full ';
  print: fullGCs; nextPutAll: ' totalling '; nextPutAll: fullGCTime asStringWithCommas; nextPutAll: 'ms (';
  print: ((fullGCTime / upTime * 100) roundTo: 1.0);
  nextPutAll: '% uptime)'.
  fullGCs = 0 ifFalse:
  [str nextPutAll: ', avg '; print: ((fullGCTime / fullGCs) roundTo: 1.0); nextPutAll: 'ms'].
  str cr.
  str nextPutAll: ' incr ';
  print: incrGCs; nextPutAll: ' totalling '; nextPutAll: incrGCTime asStringWithCommas; nextPutAll: 'ms (';
  print: ((incrGCTime / upTime * 100) roundTo: 1.0);
  nextPutAll: '% uptime), avg '; print: ((incrGCTime / incrGCs) roundTo: 1.0); nextPutAll: 'ms'; cr.
  str nextPutAll: ' tenures ';
  nextPutAll: tenureCount asStringWithCommas.
  tenureCount = 0 ifFalse:
  [str nextPutAll: ' (avg '; print: (incrGCs / tenureCount) asInteger; nextPutAll: ' GCs/tenure)'].
  str cr.
 
  LastStats ifNil: [LastStats := Array new: 6]
  ifNotNil: [
  upTime2 := upTime - (LastStats at: 1).
  fullGCs2 := fullGCs - (LastStats at: 2).
  fullGCTime2 := fullGCTime - (LastStats at: 3).
  incrGCs2 := incrGCs - (LastStats at: 4).
  incrGCTime2 := incrGCTime - (LastStats at: 5).
  tenureCount2 := tenureCount - (LastStats at: 6).
 
  str nextPutAll: self textMarkerForShortReport ;
  nextPutAll: (fullGCs2 + incrGCs2) asStringWithCommas.
  fullGCs2 + incrGCs2 > 0 ifTrue: [
  str
  nextPutAll: ' (';
  print: ((upTime2 / (fullGCs2 + incrGCs2)) roundTo: 1);
  nextPutAll: 'ms between GCs)'.
  ].
  str cr.
  str nextPutAll: ' uptime '; print: ((upTime2 / 1000.0) roundTo: 0.1); nextPutAll: 's'; cr.
  str nextPutAll: ' full ';
  print: fullGCs2; nextPutAll: ' totalling '; nextPutAll: fullGCTime2 asStringWithCommas; nextPutAll: 'ms (';
  print: ((fullGCTime2 / upTime2 * 100) roundTo: 1.0);
  nextPutAll: '% uptime)'.
  fullGCs2 = 0 ifFalse:
  [str nextPutAll: ', avg '; print: ((fullGCTime2 / fullGCs2) roundTo: 1.0); nextPutAll: 'ms'].
  str cr.
  str nextPutAll: ' incr ';
  print: incrGCs2; nextPutAll: ' totalling '; nextPutAll: incrGCTime2 asStringWithCommas; nextPutAll: 'ms (';
  print: ((incrGCTime2 / upTime2 * 100) roundTo: 1.0);
  nextPutAll: '% uptime), avg '.
  incrGCs2 > 0 ifTrue: [
  str print: ((incrGCTime2 / incrGCs2) roundTo: 1.0); nextPutAll: 'ms'
  ].
  str cr.
  str nextPutAll: ' tenures ';
  nextPutAll: tenureCount2 asStringWithCommas.
  tenureCount2 = 0 ifFalse:
  [str nextPutAll: ' (avg '; print: (incrGCs2 / tenureCount2) asInteger; nextPutAll: ' GCs/tenure)'].
  str cr.
  ].
  LastStats at: 1 put: upTime.
  LastStats at: 2 put: fullGCs.
  LastStats at: 3 put: fullGCTime.
  LastStats at: 4 put: incrGCs.
  LastStats at: 5 put: incrGCTime.
  LastStats at: 6 put: tenureCount.
 
- sendCount > 0 ifTrue: [
- str nextPutAll: 'sends ';
- nextPutAll: sendCount asStringWithCommas; cr.
- str nextPutAll: ' full ';
- nextPutAll: mcMisses asStringWithCommas;
- nextPutAll: ' ('; print: ((mcMisses / sendCount * 100) roundTo: 0.1); nextPutAll: '%)'; cr.
- str nextPutAll: ' m-cache ';
- nextPutAll: mcHits asStringWithCommas;
- nextPutAll: ' ('; print: ((mcHits / sendCount * 100) roundTo: 0.1); nextPutAll: '%)'; cr.
- str nextPutAll: ' i-cache ';
- nextPutAll: icHits asStringWithCommas;
- nextPutAll: ' ('; print: ((icHits / sendCount * 100) roundTo: 0.1); nextPutAll: '%)'; cr].
-
- icHits > 0 ifTrue: [
- str nextPutAll: 'methods ';
- nextPutAll: tms size asStringWithCommas; nextPutAll: ' translated'; cr.
- str nextPutAll: ' size ';
- nextPutAll: tmSize asStringWithCommas; nextPutAll: ' bytes, avg ';
- print: ((tmSize / tms size) roundTo: 0.1); nextPutAll: ' bytes/method'; cr.
- str nextPutAll: ' memory ';
- print: ((tmSize / youngSpaceEnd * 100) roundTo: 0.1); nextPutAll: '% of used, ';
- print: ((tmSize / memoryEnd * 100) roundTo: 0.1); nextPutAll: '% of available'; cr].
-
  ^ str contents
  !

Item was changed:
  ----- Method: SmalltalkImage>>recreateSpecialObjectsArray (in category 'special objects') -----
  recreateSpecialObjectsArray
  "Smalltalk recreateSpecialObjectsArray"
  "The Special Objects Array is an array of object pointers used
  by the
  Squeak virtual machine. Its contents are critical and
  unchecked, so don't even think of playing here unless you
  know what you are doing."
  | newArray |
  newArray := Array new: 56.
  "Nil false and true get used throughout the interpreter"
  newArray at: 1 put: nil.
  newArray at: 2 put: false.
  newArray at: 3 put: true.
  "This association holds the active process (a ProcessScheduler)"
  newArray at: 4 put: (self associationAt: #Processor).
  "Numerous classes below used for type checking and instantiation"
  newArray at: 5 put: Bitmap.
  newArray at: 6 put: SmallInteger.
  newArray at: 7 put: ByteString.
  newArray at: 8 put: Array.
  newArray at: 9 put: Smalltalk.
  newArray at: 10 put: Float.
  newArray at: 11 put: MethodContext.
  newArray at: 12 put: BlockContext.
  newArray at: 13 put: Point.
  newArray at: 14 put: LargePositiveInteger.
  newArray at: 15 put: Display.
  newArray at: 16 put: Message.
  newArray at: 17 put: CompiledMethod.
  newArray at: 18 put: (self specialObjectsArray at: 18).
  "(low space Semaphore)"
  newArray at: 19 put: Semaphore.
  newArray at: 20 put: Character.
  newArray at: 21 put: #doesNotUnderstand:.
  newArray at: 22 put: #cannotReturn:.
  newArray at: 23 put: nil.
  "An array of the 32 selectors that are compiled as special bytecodes,
  paired alternately with the number of arguments each takes."
  newArray at: 24 put: #( #+ 1 #- 1 #< 1 #> 1 #<= 1 #>= 1 #= 1 #~= 1
  #* 1 #/ 1 #\\ 1 #@ 1 #bitShift: 1 #// 1 #bitAnd: 1 #bitOr: 1
  #at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #== 1 #class 0
  #blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0 ).
  "An array of the 255 Characters in ascii order."
  newArray at: 25 put: ((0 to: 255) collect: [:ascii | Character value: ascii]).
  newArray at: 26 put: #mustBeBoolean.
  newArray at: 27 put: ByteArray.
  newArray at: 28 put: Process.
  "An array of up to 31 classes whose instances will have compact headers"
  newArray at: 29 put: self compactClassesArray.
  newArray at: 30 put: (self specialObjectsArray at: 30).
  "(delay Semaphore)"
  newArray at: 31 put: (self specialObjectsArray at: 31).
  "(user interrupt Semaphore)"
  "Prototype instances that can be copied for fast initialization"
  newArray at: 32 put: (Float new: 2).
  newArray at: 33 put: (LargePositiveInteger new: 4).
  newArray at: 34 put: Point new.
  newArray at: 35 put: #cannotInterpret:.
  "Note: This must be fixed once we start using context prototypes (yeah, right)"
  "(MethodContext new: CompiledMethod fullFrameSize)."
  newArray at: 36 put: (self specialObjectsArray at: 36). "Is the prototype MethodContext (unused by the VM)"
  newArray at: 37 put: BlockClosure.
  "(BlockContext new: CompiledMethod fullFrameSize)."
  newArray at: 38 put: (self specialObjectsArray at: 38). "Is the prototype BlockContext (unused by the VM)"
+ newArray at: 39 put: (Smalltalk specialObjectsArray at: 39). "preserve external semaphores"
+
+ "--- obsolete J3 support (could be recycled) ---"
+ newArray at: 40 put: (Smalltalk at: #PseudoContext ifAbsent:[nil]).
+ newArray at: 41 put: (Smalltalk at: #TranslatedMethod ifAbsent:[nil]).
+
- newArray at: 39 put: (self specialObjectsArray at: 39). "preserve external semaphores"
- "array of objects referred to by external code"
- newArray at: 40 put: PseudoContext.
- newArray at: 41 put: TranslatedMethod.
  "finalization Semaphore"
  newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil: [Semaphore new]).
  newArray at: 43 put: LargeNegativeInteger.
  "External objects for callout.
  Note: Written so that one can actually completely remove the FFI."
  newArray at: 44 put: (self at: #ExternalAddress ifAbsent: []).
  newArray at: 45 put: (self at: #ExternalStructure ifAbsent: []).
  newArray at: 46 put: (self at: #ExternalData ifAbsent: []).
  newArray at: 47 put: (self at: #ExternalFunction ifAbsent: []).
  newArray at: 48 put: (self at: #ExternalLibrary ifAbsent: []).
  newArray at: 49 put: #aboutToReturn:through:.
  newArray at: 50 put: #run:with:in:.
  "Entries 51 through 55 are for Alien support"
  newArray at: 51 put: nil.
  newArray at: 52 put: nil.
  newArray at: 53 put: (self at: #Alien ifAbsent: []).
  newArray at: 54 put: #invokeCallback:stack:registers:jmpbuf:.
  newArray at: 55 put: (self at: #UnsafeAlien ifAbsent: []).
  "Weak reference finalization"
  newArray at: 56 put: (self at: #WeakFinalizer ifAbsent: []).
  "Now replace the interpreter's reference in one atomic operation"
  self specialObjectsArray become: newArray!