VM Maker: VMMaker.oscog-eem.2278.mcz

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

VM Maker: VMMaker.oscog-eem.2278.mcz

commits-2
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2278.mcz

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

Name: VMMaker.oscog-eem.2278
Author: eem
Time: 13 November 2017, 4:18:45.220569 pm
UUID: 4fd41cee-a3bd-48f4-b02e-cf367a331eec
Ancestors: VMMaker.oscog-eem.2277

Spur:
Revise scavenger logging to collect data during the scavenge and log it to the file after the scavenge, hence including an accurate elapsed time.

Consequently nuke the log: methods in VMClass; they arent needed, which neatly avoids the issue of multiple classes needing to define logStream.

Slang:
Output the printf format string using the LP64/LLP64 convention in sqMemoryAccess.h

=============== Diff against VMMaker.oscog-eem.2277 ===============

Item was changed:
  ----- Method: BraceNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  "make a CCodeGenerator equivalent of me."
 
- "This is for varargs selectors (variants of printf:)"
- (elements notEmpty and: [elements allSatisfy: [:e| e isTemp]]) ifTrue:
- [^elements collect: [:elem| elem asTranslatorNodeIn: aTMethod]].
-
  "This is for case statements"
+ (elements allSatisfy:
- self assert: (elements allSatisfy:
  [:elem|
  elem isMessageNode
+ and: [elem selector key = #->]]) ifTrue:
+ [self assert: (elements allSatisfy:
+ [:elem|
+ elem receiver isBlockNode
+ and: [elem arguments first isBlockNode
+ and: [elem receiver isPotentialCCaseLabelIn: aTMethod]]]).
+ ^TBraceCaseNode new
+ caseLabels: (elements collect: [:elem| elem receiver asTranslatorNodeIn: aTMethod]);
+ cases: (elements collect: [:elem| elem arguments first asTranslatorNodeIn: aTMethod]);
+ comment: comment].
+
+ "This is for varargs selectors (variants of printf:)"
+ ^elements collect: [:elem| elem asTranslatorNodeIn: aTMethod]!
- and: [elem selector key = #->
- and: [elem receiver isBlockNode
- and: [elem arguments first isBlockNode
- and: [elem receiver isPotentialCCaseLabelIn: aTMethod]]]]]).
- ^TBraceCaseNode new
- caseLabels: (elements collect: [:elem| elem receiver asTranslatorNodeIn: aTMethod]);
- cases: (elements collect: [:elem| elem arguments first asTranslatorNodeIn: aTMethod]);
- comment: comment!

Item was added:
+ ----- Method: CCodeGenerator>>cLiteralForPrintfString: (in category 'C code generator') -----
+ cLiteralForPrintfString: aString
+ ^(('"', (PrintfFormatString new setFormat: aString) transformForVMMaker, '"')
+ copyReplaceAll: (String with: Character cr) with: '\n')
+ copyReplaceAll: (String with: Character tab) with: '\t'!

Item was added:
+ ----- Method: PrintfFormatDescriptor>>transformForVMMaker (in category '*VMMaker-C code generation') -----
+ transformForVMMaker
+ ^self printString!

Item was added:
+ ----- Method: PrintfFormatString>>transformForVMMaker (in category '*VMMaker-C code generation') -----
+ transformForVMMaker
+ [outputStream nextPutAll: string next.
+ format atEnd] whileFalse:
+ [outputStream nextPutAll: format next transformForVMMaker].
+ "any remainder is string, if so append to outputStream"
+ string atEnd ifFalse: [outputStream nextPutAll: string next].
+ ^outputStream contents!

Item was added:
+ ----- Method: PrintfNumberFormatDescriptor>>transformForVMMaker (in category '*VMMaker-C code generation') -----
+ transformForVMMaker
+ ('duxX' includes: operator) ifFalse:
+ [^super transformForVMMaker].
+ ^'%" PRI', (String with: operator), 'SQINT "'!

Item was changed:
  CogClass subclass: #SpurGenerationScavenger
+ instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize previousRememberedSetSize rememberedSetRedZone rememberedSetLimit refCountToShrinkRT weakList ephemeronList tenureCriterion tenureThreshold tenuringClassIndex tenuringProportion numRememberedEphemerons scavengeLog scavengeLogRecord statSurvivorCount statTenures'
- instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize previousRememberedSetSize rememberedSetRedZone rememberedSetLimit refCountToShrinkRT weakList ephemeronList tenureCriterion tenureThreshold tenuringClassIndex tenuringProportion numRememberedEphemerons scavengeLog statSurvivorCount statTenures'
  classVariableNames: ''
  poolDictionaries: 'SpurMemoryManagementConstants'
  category: 'VMMaker-SpurMemoryManager'!
 
  !SpurGenerationScavenger commentStamp: 'eem 11/7/2017 17:26' prior: 0!
  SpurGenerationScavenger is an implementation of David Ungar's Generation Scavenging garbage collection algorithm.  See
  Generation Scavenging, A Non-disruptive, High-Performance Storage Reclamation Algorithm
  David Ungar
  Proceeding
  SDE 1 Proceedings of the first ACM SIGSOFT/SIGPLAN software engineering symposium on Practical software development environments
  Pages 157 - 167
  ACM New York, NY, USA ©1984
 
  Also relevant are
  An adaptive tenuring policy for generation scavengers
  David Ungar & Frank Jackson
  ACM Transactions on Programming Languages and Systems (TOPLAS) TOPLAS Homepage archive
  Volume 14 Issue 1, Jan. 1992
  Pages 1 - 27
  ACM New York, NY, USA ©1992
  and
  Ephemerons: a new finalization mechanism
  Barry Hayes
  Proceedings of the 12th ACM SIGPLAN conference on Object-oriented programming, systems, languages, and applications
  Pages 176-183
  ACM New York, NY, USA ©1997
 
  See text below the variable definitions and explanation below for a full explanation of weak and ephemeron processing.
 
  Instance Variables
  coInterpreter: <StackInterpreterSimulator|CogVMSimulator>
  eden: <SpurNewSpaceSpace>
  ephemeronList: <Integer|nil>
  futureSpace: <SpurNewSpaceSpace>
  futureSurvivorStart: <Integer address>
  manager: <SpurMemoryManager|Spur32BitMMLESimulator et al>
  numRememberedEphemerons: <Integer>
  pastSpace: <SpurNewSpaceSpace>
  previousRememberedSetSize: <Integer>
  rememberedSet: <CArrayAccessor on: Array>
  rememberedSetSize: <Integer>
  tenuringProportion: <Float>
  tenuringThreshold: <Integer address>
  weakList: <Integer|nil>
 
  coInterpreter
  - the interpreter/vm, in this context, the mutator
 
  manager
  - the Spur memory manager
 
  eden
  - the space containing newly created objects
 
  futureSpace
  - the space to which surviving objects are copied during a scavenge
 
  futureSurvivorStart
  - the allocation pointer into futureSpace
 
  pastSpace
  - the space surviving objects live in until the next scavenge
 
  rememberedSet
  - the root old space objects that refer to objects in new space; a scavenge starts form these roots and the interpreter's stack
 
  rememberedSetSize
  - the size of the remembered set, also the first unused index in the rememberedSet
 
  previousRememberedSetSize:
  - the size of the remembered set before scavenging objects in future space.
 
  numRememberedEphemerons
  - the number of unscavenged ephemerons at the front of the rememberedSet.
 
  ephemeronList
  - the head of the list of corpses of unscavenged ephemerons reached in the current phase
 
  weakList
  - the head of the list of corpses of weak arrays reached during the scavenge.
 
  tenuringProportion
  - the amount of pastSpace below which the system will not tenure unless futureSpace fills up, and above which it will eagerly tenure
 
  tenuringThreshold
  - the pointer into pastSpace below which objects will be tenured
 
  Weakness and Ephemerality in the Scavenger.
  Weak arrays should not hold onto their referents (except from their strong fileds, their named inst vars).  Ephemerons are objects that implement instance-based finalization; attaching an ephemeron to an object keeps that object alive and causes the ephemeron to "fire" when the object is only reachable from the ephemeron (or other ephemerons & weak arrays).  They are a special kind of Associations that detect when their keys are about to die, i.e. when an ephemeron's key is not reachable from the roots except from weak arrays and other ephemerons with about-to-die keys.  Note that if an ephemeron's key is not about to die then references from the rest of the ephemeron can indeed prevent ephemeron keys from dying.
 
  The scavenger is concerned with collecting objects in new space, therefore it ony deals with weak arrays and ephemerons that are either in the remembered set or in new space.  By deferring scanning these objects until other reachable objects have been scavenged, the scavenger can detect dead or dying references.
 
  Weak Array Processing
  In the case of weak arrays this is simple.  The scavenger refuses to scavenge the referents of weak arrays in scavengeReferentsOf: until the entire scavenge is over.  It then scans the weak arrays in the remembered set and in future space and nils all fields in them that are referring to unforwarded objects in eden and past space, because these objects have not survived the scavenge.  The root weak arrays remaining to be scavenged are in the remembered table.  Surviving weak arrays in future space are collected on a list.  The list is threaded through the corpses of weak arrays in eden and/or past space.  weakList holds the slot offset of the first weak array found in eden and/or past space.  The next offset is stored in the weak array corpse's identityHash and format fields (22 bits & 5 bits of allocationUnits, for a max new space size of 2^28 bytes, 256Mb).  The list is threaded throguh corpses, but the surviving arrays are pointed to by the corpses' forwarding pointers.
 
  Ephemeron Processing
  The case of ephemerons is a little more complicated because an ephemeron's key should survive.  The scavenger is cyclical.  It scavenges the remembered set, which may copy and forward surviving objects in past and/or eden spaces to future space.  It then scavenges those promoted objects in future space until no more are promoted, which may in turn remember more objects.  The cycles continue until no more objects get promoted to future space and no more objects get remembered.  At this point all surviving objecta are in futureSpace.
 
  So if the scavenger does not scan ephemerons in the remembered set or in future space until the scavenger finishes cycling, it can detect ephemerons whose keys are about to die because these will be unforwarded objects in eden and/or past space.  Ephemerons encountered in the remembered set are either processed like ordinary objects if their keys have been promoted to futureSpace, or are moved to the front of the rememberedSet (because, dear reader, it is a sequence) if their keys have not been promoted.  Ephemerons encountered in scavengeReferentsOf: are either scanned like normal objects if their keys have been promoted, or added to the ephemeronList, organized identically to the weakList, if their keys are yet to be promoted.  Since references from other ephemerons with surviving keys to ephemeron keys can and should prevent the ephemerons whose keys they are from firing the scavenger does not fire ephemerons unless all unscavenged ephemerons have unscavenged keys.  So the unsca
 venged ephemerons (they will be at the beginning of the remembered set and on the ephemeronList) are scanned and any that have promoted keys are scavenged.  But if no unscavenged ephemerons have surviving keys then all the unscavenged ephemerons are fired and then scavenged.  This in turn may remember more objects and promote more objects to future space, and encounter more unscavenged ephemerons.  So the scavenger continues until no more objects are remembered, no more objects are promoted to future space and no more unscavenged ephemerons exist.!

Item was changed:
  ----- Method: SpurGenerationScavenger class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  #(eden futureSpace pastSpace) do:
  [:var| aCCodeGenerator var: var type: #SpurNewSpaceSpace].
  aCCodeGenerator
  var: #rememberedSet type: #'sqInt *';
  var: #tenuringProportion type: #double;
+ var: #scavengeLogRecord type: #SpurScavengeLogRecord;
  var: #scavengeLog type: #'FILE *'!

Item was changed:
  ----- Method: SpurGenerationScavenger>>initialize (in category 'initialization') -----
  initialize
  pastSpace := SpurNewSpaceSpace new.
  futureSpace := SpurNewSpaceSpace new.
  eden := SpurNewSpaceSpace new.
  rememberedSetSize := 0.
  tenureThreshold := 0.
+ statSurvivorCount := statTenures := 0.
+ scavengeLogRecord := SpurScavengeLogRecord new!
- statSurvivorCount := statTenures := 0!

Item was changed:
  ----- Method: SpurGenerationScavenger>>logEndScavenge (in category 'logging') -----
  logEndScavenge
  <inline: #always>
+ scavengeLogRecord
+ eSurvivorBytes: futureSurvivorStart - pastSpace start;
+ eRememberedSetSize: rememberedSetSize;
+ eStatTenures: statTenures!
- self log: ' survivor bytes: 0x%lx/%ld remembered objects: %ld tenured: %ld\n'
- with: futureSurvivorStart - pastSpace start
- with: futureSurvivorStart - pastSpace start
- with: rememberedSetSize
- with: statTenures;
- flushLog!

Item was added:
+ ----- Method: SpurGenerationScavenger>>logScavenge (in category 'logging') -----
+ logScavenge
+ <inline: #always>
+ scavengeLog ifNotNil:
+ [self writeScavengeLog]!

Item was changed:
  ----- Method: SpurGenerationScavenger>>logStartScavenge (in category 'logging') -----
  logStartScavenge
  <inline: #always>
+ scavengeLogRecord
+ sEdenBytes: manager freeStart - eden start;
+ sPastBytes: manager pastSpaceStart - pastSpace start;
+ sRememberedSetSize: rememberedSetSize;
+ sRememberedSetRedZone: rememberedSetRedZone;
+ sRememberedSetLimit: rememberedSetLimit;
+ sStatTenures: statTenures!
- self log: 'scavenge %ld eden bytes: 0x%lx/%ld past bytes: 0x%lx/%ld\n\tremembered set: %ld redzone: %ld size: %ld\n'
- with: manager statScavenges
- with: manager freeStart - eden start
- with: manager freeStart - eden start
- with: manager pastSpaceStart - pastSpace start
- with: manager pastSpaceStart - pastSpace start
- with: rememberedSetSize
- with: rememberedSetRedZone
- with: rememberedSetLimit!

Item was changed:
  ----- Method: SpurGenerationScavenger>>logTenuringPolicy (in category 'logging') -----
  logTenuringPolicy
  <inline: #always>
+ scavengeLogRecord
+ tTenureCriterion: tenureCriterion;
+ tTenureThreshold: ((tenureCriterion = TenureByAge and: [tenureThreshold > pastSpace start])
+ ifTrue: [tenureThreshold - pastSpace start]
+ ifFalse: [0]);
+ tRefCountToShrinkRT: refCountToShrinkRT!
- | policyNames |
- <var: 'policyNames' declareC: 'static char *policyNames[] = {"", "by age", "by class", "to shrink rt", "don''t tenure", "mark on tenure"}'>
- self cCode: []
- inSmalltalk: [policyNames := CLiteralArray on: #('' 'by age' 'by class' 'to shrink rt' 'don''t tenure' 'mark on tenure')].
- self log: (tenureCriterion = TenureToShrinkRT ifFalse: [' tenure below 0x%lx/%ld %s\n'] ifTrue: [' tenure below 0x%lx/%ld %s refct %ld\n'])
- with: ((tenureCriterion = TenureByAge and: [tenureThreshold > pastSpace start]) ifTrue: [tenureThreshold - pastSpace start] ifFalse: [0])
- with: ((tenureCriterion = TenureByAge and: [tenureThreshold > pastSpace start]) ifTrue: [tenureThreshold - pastSpace start] ifFalse: [0])
- with: (policyNames at: tenureCriterion)
- with: refCountToShrinkRT!

Item was added:
+ ----- Method: SpurGenerationScavenger>>writeScavengeLog (in category 'logging') -----
+ writeScavengeLog
+ "Output the entire record."
+ <inline: #never>
+ | policyNames |
+ <var: 'policyNames' declareC: 'static char *policyNames[] = {"", "by age", "by class", "to shrink rt", "don''t tenure", "mark on tenure"}'>
+ self cCode: []
+ inSmalltalk: [policyNames := CLiteralArray on: #('' 'by age' 'by class' 'to shrink rt' 'don''t tenure' 'mark on tenure')].
+ scavengeLog "log data collected by logStartScavenge"
+ f: 'scavenge %ld eden bytes: 0x%lx/%ld past bytes: 0x%lx/%ld\n\trem set: %ld redzone: %ld size: %ld\n'
+ printf:{ manager statScavenges.
+ scavengeLogRecord sEdenBytes.
+ scavengeLogRecord sEdenBytes.
+ scavengeLogRecord sPastBytes.
+ scavengeLogRecord sPastBytes.
+ scavengeLogRecord sRememberedSetSize.
+ scavengeLogRecord sRememberedSetRedZone.
+ scavengeLogRecord sRememberedSetLimit }.
+ scavengeLog "log data collected by logTenuringPolicy"
+ f: (scavengeLogRecord tTenureCriterion = TenureToShrinkRT
+ ifFalse: [' tenure below 0x%lx/%ld %s\n']
+ ifTrue: [' tenure below 0x%lx/%ld %s refct %ld\n'])
+ printf:{ scavengeLogRecord tTenureThreshold.
+ scavengeLogRecord tTenureThreshold.
+ policyNames at: scavengeLogRecord tTenureCriterion.
+ scavengeLogRecord tRefCountToShrinkRT }.
+ scavengeLog "log data collected by logEndScavenge"
+ f: ' survivor bytes: 0x%lx/%ld rem set: %ld tenured: %ld usecs: %ld\n'
+ printf:{ scavengeLogRecord eSurvivorBytes.
+ scavengeLogRecord eSurvivorBytes.
+ scavengeLogRecord eRememberedSetSize.
+ scavengeLogRecord eStatTenures - scavengeLogRecord sStatTenures.
+ manager statSGCDeltaUsecs asUnsignedLong }.
+ scavengeLog fflush!

Item was changed:
  ----- Method: SpurMemoryManager class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  initializationOptions ifNil: [initializationOptions := options].
+ ^{ SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo. self compactorClass },
- ^{ SpurGenerationScavenger. SpurSegmentManager. SpurSegmentInfo. self compactorClass },
  SpurNewSpaceSpace withAllSubclasses!

Item was changed:
  ----- Method: SpurMemoryManager>>scavengingGCTenuringIf: (in category 'gc - scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
  "Run the scavenger."
  <inline: false>
  self assert: remapBufferCount = 0.
  (self asserta: scavenger eden limit - freeStart > coInterpreter interpreterAllocationReserveBytes) ifFalse:
  [coInterpreter tab;
  printNum: scavenger eden limit - freeStart; space;
  printNum: coInterpreter interpreterAllocationReserveBytes; space;
  printNum: coInterpreter interpreterAllocationReserveBytes - (scavenger eden limit - freeStart); cr].
  self checkMemoryMap.
  self checkFreeSpace: GCModeNewSpace.
  self runLeakCheckerFor: GCModeNewSpace.
 
  coInterpreter
  preGCAction: GCModeNewSpace;
  "would prefer this to be in mapInterpreterOops, but
  compatibility with ObjectMemory dictates it goes here."
  flushMethodCacheFrom: newSpaceStart to: newSpaceLimit.
  needGCFlag := false.
 
  gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
 
  self doScavenge: tenuringCriterion.
 
  statScavenges := statScavenges + 1.
  statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
  statRootTableCount := scavenger rememberedSetSize.
 
+ scavenger logScavenge.
+
  coInterpreter postGCAction: GCModeNewSpace.
 
  self runLeakCheckerFor: GCModeNewSpace.
  self checkFreeSpace: GCModeNewSpace!

Item was added:
+ VMStructType subclass: #SpurScavengeLogRecord
+ instanceVariableNames: 'sEdenBytes sPastBytes sRememberedSetSize sRememberedSetRedZone sRememberedSetLimit sStatTenures tTenureCriterion tTenureThreshold tRefCountToShrinkRT eSurvivorBytes eRememberedSetSize eStatTenures'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'VMMaker-SpurMemoryManager'!

Item was added:
+ ----- Method: SpurScavengeLogRecord class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
+ instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ self allInstVarNames do:
+ [:ivn|
+ (SpurMemoryManager isNonArgumentImplicitReceiverVariableName: ivn) ifFalse:
+ [aBinaryBlock value: ivn value: #usqInt]]!

Item was added:
+ ----- Method: SpurScavengeLogRecord>>eRememberedSetSize (in category 'accessing') -----
+ eRememberedSetSize
+
+ ^ eRememberedSetSize
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>eRememberedSetSize: (in category 'accessing') -----
+ eRememberedSetSize: anObject
+
+ ^ eRememberedSetSize := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>eStatTenures (in category 'accessing') -----
+ eStatTenures
+
+ ^ eStatTenures
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>eStatTenures: (in category 'accessing') -----
+ eStatTenures: anObject
+
+ ^ eStatTenures := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>eSurvivorBytes (in category 'accessing') -----
+ eSurvivorBytes
+
+ ^ eSurvivorBytes
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>eSurvivorBytes: (in category 'accessing') -----
+ eSurvivorBytes: anObject
+
+ ^ eSurvivorBytes := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sEdenBytes (in category 'accessing') -----
+ sEdenBytes
+
+ ^ sEdenBytes
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sEdenBytes: (in category 'accessing') -----
+ sEdenBytes: anObject
+
+ ^ sEdenBytes := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sPastBytes (in category 'accessing') -----
+ sPastBytes
+
+ ^ sPastBytes
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sPastBytes: (in category 'accessing') -----
+ sPastBytes: anObject
+
+ ^ sPastBytes := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sRememberedSetLimit (in category 'accessing') -----
+ sRememberedSetLimit
+
+ ^ sRememberedSetLimit
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sRememberedSetLimit: (in category 'accessing') -----
+ sRememberedSetLimit: anObject
+
+ ^ sRememberedSetLimit := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sRememberedSetRedZone (in category 'accessing') -----
+ sRememberedSetRedZone
+
+ ^ sRememberedSetRedZone
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sRememberedSetRedZone: (in category 'accessing') -----
+ sRememberedSetRedZone: anObject
+
+ ^ sRememberedSetRedZone := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sRememberedSetSize (in category 'accessing') -----
+ sRememberedSetSize
+
+ ^ sRememberedSetSize
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sRememberedSetSize: (in category 'accessing') -----
+ sRememberedSetSize: anObject
+
+ ^ sRememberedSetSize := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sStatTenures (in category 'accessing') -----
+ sStatTenures
+
+ ^ sStatTenures
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>sStatTenures: (in category 'accessing') -----
+ sStatTenures: anObject
+
+ ^ sStatTenures := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>tRefCountToShrinkRT (in category 'accessing') -----
+ tRefCountToShrinkRT
+
+ ^ tRefCountToShrinkRT
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>tRefCountToShrinkRT: (in category 'accessing') -----
+ tRefCountToShrinkRT: anObject
+
+ ^ tRefCountToShrinkRT := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>tTenureCriterion (in category 'accessing') -----
+ tTenureCriterion
+
+ ^ tTenureCriterion
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>tTenureCriterion: (in category 'accessing') -----
+ tTenureCriterion: anObject
+
+ ^ tTenureCriterion := anObject.
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>tTenureThreshold (in category 'accessing') -----
+ tTenureThreshold
+
+ ^ tTenureThreshold
+ !

Item was added:
+ ----- Method: SpurScavengeLogRecord>>tTenureThreshold: (in category 'accessing') -----
+ tTenureThreshold: anObject
+
+ ^ tTenureThreshold := anObject.
+ !

Item was added:
+ ----- Method: TConstantNode>>asPrintfFormatStringNode (in category 'transformations') -----
+ asPrintfFormatStringNode
+ ^TPrintfFormatStringNode new
+ setValue: value;
+ comment: comment;
+ yourself!

Item was changed:
  ----- Method: TMethod>>prepareMethodIn: (in category 'transformations') -----
  prepareMethodIn: aCodeGen
  "Record sends of builtin operators, map sends of the special selector dispatchOn:in:
  with case statement nodes, and map sends of caseOf:[otherwise:] to switch statements.
  Declare limit variables for to:[by:]do: loops with limits that potentially have side-effects.
  As a hack also update the types of variables introduced to implement cascades correctly.
  This has to be done at the same time as this is done, so why not piggy back here?"
  extraVariableNumber ifNotNil:
  [declarations keysAndValuesDo:
  [:varName :decl|
  decl isBlock ifTrue:
  [self assert: ((varName beginsWith: 'cascade') and: [varName last isDigit]).
  locals add: varName.
  self declarationAt: varName
  put: (decl value: self value: aCodeGen), ' ', varName]]].
  aCodeGen
  pushScope: declarations
  while:"N.B.  nodesWithParentsDo: is bottom-up, hence replacement is destructive and conserved."
  [parseTree nodesWithParentsDo:
  [:node :parent|
  node isSend ifTrue:
  [(aCodeGen isBuiltinSelector: node selector)
  ifTrue:
  [node isBuiltinOperator: true.
  "If a to:by:do:'s limit has side-effects, declare the limit variable, otherwise delete it from the args"
  node selector = #to:by:do: ifTrue:
  [self ensureToByDoLoopLimitIsSafeAndEfficient: node in: aCodeGen]]
  ifFalse:
  [(CaseStatements includes: node selector) ifTrue:
  [parent replaceNodesIn: (Dictionary newFromPairs: { node. self buildCaseStmt: node in: aCodeGen})].
  (#(caseOf: #caseOf:otherwise:) includes: node selector) ifTrue:
+ [parent replaceNodesIn: (Dictionary newFromPairs: { node. self buildSwitchStmt: node parent: parent })].
+ (#(printf: f:printf:) includes: node selector) ifTrue:
+ [| map |
+ map := Dictionary new.
+ node nodesDo:
+ [:subNode|
+ (subNode isConstant and: [subNode value isString and: [subNode value includes: $%]]) ifTrue:
+ [map at: subNode put: subNode asPrintfFormatStringNode].
+ node replaceNodesIn: map]]]]]]!
- [parent replaceNodesIn: (Dictionary newFromPairs: { node. self buildSwitchStmt: node parent: parent })]]]]]!

Item was added:
+ TConstantNode subclass: #TPrintfFormatStringNode
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'VMMaker-Translation to C'!

Item was added:
+ ----- Method: TPrintfFormatStringNode>>emitCCodeOn:level:generator: (in category 'C code generation') -----
+ emitCCodeOn: aStream level: level generator: aCodeGen
+ "Transform the printf string according to the LP64/LLP64 convention in sqMemoryAccess.h."
+ aStream nextPutAll: (aCodeGen cLiteralForPrintfString: value).
+ comment ifNotNil:
+ [aStream
+ nextPutAll: ' /* ';
+ nextPutAll: comment;
+ nextPutAll: ' */']!

Item was changed:
  ----- Method: VMClass>>f:open: (in category 'printf logging') -----
  f: logFilename open: mode
  "Simulate a FILE stream by answering a transcript.
+ Can be used with the f:printf: method."
- Can be used with the log:* methods."
  <doNotGenerate>
  ^true
  ifTrue: [(TranscriptStream on: (String new: 100000))
  openLabel: logFilename;
  yourself]
  ifFalse: [self coInterpreter transcript]!

Item was removed:
- ----- Method: VMClass>>flushLog (in category 'printf logging') -----
- flushLog
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream fflush]!

Item was removed:
- ----- Method: VMClass>>log: (in category 'printf logging') -----
- log: printfString
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [printfString fprintf: self logStream]!

Item was removed:
- ----- Method: VMClass>>log:with: (in category 'printf logging') -----
- log: printfString with: anArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {anArgument}]!

Item was removed:
- ----- Method: VMClass>>log:with:with: (in category 'printf logging') -----
- log: printfString with: aArgument with: bArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {aArgument. bArgument}]!

Item was removed:
- ----- Method: VMClass>>log:with:with:with: (in category 'printf logging') -----
- log: printfString with: aArgument with: bArgument with: cArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {aArgument. bArgument. cArgument}]!

Item was removed:
- ----- Method: VMClass>>log:with:with:with:with: (in category 'printf logging') -----
- log: printfString with: aArgument with: bArgument with: cArgument with: dArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {aArgument. bArgument. cArgument. dArgument}]!

Item was removed:
- ----- Method: VMClass>>log:with:with:with:with:with: (in category 'printf logging') -----
- log: printfString with: aArgument with: bArgument with: cArgument with: dArgument with: eArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {aArgument. bArgument. cArgument. dArgument. eArgument}]!

