[Vm-dev] VM Maker: VMMaker.oscog-eem.1916.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Aug 15 18:36:37 UTC 2016


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

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

Name: VMMaker.oscog-eem.1916
Author: eem
Time: 15 August 2016, 11:34:30.068659 am
UUID: d6becd10-57b4-4448-9af1-ed75251fa141
Ancestors: VMMaker.oscog-eem.1915

Fix Spur machine-code shallowCopy for 64-bits.  Enable it for 32-bits.

Improve printContext: to include the Cog method if it exists.

Spur:
Add a facility to record where scavenged objects originated so that one can track back to find a previous location of a scavenged object.

Improve the CoInterpreter simulator's utilitiesMenu.  Fix printHexnp: to accept a CogMethod proxy.

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

Item was added:
+ ----- Method: CoInterpreter>>printMethodFieldForPrintContext: (in category 'debug printing') -----
+ printMethodFieldForPrintContext: aContext
+ 	<inline: true>
+ 	| meth |
+ 	meth := objectMemory fetchPointer: MethodIndex ofObject: aContext.
+ 	(self methodHasCogMethod: meth) ifTrue:
+ 		[self printHexnp: (self cogMethodOf: meth); space].
+ 	self shortPrintOop: meth.!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveShallowCopy (in category 'primitive generators') -----
  genPrimitiveShallowCopy
  	"Implement primitiveShallowCopy/primitiveClone for convenient cases:
  	- the receiver is not a context
  	- the receiver is not a compiled method
  	- the result fits in eden (actually below scavengeThreshold)"
  
  	| formatReg resultReg slotsReg ptrReg
  	  jumpImmediate jumpIsMethod jumpVariable jumpTooBig jumpEmpty jumpNoSpace
  	  continuance copyLoop |
  	<var: #continue type: #'AbstractInstruction *'>
  	<var: #copyLoop type: #'AbstractInstruction *'>
  	<var: #jumpTooBig type: #'AbstractInstruction *'>
  	<var: #jumpVariable type: #'AbstractInstruction *'>
  	<var: #jumpNoSpace type: #'AbstractInstruction *'>
  	<var: #jumpIsMethod type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 
