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

commits at source.squeak.org commits at source.squeak.org
Wed Oct 2 01:02:41 UTC 2013


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

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

Name: VMMaker.oscog-eem.422
Author: eem
Time: 1 October 2013, 6:00:00.977 pm
UUID: b892d1f0-5b73-4fe6-9cc6-5ac122276de6
Ancestors: VMMaker.oscog-eem.421

Fix bad slip in CoInterpreter>>mapVMRegisters.

Fix alignment of fake block headers.  Use
	self AlignmentNops: (methodZone roundUpLength: 1)
instead of
	self AlignmentNops: (self sizeof: CogBlockMethod).

Refactor genPushReceiverVariable: to eliminate genSSPushSlot:reg:.

Get ceNewArraySlotSize: to use faster Spur allocation.

More protocol added to CogObjectRepresentationFor[NBit]Spur.

Make checkIfValidObjectRef:pc:cogMethod: distinguish between
linked and unlinked sends.

Clue SpurMemoryManager>>checkHeapIntegrity into CogMethods.

Do some plumbing work for heapMapAtWord:[Put:].

More isIntegerObject: => isImmediate:,
isNonIntegerObject: => isNonImmediate:.

Bootstrap proceeds to first compilation of something containing
special selector class.

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

Item was changed:
  ----- Method: CoInterpreter>>ceNewArraySlotSize: (in category 'trampolines') -----
  ceNewArraySlotSize: slotSize
  	<api>
+ 	objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 		[| obj |
+ 		 obj := objectMemory
+ 					eeInstantiateClassIndex: ClassArrayCompactIndex
+ 					format: objectMemory arrayFormat
+ 					numSlots: slotSize.
+ 		objectMemory fillObj: obj numSlots: slotSize with: objectMemory nilObject.
+ 		^obj].
+ 	^objectMemory
+ 		eeInstantiateAndInitializeClass: (objectMemory splObj: ClassArray)
+ 		indexableSize: slotSize!
- 	^objectMemory eeInstantiateAndInitializeClass: (objectMemory splObj: ClassArray) indexableSize: slotSize!

