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

commits at source.squeak.org commits at source.squeak.org
Wed Mar 11 20:31:13 UTC 2020


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

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

Name: VMMaker.oscog-eem.2727
Author: eem
Time: 11 March 2020, 1:30:57.591349 pm
UUID: 64327c90-1337-4d4d-889b-bfb75e5ad066
Ancestors: VMMaker.oscog-eem.2726

Actally fix a bogus failing assert over-zealously added to the VMMaker.oscog-eem.2724 commit (really this time).
Fix in-image compilation and rename specialObjectsArrayAddress to specialObjectsOopAddress to match the other fooAddress accessors.

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

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>maybeGenerateSelectorIndexDereferenceRoutine (in category 'initialization') -----
  maybeGenerateSelectorIndexDereferenceRoutine
  	"Generate the routine that converts selector indices into selector objects.
  	 It is called from the send trampolines.
  	 If the selector index is negative, convert it into a positive index into the
  	 special selectors array and index that.  Otherwise, index the current method.
  	 The routine uses Extra0Reg & Extra1Reg, which are available, since they
  	 are not live at point of send."
  	| jumpNegative jumpNotBlock jumpFullBlock |
  	<var: 'jumpNegative' type: #'AbstractInstruction *'>
  	<var: 'jumpNotBlock' type: #'AbstractInstruction *'>
  	<var: 'jumpFullBlock' type: #'AbstractInstruction *'>
  	cogit zeroOpcodeIndex.
  	cogit CmpCq: 0 R: ClassReg.
  	jumpNegative := cogit JumpLess: 0.
  	cogit
  		MoveMw: FoxMethod r: FPReg R: Extra0Reg;
  		AddCq: 2 R: ClassReg; "Change selector index to 1-relative, skipping the method header"
  		TstCq: MFMethodFlagIsBlockFlag R: Extra0Reg.
  	jumpNotBlock := cogit JumpZero: 0.
  	"If in a block, need to find the home method...  If using full blocks, need to test the cpicHasMNUCaseOrCMIsFullBlock bit"
  	cogit AndCq: methodZone zoneAlignment negated R: Extra0Reg.
  	SistaV1BytecodeSet ifTrue:
  		[self bitAndByteOffsetOfIsFullBlockBitInto:
  			[:bitmask :byteOffset|
  			jumpFullBlock := cogit
  				MoveMb: byteOffset r: Extra0Reg R: Extra1Reg;
  				TstCq: bitmask R: Extra1Reg;
  				JumpNonZero: 0]].
  	cogit 
  		MoveM16: 0 r: Extra0Reg R: Extra1Reg;
  		SubR: Extra1Reg R: Extra0Reg.
  	jumpNotBlock jmpTarget: cogit Label.
  	SistaV1BytecodeSet ifTrue:
  		[jumpFullBlock jmpTarget: jumpNotBlock getJmpTarget].
  	cogit "Now fetch the method object and index with the literal index to retrieve the selector"
  		AndCq: methodZone zoneAlignment negated R: Extra0Reg;
  		MoveMw: (cogit offset: CogMethod of: #methodObject) r: Extra0Reg R: Extra1Reg;
  		MoveXwr: ClassReg R: Extra1Reg R: ClassReg;
  		RetN: 0.
  	jumpNegative jmpTarget: cogit Label.
  	cogit
  		NegateR: ClassReg;
  		LogicalShiftLeftCq: 1 R: ClassReg;
+ 		MoveAw: objectMemory specialObjectsOopAddress R: Extra0Reg;
- 		MoveAw: objectMemory specialObjectsArrayAddress R: Extra0Reg;
  		SubCq: 1 R: ClassReg;
  		MoveMw: SpecialSelectors + 1 * objectMemory wordSize r: Extra0Reg R: Extra1Reg; "Index, including header size"
  		MoveXwr: ClassReg R: Extra1Reg R: ClassReg;
  		RetN: 0.
  	ceDereferenceSelectorIndex := cogit methodZoneBase.
  	cogit
  		outputInstructionsForGeneratedRuntimeAt: ceDereferenceSelectorIndex;
  		recordGeneratedRunTime: 'ceDereferenceSelectorIndex' address: ceDereferenceSelectorIndex;
  		recordRunTimeObjectReferences!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>cogit: (in category 'initialize-release') -----
  cogit: aCogit
+ 	| accessors |
  	cogit := aCogit.
  	cogit objectMemory ifNil:
  		[cogit instVarNamed: 'objectMemory' put: objectMemory].
  	coInterpreter cogit: aCogit.
  	(objectMemory respondsTo: #cogit:) ifTrue:
  		[objectMemory cogit: aCogit].
  	(objectMemory respondsTo: #coInterpreter:) ifTrue:
  		[objectMemory coInterpreter: coInterpreter].
  	coInterpreter setUpForUseByFacade: self.
  	objectMemory setUpForUseByFacade: self.
+ 	accessors := CurrentImageCoInterpreterFacade organization listAtCategoryNamed: #accessing.
  	coInterpreter class clusteredVariableNames do:
+ 		[:var|
+ 		(Symbol lookup: (var first = $C ifTrue: ['c', var allButFirst] ifFalse: [var]), 'Address') ifNotNil:
+ 			[:accessor|
+ 			(accessors includes: accessor) ifTrue:
+ 				[self perform: accessor]]].
- 		[:var| self perform: ((var first = $C ifTrue: ['c', var allButFirst] ifFalse: [var]), 'Address') asSymbol].
  	self initializeObjectMap!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>specialObjectsOopAddress (in category 'accessing') -----
+ specialObjectsOopAddress
+ 	self subclassResponsibility!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacadeFor64BitSpurObjectRepresentation>>specialObjectsArrayAddress (in category 'accessing') -----
- specialObjectsArrayAddress
- 	^self addressForLabel: #specialObjectsOop!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeFor64BitSpurObjectRepresentation>>specialObjectsOopAddress (in category 'accessing') -----
+ specialObjectsOopAddress
+ 	^self addressForLabel: #specialObjectsOop!

Item was removed:
- ----- Method: Spur64BitCoMemoryManager>>specialObjectsArrayAddress (in category 'trampoline support') -----
- specialObjectsArrayAddress
- 	<api>
- 	^self cCode: [(self addressOf: specialObjectsOop) asUnsignedInteger]
- 		inSmalltalk: [cogit simulatedVariableAddress: #specialObjectsOop in: self]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>specialObjectsOopAddress (in category 'trampoline support') -----
+ specialObjectsOopAddress
+ 	<api>
+ 	^self cCode: [(self addressOf: specialObjectsOop) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedVariableAddress: #specialObjectsOop in: self]!

Item was changed:
  ----- Method: SpurMemoryManager>>relocateObjStackForPlanningCompactor:andContents: (in category 'compaction') -----
  relocateObjStackForPlanningCompactor: objStack andContents: relocateContents
  	"Relocate all objStack pages that comprise objStack, including contents if requested."
  	| stackOrNil freeList next relocated result |
  	objStack = nilObj ifTrue:
  		[^objStack].
+ 	self assert: (relocateContents ifTrue: [(self rawHashBitsOf: objStack) < ObjStackLimit] ifFalse: [(self rawHashBitsOf: objStack) = 0]).
- 	self assert: (relocateContents or: [(self rawHashBitsOf: objStack) = 0]).
  	stackOrNil := objStack.
  	freeList := self fetchPointer: ObjStackFreex ofObject: objStack.
  	[self assert: (self numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
  	 "There are four fixed slots in an obj stack, and a Topx of 0 indicates empty, so
  	   if there were 5 slots in an oop stack, full would be 2, and the last 0-rel index is 4.
  	   Hence the last index is topx + fixed slots - 1, or topx + ObjStackNextx. The first
  	   two slots, Topx and Myx are not object references."
  	 next := self fetchPointer: ObjStackNextx ofObject: stackOrNil.
  	 relocated := compactor
  					relocateObjectsInHeapEntity: stackOrNil
  					from: ObjStackFreex
  					to: ObjStackNextx + (relocateContents ifTrue: [self rawHashBitsOf: stackOrNil] ifFalse: [0]).
  	 stackOrNil = objStack ifTrue:
  		[result := relocated].
  	 next ~= 0]
  		whileTrue:
  			[stackOrNil := next].
  	[freeList ~= 0] whileTrue:
  		[self assert: (self numSlotsOfAny: freeList) = ObjStackPageSlots.
  		 next := self fetchPointer: ObjStackFreex ofObject: freeList.
  		 compactor
  			relocateObjectsInHeapEntity: freeList
  			from: ObjStackFreex
  			to: ObjStackFreex.
  		 freeList := next].
- 	self assert: (relocateContents or: [(self rawHashBitsOf: relocated) = 0]).
  	^relocated!



More information about the Vm-dev mailing list