- 	true ifTrue: [^UnimplementedPrimitive].
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	resultReg := Arg0Reg.
  	slotsReg := Arg1Reg.
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: resultReg.
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self genGetFormatOf: ReceiverResultReg
  		into: (ptrReg := formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
  
  	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
  	jumpIsMethod := cogit JumpAboveOrEqual: 0.
  	cogit CmpCq: objectMemory indexablePointersFormat R: formatReg.
  	jumpVariable := cogit JumpZero: 0.
  	continuance := cogit Label.
  
  	self genGetRawSlotSizeOfNonImm: ReceiverResultReg into: slotsReg.
  	cogit CmpCq: objectMemory numSlotsMask R: slotsReg.
  	jumpTooBig := cogit JumpZero: 0.
  
  	cogit CmpCq: 0 R: slotsReg.
  	jumpEmpty := cogit JumpZero: 0.
  
  	"round up to allocationUnit"
  	cogit
  		MoveR: slotsReg R: TempReg;
  		AndCq: 1 R: TempReg;
  		AddR: TempReg R: slotsReg;
  		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: slotsReg;
  		LogicalShiftLeftCq: objectMemory shiftForWord R: slotsReg;
  	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
  		AddR: resultReg R: slotsReg;
  		CmpCq: objectMemory getScavengeThreshold R: slotsReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	cogit
  		MoveR: resultReg R: ptrReg;
  	"write back new freeStart; get result. slotsReg holds new freeStart, the limit of the object"
  		MoveR: slotsReg Aw: objectMemory freeStartAddress;
  	"set up loop bounds"
  		SubCq: objectMemory wordSize * 2 R: slotsReg;
  	"copy header, masking off irrelevant bits"
  		MoveMw: 0 r: ReceiverResultReg R: TempReg;
  		AndCq: objectMemory formatMask << objectMemory formatShift + objectMemory classIndexMask R: TempReg;
  		MoveR: TempReg Mw: 0 r: resultReg;
  		MoveMw: objectMemory wordSize r: ReceiverResultReg R: TempReg;
  		AndCq: objectMemory numSlotsMask << objectMemory numSlotsHalfShift R: TempReg;
  		MoveR: TempReg Mw: objectMemory wordSize r: resultReg.
  	"copy two fields at a time..."
  	copyLoop := cogit Label.
  	cogit
  		AddCq: objectMemory wordSize * 2 R: ReceiverResultReg;
  		AddCq: objectMemory wordSize * 2 R: ptrReg;
  		MoveMw: 0 r: ReceiverResultReg R: TempReg;
  		MoveR: TempReg Mw: 0 r: ptrReg;
  		MoveMw: objectMemory wordSize r: ReceiverResultReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory wordSize r: ptrReg;
  		CmpR: ptrReg R: slotsReg;
  		JumpAbove: copyLoop;
  		MoveR: resultReg R: ReceiverResultReg;
  		genPrimReturn.
  
  	"If the receiver is variable pointers, fail if its a context, otherwise continue"
  	jumpVariable jmpTarget: cogit Label.
  	self genGetClassIndexOfNonImm: ReceiverResultReg into: ClassReg.
  	cogit
  		CmpCq: ClassMethodContextCompactIndex R: ClassReg;
  		JumpNonZero: continuance.
  
  	jumpImmediate jmpTarget:
  	(jumpNoSpace jmpTarget:
  	(jumpIsMethod jmpTarget:
  	(jumpTooBig jmpTarget:
  	(jumpEmpty jmpTarget: cogit Label)))).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveShallowCopy (in category 'primitive generators') -----
  genPrimitiveShallowCopy
  	"Implement primitiveShallowCopy/primitiveClone for convenient cases:
  	- the receiver is not a context
  	- the receiver is not a compiled method
  	- the result fits in eden (actually below scavengeThreshold)"
  
  	| formatReg resultReg slotsReg ptrReg
  	  jumpImmediate jumpIsMethod jumpVariable jumpTooBig jumpEmpty jumpNoSpace
  	  continuance copyLoop |
  	<var: #continue type: #'AbstractInstruction *'>
  	<var: #copyLoop type: #'AbstractInstruction *'>
  	<var: #jumpTooBig type: #'AbstractInstruction *'>
  	<var: #jumpVariable type: #'AbstractInstruction *'>
  	<var: #jumpNoSpace type: #'AbstractInstruction *'>
  	<var: #jumpIsMethod type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	resultReg := Arg0Reg.
  	slotsReg := Arg1Reg.
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: resultReg.
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self genGetFormatOf: ReceiverResultReg
  		into: (ptrReg := formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
  
  	cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
  	jumpIsMethod := cogit JumpAboveOrEqual: 0.
  	cogit CmpCq: objectMemory indexablePointersFormat R: formatReg.
  	jumpVariable := cogit JumpZero: 0.
  	continuance := cogit Label.
  
  	self genGetRawSlotSizeOfNonImm: ReceiverResultReg into: slotsReg.
  	cogit CmpCq: objectMemory numSlotsMask R: slotsReg.
  	jumpTooBig := cogit JumpZero: 0.
  
  	cogit CmpCq: 0 R: slotsReg.
  	jumpEmpty := cogit JumpZero: 0.
  
  	"compute byte size for slots"
  	cogit
  		AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: slotsReg;
  		LogicalShiftLeftCq: objectMemory shiftForWord R: slotsReg;
  	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
  		AddR: resultReg R: slotsReg;
  		CmpCq: objectMemory getScavengeThreshold R: slotsReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	cogit
  		MoveR: resultReg R: ptrReg;
  	"write back new freeStart; get result. slotsReg holds new freeStart, the limit of the object"
  		MoveR: slotsReg Aw: objectMemory freeStartAddress;
  	"set up loop bounds"
  		SubCq: objectMemory wordSize * 2 R: slotsReg;
  	"copy header, masking off irrelevant bits"
  		MoveMw: 0 r: ReceiverResultReg R: TempReg;
  		AndCq: (objectMemory
  					headerForSlots: objectMemory numSlotsMask
  					format: objectMemory formatMask
  					classIndex: objectMemory classIndexMask) R: TempReg;
  		MoveR: TempReg Mw: 0 r: resultReg.
  	copyLoop := cogit Label.
  	cogit
  		AddCq: objectMemory wordSize R: ReceiverResultReg;
  		AddCq: objectMemory wordSize R: ptrReg;
  		MoveMw: 0 r: ReceiverResultReg R: TempReg;
  		MoveR: TempReg Mw: 0 r: ptrReg;
  		CmpR: ptrReg R: slotsReg;
+ 		JumpAboveOrEqual: copyLoop;
- 		JumpAbove: copyLoop;
  		MoveR: resultReg R: ReceiverResultReg;
  		genPrimReturn.
  
  	"If the receiver is variable pointers, fail if its a context, otherwise continue"
  	jumpVariable jmpTarget: cogit Label.
  	self genGetClassIndexOfNonImm: ReceiverResultReg into: ClassReg.
  	cogit
  		CmpCq: ClassMethodContextCompactIndex R: ClassReg;
  		JumpNonZero: continuance.
  
  	jumpImmediate jmpTarget:
  	(jumpNoSpace jmpTarget:
  	(jumpIsMethod jmpTarget:
  	(jumpTooBig jmpTarget:
  	(jumpEmpty jmpTarget: cogit Label)))).
  
  	^0!

Item was changed:
  ----- Method: CogVMSimulator>>printHexnp: (in category 'debug printing') -----
  printHexnp: anInteger
  
  	traceOn ifTrue:
+ 		[transcript nextPutAll: (anInteger asInteger storeStringBase: 16)]!
- 		[transcript nextPutAll: (anInteger storeStringBase: 16)]!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulationWindow;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
+ 		add: 'print mc/cog head frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
+ 		add: 'short print ext head frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
+ 		add: 'short print int head frame & callers' action: [self shortPrintFrameAndCallers: localFP];
+ 		add: 'short print mc/cog head frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
+ 		add: 'long print ext head frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
+ 		add: 'long print int head frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
+ 		add: 'long print mc/cog head frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
- 		add: 'print mc/cog frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
- 		add: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
- 		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
- 		add: 'short print mc/cog frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
- 		add: 'long print ext frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
- 		add: 'long print int frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
- 		add: 'long print mc/cog frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
+ 		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor pc.
+ 											self externalWriteBackHeadFramePointers];
- 		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor eip.
- 											self writeBackHeadFramePointers];
  		addLine;
  		add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: cogit getCStackPointer];
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action:
  			[cogit disassembleCodeAt: (((cogit codeEntryFor: cogit processor pc) isNil
  										  and: [(cogit methodZone methodFor: cogit processor pc) = 0])
  											ifTrue: [instructionPointer]
  											ifFalse: [cogit processor pc])];
  		add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect.
  	self isThreadedVM ifTrue:
  		[aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  	aMenuMorph
  		addLine;
  		add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
  		add: 'print cog methods with prim...' action: [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  		add: 'print cog methods with selector...' action:
  			[|s| s := UIManager default request: 'selector'.
  			s notEmpty ifTrue:
  				[s = 'nil' ifTrue: [s := nil].
  				 cogMethodZone methodsDo:
  					[:m|
  					(s ifNil: [m selector = objectMemory nilObject]
  					 ifNotNil: [(objectMemory numBytesOf: m selector) = s size
  							and: [(self str: s
  									n: (m selector + objectMemory baseHeaderSize)
  									cmp: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  						[cogit printCogMethod: m]]]];
  		add: 'print cog method for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodFor: pc]];
  		add: 'print cog method header for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodHeaderFor: pc]];
  		add: 'print trampoline table' target: cogit action: #printTrampolineTable;
  		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
- 		add: 'set break pc', cogit breakPC menuPrompt, '...-ve to disable or remove' action: [cogit promptForBreakPC];
  		add: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: (cogit printRegisters
  				ifTrue: ['no print registers each instruction']
  				ifFalse: ['print registers each instruction'])
  			action: [cogit printRegisters: cogit printRegisters not];
  		add: (cogit printInstructions
  				ifTrue: ['no print instructions each instruction']
  				ifFalse: ['print instructions each instruction'])
  			action: [cogit printInstructions: cogit printInstructions not];
  		addLine;
  		add: 'click step' action: [cogit setClickStepBreakBlock];
+ 		add: 'set break pc', cogit breakPC menuPrompt, '...-ve to disable or remove' action: [cogit promptForBreakPC];
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
  											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: 'set break block...' action: [|s| s := UIManager default request: 'break block' initialAnswer: '[:theCogit| false]'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: 'set cogit break method...' action: [(self promptHex: 'cogit breakMethod') ifNotNil: [:bm| cogit setBreakMethod: bm]];
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

Item was changed:
  ----- Method: FakeStdinStream>>next (in category 'accessing') -----
  next
  	"Answer the next object in the Stream represented by the receiver.
  	 If there are no more elements in the stream fill up the buffer by prompting for input"
  	| sem threadIndex inputLine next |
  	position >= readLimit ifTrue:
  		[simulator isThreadedVM
  			ifTrue:
  				["(simulator cogit singleStep not
  				  and: [UIManager confirm: 'Single step?']) ifTrue:
  					[simulator cogit singleStep: true]."
  				 threadIndex := simulator disownVM: DisownVMLockOutFullGC.
  				 simulator forceInterruptCheckFromHeartbeat.
  				 sem := Semaphore new.
  				 WorldState addDeferredUIMessage:
  					[inputLine := UIManager default request: 'Input please!!'.
  					 sem signal].
  				 sem wait]
+ 			ifFalse: "simulate line-oriented input"
+ 				[inputLine := FillInTheBlankMorph
+ 								request: 'Input please!!'
+ 								initialAnswer: ''
+ 								centerAt: ActiveHand cursorPoint
+ 								inWorld: ActiveWorld
+ 								onCancelReturn: nil 
+ 								acceptOnCR: true.
+ 				inputLine ifNil: [self halt]].
- 			ifFalse:
- 				[inputLine := UIManager default request: 'Input please!!'].
  		 collection size <= inputLine size ifTrue:
  			[collection := collection species new: inputLine size + 1].
  		 collection
  			replaceFrom: 1 to: inputLine size with: inputLine startingAt: 1;
  		 	at: (readLimit := inputLine size + 1) put: Character lf.
  		 position := 0.
  		 simulator isThreadedVM ifTrue:
  			[simulator ownVM: threadIndex]].
  	next := collection at: (position := position + 1).
  	"This is set temporarily to allow (FilePluginSimulator>>#sqFile:Read:Into:At:
  	 to brwak out of its loop.  sqFile:Read:Into:At: resets it on the way out."
  	atEnd := position >= readLimit.
  	^next
  	
  
  " This does it with workspaces:
  | ws r s |
  s := Semaphore new.
  ws := Workspace new contents: ''.
  ws acceptAction: [:t| r := t asString. s signal].
  [ws openLabel: 'Yo!!'; shouldStyle: false.
  (ws dependents detect: [:dep | dep isKindOf: PluggableTextMorph] ifNone: [nil]) ifNotNil:
  	[:textMorph| textMorph acceptOnCR: true; hasUnacceptedEdits: true]] fork.
  Processor activeProcess ==  Project uiProcess
  	ifTrue: [[r isNil] whileTrue: [World doOneCycle]]
  	ifFalse: [s wait].
  ws topView delete.
  s wait. s signal.
  r"!

Item was changed:
  SpurGenerationScavenger subclass: #SpurGenerationScavengerSimulator
+ 	instanceVariableNames: 'cameFrom'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManagerSimulation'!

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

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>cameFrom: (in category 'accessing') -----
+ cameFrom: anObject
+ 
+ 	cameFrom := anObject!

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>copyAndForward: (in category 'scavenger') -----
+ copyAndForward: survivor
+ 	| relocatedOop |
+ 	relocatedOop := super copyAndForward: survivor.
+ 	cameFrom ifNotNil:
+ 		[cameFrom at: relocatedOop put: survivor].
+ 	^relocatedOop!

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>copyAndForwardMourner: (in category 'scavenger') -----
+ copyAndForwardMourner: survivor
+ 	| relocatedOop |
+ 	relocatedOop := super copyAndForwardMourner: survivor.
+ 	cameFrom ifNotNil:
+ 		[cameFrom at: relocatedOop put: survivor].
+ 	^relocatedOop!

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>recordMovements (in category 'scavenger') -----
+ recordMovements
+ 	cameFrom := Dictionary new!

Item was changed:
  ----- Method: SpurGenerationScavengerSimulator>>scavenge: (in category 'scavenger') -----
  scavenge: tenuringCriterion
  	manager bootstrapping ifFalse:
+ 		[coInterpreter transcript nextPutAll: 'scavenging('; print: manager statScavenges; nextPutAll: ')...'; flush.
+ 		 cameFrom ifNotNil:
+ 			[cameFrom := Dictionary new]].
- 		[coInterpreter transcript nextPutAll: 'scavenging('; print: manager statScavenges; nextPutAll: ')...'; flush].
  	^super scavenge: tenuringCriterion!

Item was changed:
  ----- Method: StackInterpreter>>printContext: (in category 'debug printing') -----
  printContext: aContext
  	| sender ip sp |
  	<inline: false>
  	self shortPrintContext: aContext.
  	sender := objectMemory fetchPointer: SenderIndex ofObject: aContext.
  	ip := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	(objectMemory isIntegerObject: sender)
  		ifTrue:
  			[(self checkIsStillMarriedContext: aContext currentFP: framePointer)
  				ifTrue: [self print: 'married (assuming framePointer valid)'; cr]
  				ifFalse: [self print: 'widowed (assuming framePointer valid)'; cr].
  			self print: 'sender   '; printNum: sender; print: ' (';
  				printHexPtr: (self withoutSmallIntegerTags: sender); printChar: $); cr.
  			 self print: 'ip       '; printNum: ip; print: ' (';
  				printHexPtr: (self withoutSmallIntegerTags: ip); printChar: $); cr]
  		ifFalse:
  			[self print: 'sender   '; shortPrintOop: sender.
  			 self print: 'ip       '.
  			 ip = objectMemory nilObject
  				ifTrue: [self shortPrintOop: ip]
  				ifFalse: [self printNum: ip; print: ' ('; printNum: (objectMemory integerValueOf: ip); space; printHex: (objectMemory integerValueOf: ip); printChar: $); cr]].
  	sp := objectMemory fetchPointer: StackPointerIndex ofObject: aContext.
  	sp := sp min: (objectMemory lengthOf: aContext) - ReceiverIndex.
  	self print: 'sp       '; printNum: sp; print: ' ('; printNum: (objectMemory integerValueOf: sp); printChar: $); cr.
+ 	self print: 'method   '; printMethodFieldForPrintContext: aContext.
- 	self print: 'method   '; shortPrintOop: (objectMemory fetchPointer: MethodIndex ofObject: aContext).
  	self print: 'closure  '; shortPrintOop: (objectMemory fetchPointer: ClosureIndex ofObject: aContext).
  	self print: 'receiver '; shortPrintOop: (objectMemory fetchPointer: ReceiverIndex ofObject: aContext).
  	sp := objectMemory integerValueOf: sp.
  	1 to: sp do:
  		[:i|
  		self print: '       '; printNum: i; space; shortPrintOop: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)]!

Item was added:
+ ----- Method: StackInterpreter>>printMethodFieldForPrintContext: (in category 'debug printing') -----
+ printMethodFieldForPrintContext: aContext
+ 	<inline: true>
+ 	self shortPrintOop: (objectMemory fetchPointer: MethodIndex ofObject: aContext)!



More information about the Vm-dev mailing list