Item was changed:
  ----- Method: CoInterpreter>>checkStackIntegrity (in category 'object memory support') -----
  checkStackIntegrity
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccesibleObjects has set a bit at each
  	 object's header.  Scan all objects accessible from the stack
  	 checking that every pointer points to a header.  Answer if no
  	 dangling pointers were detected."
  	| ok |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	ok := true.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP frameRcvrOffset callerFP oop |
  		thePage := stackPages stackPageAt: i.
  		(stackPages isFree: thePage) ifFalse:
  			[thePage = stackPage
  				ifTrue:
  					[theSP := stackPointer.
  					 theFP := framePointer]
  				ifFalse:
  					[theSP := thePage headSP.
  					 theFP := thePage  headFP].
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage ifFalse:
  				[theSP := theSP + BytesPerWord].
  			 [frameRcvrOffset := self frameReceiverOffset: theFP.
  			  [theSP <= frameRcvrOffset] whileTrue:
  				[oop := stackPages longAt: theSP.
+ 				 ((objectMemory isNonImmediate: oop) 
- 				 ((objectMemory isNonIntegerObject: oop) 
  				   and: [(self heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  					[self printFrameThing: 'object leak in frame temp' at: theSP; cr.
  					 ok := false].
  				 theSP := theSP + BytesPerWord].
  			 (self frameHasContext: theFP) ifTrue:
  				[oop := self frameContext: theFP.
+ 				 ((objectMemory isImmediate: oop) 
- 				 ((objectMemory isIntegerObject: oop) 
  				   or: [(self heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  					[self printFrameThing: 'object leak in frame ctxt' at: theFP + FoxThisContext; cr.
  					 ok := false].
  				 (oop = objectMemory nilObject or: [objectMemory isContext: oop]) ifFalse:
  					[self printFrameThing: 'frame ctxt should be context' at: theFP + FoxThisContext; cr.
  					 ok := false]].
  			 (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[| cogMethod |
  					 cogMethod := self mframeHomeMethod: theFP.
  					 (self heapMapAtWord: (self pointerForOop: cogMethod)) = 0 ifTrue:
  						[self printFrameThing: 'object leak in mframe mthd' at: theFP + FoxMethod; cr.
  						 ok := false]]
  				ifFalse:
  					[oop := self iframeMethod: theFP.
+ 					 ((objectMemory isImmediate: oop) 
- 					 ((objectMemory isIntegerObject: oop) 
  					   or: [(self heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  						[self printFrameThing: 'object leak in iframe mthd' at: theFP + FoxMethod; cr.
  						 ok := false]].
  			 (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theSP := theFP + FoxCallerSavedIP + BytesPerWord.
  				 theFP := callerFP].
  			 theSP := theFP + FoxCallerSavedIP + BytesPerWord.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
+ 				 ((objectMemory isNonImmediate: oop) 
- 				 ((objectMemory isNonIntegerObject: oop) 
  				   and: [(self heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  					[self printFrameThing: 'object leak in frame arg' at: theSP; cr.
  					 ok := false].
  				 theSP := theSP + BytesPerWord]]].
  	^ok!

Item was changed:
  ----- Method: CoInterpreter>>mapVMRegisters (in category 'object memory support') -----
  mapVMRegisters
  	"Map the oops in the interpreter's vm ``registers'' to their new values 
  	 during garbage collection or a become: operation."
  	"Assume: All traced variables contain valid oops.
  	 N.B. Don't trace messageSelector and lkupClass; these are ephemeral, live
  	 only during message lookup and because createActualMessageTo will not
  	 cause a GC these cannot change during message lookup."
  	| mapInstructionPointer |
  	(objectMemory shouldRemapObj: method) ifTrue:
  		["i.e. interpreter instructionPointer in method as opposed to machine code?"
  		(mapInstructionPointer := instructionPointer > method) ifTrue:
  			[instructionPointer := instructionPointer - method]. "*rel to method"
  		method := objectMemory remapObj: method.
  		mapInstructionPointer ifTrue:
  			[instructionPointer := instructionPointer + method]]. "*rel to method"
+ 	(objectMemory shouldRemapOop: newMethod) ifTrue: "maybe oop due to object-as-method"
+ 		[newMethod := objectMemory remapObj: newMethod]!
- 	(objectMemory shouldRemapOop: newMethod) ifFalse: "maybe oop due to object-as-method"
- 		[newMethod := objectMemory remap: newMethod]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveClone (in category 'object access primitives') -----
  primitiveClone
  	"Return a shallow copy of the receiver.
  	 Special-case non-single contexts (because of context-to-stack mapping).
  	 Can't fail for contexts cuz of image context instantiation code (sigh).
  	 Special case CompiledMerhods since the copy mustn't refer to CogMethod
  	 if receiver has been cogged."
  
  	| rcvr newCopy objHeader |
  	rcvr := self stackTop.
+ 	(objectMemory isImmediate: rcvr)
- 	(objectMemory isIntegerObject: rcvr)
  		ifTrue: [newCopy := rcvr]
  		ifFalse:
  			[objHeader := objectMemory baseHeader: rcvr.
  			(objectMemory isContextHeader: objHeader)
  				ifTrue: [newCopy := self cloneContext: rcvr]
  				ifFalse: [newCopy := objectMemory clone: rcvr].
  			newCopy = 0 ifTrue:
  				[^self primitiveFailFor: PrimErrNoMemory].
  			(objectMemory isCompiledMethodHeader: objHeader) ifTrue:
  				["use stackTop since GC may have moved rcvr"
  				 self rawHeaderOf: newCopy put: (self headerOf: self stackTop)]].
  	self pop: 1 thenPush: newCopy!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genRemoveSmallIntegerTagsInScratchReg: (in category 'compile abstract instructions') -----
+ genRemoveSmallIntegerTagsInScratchReg: scratchReg
+ 	cogit SubCq: 1 R: scratchReg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genSetSmallIntegerTagsIn: (in category 'compile abstract instructions') -----
+ genSetSmallIntegerTagsIn: scratchReg
+ 	cogit OrCq: 1 R: scratchReg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>checkValidInlineCacheTag: (in category 'debug support') -----
+ checkValidInlineCacheTag: classIndexOrTagPattern
+ 	^classIndexOrTagPattern <= objectMemory tagMask
+ 	  or: [(objectMemory classAtIndex: classIndexOrTagPattern) notNil]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>checkValidObjectReference: (in category 'debug support') -----
+ checkValidObjectReference: anOop
+ 	^(objectMemory isImmediate: anOop)
+ 	   or: [(objectMemory heapMapAtWord: (self pointerForOop: anOop)) ~= 0]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genRemoveSmallIntegerTagsInScratchReg: (in category 'compile abstract instructions') -----
+ genRemoveSmallIntegerTagsInScratchReg: scratchReg
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genSetSmallIntegerTagsIn: (in category 'compile abstract instructions') -----
+ genSetSmallIntegerTagsIn: scratchReg
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genStoreImmediateInSourceReg:slotIndex:destReg: (in category 'compile abstract instructions') -----
+ genStoreImmediateInSourceReg: sourceReg slotIndex: index destReg: destReg
+ 	cogit MoveR: sourceReg
+ 		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
+ 		   r: destReg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genStoreSourceReg:slotIndex:destReg:scratchReg: (in category 'compile abstract instructions') -----
+ genStoreSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg
+ 	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered mask rememberedBitByteOffset |
+ 	<var: #jmpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jmpDestYoung type: #'AbstractInstruction *'>
+ 	<var: #jmpSourceOld type: #'AbstractInstruction *'>
+ 	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
+ 	"do the store"
+ 	cogit MoveR: sourceReg
+ 		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
+ 		   r: destReg.
+ 	"now the check.  Is value stored an integer?  If so we're done"
+ 	cogit MoveR: sourceReg R: scratchReg.
+ 	cogit AndCq: objectMemory tagMask R: scratchReg.
+ 	jmpImmediate := cogit JumpNonZero: 0.
+ 	"Get the old/new boundary in scratchReg"
+ 	cogit MoveAw: objectMemory newSpaceLimitAddress R: scratchReg.
+ 	"Is target young?  If so we're done"
+ 	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
+ 	jmpDestYoung := cogit JumpBelow: 0.
+ 	"Is value stored old?  If so we're done."
+ 	cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := sourceReg - scratchReg"
+ 	jmpSourceOld := cogit JumpAboveOrEqual: 0.
+ 	"value is young and target is old.
+ 	 Need to remember this only if the remembered bit is not already set.
+ 	 Test the remembered bit.  Only need to fetch the byte containing it,
+ 	 which reduces the size of the mask constant."
+ 	rememberedBitByteOffset := jmpSourceOld isBigEndian
+ 									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
+ 									ifFalse:[objectMemory rememberedBitShift // 8].
+ 	mask := 1 << (objectMemory rememberedBitShift \\ 8).
+ 	cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
+ 	cogit AndCq: mask R: scratchReg.
+ 	jmpAlreadyRemembered := cogit JumpNonZero: 0.
+ 	"Remembered bit is not set.  Call store check to insert dest into remembered table."
+ 	self assert: destReg == ReceiverResultReg.
+ 	cogit CallRT: cogit ceStoreCheckTrampoline.
+ 	jmpImmediate jmpTarget:
+ 	(jmpDestYoung jmpTarget:
+ 	(jmpSourceOld jmpTarget:
+ 	(jmpAlreadyRemembered jmpTarget:
+ 		cogit Label))).
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>hasValidHeaderPostGC: (in category 'garbage collection') -----
+ hasValidHeaderPostGC: cogMethod
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<inline: true>
+ 	^cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>inlineCacheTagForInstance: (in category 'in-line cacheing') -----
+ inlineCacheTagForInstance: oop
+ 	"c.f. getInlineCacheClassTagFrom:into:"
+ 	(objectMemory isImmediate: oop) ifTrue:
+ 		[(objectMemory isIntegerObject: oop) ifTrue:
+ 			[^objectMemory integerObjectOf: 0]. "the SmallInteger tag"
+ 		 ^oop bitAnd: objectMemory tagMask]. "the other tags"
+ 	^objectMemory classIndexOf: oop!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>inlineCacheTagIsYoung: (in category 'in-line cacheing') -----
+ inlineCacheTagIsYoung: anInteger
+ 	"classIndices are not objects, heh, heh, heh..."
+ 	^false!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>isImmediate: (in category 'object representation') -----
+ isImmediate: oop
+ 	^objectMemory isImmediate: oop!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>slotOffsetOfInstVarIndex: (in category 'compile abstract instructions') -----
+ slotOffsetOfInstVarIndex: index
+ 	^index * objectMemory wordSize + objectMemory baseHeaderSize!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>genSSPushSlot:reg: (in category 'compile abstract instructions') -----
- genSSPushSlot: index reg: baseReg
- 	^cogit ssPushBase: baseReg offset: (self slotOffsetOfInstVarIndex: index)!

Item was added:
+ ----- Method: CogVMSimulator>>heapMapAtWord: (in category 'debug support') -----
+ heapMapAtWord: address
+ 	^objectMemory heapMap heapMapAtWord: address asUnsignedInteger!

Item was added:
+ ----- Method: CogVMSimulator>>heapMapAtWord:Put: (in category 'debug support') -----
+ heapMapAtWord: address Put: aBit
+ 	^objectMemory heapMap heapMapAtWord: address asUnsignedInteger Put: aBit!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		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 call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print all stacks' action: #printAllStacks;
  		addLine;
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action: [cogit disassembleCodeAt: 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]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		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 trampoline table' target: cogit action: #printTrampolineTable;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  		add: 'set break pc...' action: [(self promptHex: 'break pc') ifNotNil: [:bpc| cogit breakPC: bpc]];
  		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: '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 selector'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		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: Cogit>>addCogMethodsToHeapMap (in category 'debugging') -----
  addCogMethodsToHeapMap
  	<api>
  	"Perform an integrity/leak check using the heapMap.
  	 Set a bit at each cog method's header."	
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod ifTrue:
+ 			[coInterpreter heapMapAtWord: cogMethod Put: 1].
- 			[self heapMapAtWord: cogMethod Put: 1].
  		cogMethod := methodZone methodAfter: cogMethod]!

Item was changed:
  ----- Method: Cogit>>checkIfValidObjectRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidObjectRef: annotation pc: mcpc cogMethod: cogMethod
  	<var: #mcpc type: #'char *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation checkValidObjectReference: literal) ifFalse:
  			[self print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
  	(self isSendAnnotation: annotation) ifTrue:
+ 		[| entryPoint selectorOrCacheTag |
+ 		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
+ 		 entryPoint > methodZoneBase
+ 			ifTrue: "linked send, cacheTag is a cacheTag"
+ 				[(objectRepresentation checkValidInlineCacheTag: selectorOrCacheTag) ifFalse:
+ 					[self print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
+ 					^1]]
+ 			ifFalse: "unlinked send; cacheTag is a selector"
+ 				[(objectRepresentation checkValidObjectReference: selectorOrCacheTag) ifFalse:
+ 					[self print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
+ 					^1]]].
- 		[| cacheTag |
- 		 cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
- 		 (objectRepresentation checkValidInlineCacheTag: cacheTag) ifFalse:
- 			[self print: 'cache tag/selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
- 			^1]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>compileBlockEntry: (in category 'compile abstract instructions') -----
  compileBlockEntry: blockStart
  	"Compile a block's entry.  This looks like a dummy CogBlockMethod header (for frame parsing)
  	 followed by either a frame build, if a frame is required, or nothing.  The CogMethodHeader's
  	 objectHeader field is a back pointer to the method, but this can't be filled in until code generation."
  	<var: #blockStart type: #'BlockStart *'>
+ 	"Block method headers must be aligned on the correct boundary, just like non-block method headers."
+ 	self AlignmentNops: (methodZone roundUpLength: 1).
- 	self AlignmentNops: (self sizeof: CogBlockMethod).
  	blockStart fakeHeader: self Label.
  	(self sizeof: CogBlockMethod) caseOf:
  		{ [2 * BytesPerWord]	"ObjectMemory"
  			->	[self Fill32: 0.		"gets filled in later with the homeOffset and startpc"
  				 self Fill32: 0].		"gets filled in later with numArgs et al"
  		   [3 * BytesPerWord]	"Spur"
  			->	[self Fill32: 0.		"gets filled in later with the homeOffset and startpc"
  				 self Fill32: 0.		"is left fallow"
  				 self Fill32: 0].		"gets filled in later with numArgs et al"
  		}.
  	blockStart entryLabel: self Label.
  	needsFrame
  		ifTrue:
  			[self compileBlockFrameBuild: blockStart.
  			 self recordBlockTrace ifTrue:
  				[self CallRT: ceTraceBlockActivationTrampoline]]
  		ifFalse:
  			[self compileBlockFramelessEntry: blockStart]!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>clearLeakMapAndMapAccessibleObjects (in category 'debug support') -----
+ clearLeakMapAndMapAccessibleObjects
+ 	"Perform an integrity/leak check using the heapMap.  Set a bit at each object's header.
+ 	 Override to set a bit at each Cog method"
+ 	super clearLeakMapAndMapAccessibleObjects.
+ 	cogit addCogMethodsToHeapMap!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>newSpaceLimitAddress (in category 'trampoline support') -----
+ newSpaceLimitAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: newSpaceLimit) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #newSpaceLimit in: self]!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>heapMapAtWord: (in category 'debug support') -----
+ heapMapAtWord: address
+ 	^heapMap heapMapAtWord: address!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity (in category 'debug support') -----
  checkHeapIntegrity
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccessibleObjects has set a bit at each
  	 object's header.  Scan all objects in the heap checking that every
  	 pointer points to a header.  Scan the rootTable, remapBuffer and
  	 extraRootTable checking that every entry is a pointer to a header.
  	 Check that the number of roots is correct and that all rootTable
  	 entries have their rootBit set. Answer if all checks pass."
  	| prevObj prevPrevObj ok numRememberedRootsInHeap |
  	<inline: false>
  	ok := true.
  	numRememberedRootsInHeap := 0.
  	self allHeapEntitiesDo:
  		[:obj| | containsYoung fieldOop classIndex classOop |
  		(self isFreeObject: obj) ifFalse:
  			[containsYoung := false.
  			 (self isRemembered: obj) ifTrue:
  				[numRememberedRootsInHeap := numRememberedRootsInHeap + 1.
  				 (scavenger isInRememberedTable: obj) ifFalse:
  					[coInterpreter print: 'remembered object '; printHex: obj; print: ' is not in remembered table'; cr.
  					 self eek.
  					 ok := false]].
  			 (self isForwarded: obj)
  				ifTrue:
  					[fieldOop := self fetchPointer: 0 ofMaybeForwardedObject: obj.
  					 (heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  						[coInterpreter print: 'object leak in forwarder '; printHex: obj; print: ' to unmapped '; printHex: fieldOop; cr.
  						 self eek.
  						 ok := false].
  					 (self isYoung: fieldOop) ifTrue:
  						[containsYoung := true]]
  				ifFalse:
  					[classOop := self classAtIndex: (classIndex := self classIndexOf: obj).
  					 (classOop isNil or: [classOop = nilObj]) ifTrue:
  						[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; print: (classOop ifNil: ['nil'] ifNotNil: ['nilObj']); cr.
  						 self eek.
  						 ok := false].
  					 self baseHeaderSize to: (self lastPointerOf: obj) by: BytesPerOop do:
  						[:ptr|
  						 fieldOop := self longAt: obj + ptr.
  						 (self isNonImmediate: fieldOop) ifTrue:
  							[| fi |
  							 fi := ptr - self baseHeaderSize / self wordSize.
  							 (fieldOop bitAnd: self wordSize - 1) ~= 0
  								ifTrue:
  									[coInterpreter print: 'misaligned oop in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  									 self eek.
  									 ok := false]
  								ifFalse:
  									[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  										[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  										 self eek.
  										 ok := false].
+ 									 "don't be misled by CogMethods; they appear to be young, but they're not"
+ 									 ((self isYoung: fieldOop) and: [fieldOop >= startOfMemory]) ifTrue:
- 									 (self isYoung: fieldOop) ifTrue:
  										[containsYoung := true]]]]].
  					(containsYoung and: [(self isYoung: obj) not]) ifTrue:
  						[(self isRemembered: obj) ifFalse:
  							[coInterpreter print: 'unremembered object '; printHex: obj; print: ' contains young oop(s)'; cr.
  							 self eek.
  							 ok := false]]].
  		prevPrevObj := prevObj.
  		prevObj := obj].
  	numRememberedRootsInHeap ~= scavenger rememberedSetSize ifTrue:
  		[coInterpreter
  			print: 'root count mismatch. #heap roots ';
  			printNum: numRememberedRootsInHeap;
  			print: '; #roots ';
  			printNum: scavenger rememberedSetSize;
  			cr.
  		self eek.
  		"But the system copes with overflow..."
  		self flag: 'no support for remembered set overflow yet'.
  		"ok := rootTableOverflowed and: [needGCFlag]"].
  	scavenger rememberedSetWithIndexDo:
  		[:obj :i|
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned oop in rootTable @ '; printNum: i; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  						 self eek.
  						 ok := false]
  					ifFalse:
  						[(self isYoung: obj) ifTrue:
  							[coInterpreter print: 'non-root in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  							 self eek.
  							 ok := false]]]].
  	self flag: 'no support for remap buffer yet'.
  	"1 to: remapBufferCount do:
  		[:ri|
  		obj := remapBuffer at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  						 self eek.
  						 ok := false]]]."
  	self flag: 'no support for extraRoots yet'.
  	"1 to: extraRootCount do:
  		[:ri|
  		obj := (extraRoots at: ri) at: 0.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  						 self eek.
  						 ok := false]]]."
  	^ok!

Item was changed:
  ----- Method: SpurMemoryManager>>isIntegerObject: (in category 'object testing') -----
  isIntegerObject: oop
  	"This list records the valid senders of isIntegerObject: as we replace uses of
  	  isIntegerObject: by isImmediate: where appropriate."
  	| sel |
  	sel := thisContext sender method selector.
  	(#(	DoIt
  		DoItIn:
  		on:do: "from the debugger"
  		makeBaseFrameFor:
  		quickFetchInteger:ofObject:
  		frameOfMarriedContext:
  		objCouldBeClassObj:
  		isMarriedOrWidowedContext:
  		shortPrint:
  		bytecodePrimAt
  		bytecodePrimAtPut
  		commonAt:
  		commonAtPut:
  		loadFloatOrIntFrom:
  		positive32BitValueOf:
  		primitiveExternalCall
  		checkedIntegerValueOf:
  		bytecodePrimAtPut
  		commonAtPut:
  		primitiveVMParameter
  		checkIsStillMarriedContext:currentFP:
  		displayBitsOf:Left:Top:Right:Bottom:
  		fetchStackPointerOf:
  		primitiveContextAt
  		primitiveContextAtPut
  		subscript:with:storing:format:
  		printContext:
  		compare31or32Bits:equal:
  		signed64BitValueOf:
  		primDigitMultiply:negative:
  		digitLength:
  		isNegativeIntegerValueOf:
  		magnitude64BitValueOf:
  		primitiveMakePoint
  		primitiveAsCharacter
  		primitiveInputSemaphore
  		baseFrameReturn
  		primitiveExternalCall
  		primDigitCompare:
  		isLiveContext:
  		numPointerSlotsOf:
  		fileValueOf:
  		loadBitBltDestForm
  		fetchIntOrFloat:ofObject:ifNil:
  		fetchIntOrFloat:ofObject:
  		loadBitBltSourceForm
  		loadPoint:from:
  		primDigitAdd:
  		primDigitSubtract:
  		positive64BitValueOf:
  		digitBitLogic:with:opIndex:
  		signed32BitValueOf:
  		isNormalized:
  		primDigitDiv:negative:
  		bytesOrInt:growTo:
  		primitiveNewMethod
  		isCogMethodReference:
  		functionForPrimitiveExternalCall:
  		genSpecialSelectorArithmetic
+ 		genSpecialSelectorComparison
+ 		ensureContextHasBytecodePC:
+ 		instVar:ofContext:) includes: sel) ifFalse:
- 		genSpecialSelectorComparison) includes: sel) ifFalse:
  		[self halt].
  	^(oop bitAnd: 1) ~= 0!

Item was changed:
  ----- Method: StackInterpreter>>findSelectorOfMethod: (in category 'debug support') -----
+ findSelectorOfMethod: methArg
+ 	| meth classObj classDict classDictSize methodArray i |
+ 	(objectMemory addressCouldBeObj: methArg) ifFalse:
- findSelectorOfMethod: meth
- 	| classObj classDict classDictSize methodArray i |
- 	(objectMemory addressCouldBeObj: meth) ifFalse:
  		[^objectMemory nilObject].
+ 	meth := (objectMemory isForwarded: methArg)
+ 				ifTrue: [objectMemory followForwarded: methArg]
+ 				ifFalse: [methArg].
+ 	 (objectMemory isOopCompiledMethod: meth) ifFalse:
+ 		[^objectMemory nilObject].
  	classObj := self methodClassOf: meth.
  	(self addressCouldBeClassObj: classObj) ifTrue:
  		[classDict := objectMemory fetchPointer: MethodDictionaryIndex ofObject: classObj.
  		 classDictSize := objectMemory fetchWordLengthOf: classDict.
  		 methodArray := objectMemory fetchPointer: MethodArrayIndex ofObject: classDict.
  		 i := 0.
  		 [i <= (classDictSize - SelectorStart)] whileTrue:
  			[meth = (objectMemory fetchPointer: i ofObject: methodArray) ifTrue:
  				[^(objectMemory fetchPointer: i + SelectorStart ofObject: classDict)].
  				 i := i + 1]].
  	^objectMemory nilObject!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushReceiverVariable: (in category 'bytecode generators') -----
  genPushReceiverVariable: index
  	<inline: false>
  	self ensureReceiverResultRegContainsSelf.
+ 	^self ssPushBase: ReceiverResultReg
+ 			offset: (objectRepresentation slotOffsetOfInstVarIndex: index)!
- 	^objectRepresentation genSSPushSlot: index reg: ReceiverResultReg!



More information about the Vm-dev mailing list