Item was removed:
- ----- Method: VMClass>>log:with:with:with:with:with:with: (in category 'printf logging') -----
- log: printfString with: aArgument with: bArgument with: cArgument with: dArgument with: eArgument with: fArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {aArgument. bArgument. cArgument. dArgument. eArgument. fArgument}]!

Item was removed:
- ----- Method: VMClass>>log:with:with:with:with:with:with:with: (in category 'printf logging') -----
- log: printfString with: aArgument with: bArgument with: cArgument with: dArgument with: eArgument with: fArgument with: gArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {aArgument. bArgument. cArgument. dArgument. eArgument. fArgument. gArgument}]!

Item was removed:
- ----- Method: VMClass>>log:with:with:with:with:with:with:with:with: (in category 'printf logging') -----
- log: printfString with: aArgument with: bArgument with: cArgument with: dArgument with: eArgument with: fArgument with: gArgument with: hArgument
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: {aArgument. bArgument. cArgument. dArgument. eArgument. fArgument. gArgument. hArgument}]!

Item was removed:
- ----- Method: VMClass>>log:withArgs: (in category 'printf logging') -----
- log: printfString withArgs: arguments
- "Log via printf-style format strings.  Subclasses must implement logStream to answer their log stream/file."
- <inline: #always>
- self logStream ifNotNil:
- [self logStream f: printfString printf: arguments]!