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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 22 19:23:59 UTC 2018


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

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

Name: VMMaker.oscog-eem.2322
Author: eem
Time: 22 January 2018, 11:23:26.827661 am
UUID: 3bf03f98-466c-41eb-9346-97c7b5567559
Ancestors: VMMaker.oscog-eem.2321

RegisterAllocatingCogit:
Make sure the receiverResultReg state is valid on backwards jump when the stackLimit is not exceeded.  Implement branch following as per StackToRegisterMappingCogit>>#genJumpTo:.  Avoid duplicating send of moveVolatileSimStackEntriesToRegisters in ensureFixupAt:.

Cogit:
Implement inst var name decoration in x64 disassembly.

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

Item was added:
+ ----- Method: Cogit class>>attemptToComputeInstVarNamesFor: (in category 'in-image compilation support') -----
+ attemptToComputeInstVarNamesFor: aCompiledMethod
+ 	(aCompiledMethod methodClass instSize > 0) ifTrue:
+ 		[initializationOptions
+ 			at: #instVarNames
+ 			put: (aCompiledMethod methodClass allInstVarNames)]!

Item was changed:
  ----- Method: Cogit class>>cog:selectorOrNumCopied:options: (in category 'in-image compilation') -----
  cog: aCompiledMethod selectorOrNumCopied: selectorOrNumCopied options: optionsDictionaryOrArray
  	"StackToRegisterMappingCogit cog: (Integer >> #benchFib) selector: #benchFib options: #(COGMTVM false)"
  	| cogit coInterpreter |
  	cogit := self instanceForTests: optionsDictionaryOrArray.
  	self attemptToComputeTempNamesFor: aCompiledMethod.
+ 	self attemptToComputeInstVarNamesFor: aCompiledMethod.
  	coInterpreter := CurrentImageCoInterpreterFacade forCogit: cogit.
  	[cogit
  		setInterpreter: coInterpreter;
  		singleStep: true;
  		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size / 2. "leave space for rump C stack"
  	 cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
  		on: Notification
  		do: [:ex|
  			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
  				[ex resume: coInterpreter].
  			ex pass].
  	^{ coInterpreter.
  		cogit.
  		selectorOrNumCopied isInteger
  			ifTrue: [ cogit cogFullBlockMethod: (coInterpreter oopForObject: aCompiledMethod) numCopied: selectorOrNumCopied ]
  			ifFalse: [ cogit cog: (coInterpreter oopForObject: aCompiledMethod) selector: (coInterpreter oopForObject: selectorOrNumCopied) ] }!

Item was changed:
  ----- Method: Cogit>>disassembleFrom:to:labels:on: (in category 'disassembly') -----
  disassembleFrom: startAddress to: endAddress labels: labelDictionary on: aStream
  	<doNotGenerate>
+ 	| previousTVP |
  	aStream ensureCr.
+ 	previousTVP := processor class printTempNames.
+ 	processor class
+ 		printTempNames: (self class initializationOptions includesKey: #tempNames);
+ 		setReceiverResultReg: ((self class initializationOptions includesKey: #instVarNames) ifTrue:
+ 									[ReceiverResultReg]).
+ 	[processor
+ 		disassembleFrom: startAddress
+ 		to: endAddress
+ 		in: coInterpreter memory
+ 		for: self
+ 		labels: labelDictionary
+ 		on: aStream] ensure:
+ 			[processor class
+ 				printTempNames: previousTVP;
+ 				setReceiverResultReg: nil].
- 	processor disassembleFrom: startAddress to: endAddress in: coInterpreter memory for: self labels: labelDictionary on: aStream.
  	aStream flush!

Item was added:
+ ----- Method: Cogit>>lookupInstVarOffset: (in category 'disassembly') -----
+ lookupInstVarOffset: offset
+ 	^offset \\ objectMemory bytesPerOop = 0 ifTrue:
+ 		[(self class initializationOptions at: #instVarNames ifAbsent: nil) ifNotNil:
+ 			[:array|
+ 			 array
+ 				at: offset - objectMemory baseHeaderSize / objectMemory bytesPerOop + 1
+ 				ifAbsent: nil]]!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ensureFixupAt: (in category 'bytecode generator support') -----
  ensureFixupAt: targetPC
  	"Make sure there's a flagged fixup at the target pc in fixups.
  	 Initially a fixup's target is just a flag.  Later on it is replaced with a proper instruction.
  	 Override to generate stack merging code if required."
  	| fixup |	
  	<var: #fixup type: #'BytecodeFixup *'>
  	self assert: targetPC > bytecodePC.
  	fixup := self fixupAt: targetPC.
  	"If a non-merge fixup has already been defined then where-ever that was done didn't
  	 realise there needed to be a merge and forgot to save the stack state for that merge."
  	self deny: fixup isNonMergeFixup.
  	fixup needsFixup 
  		ifTrue:
  			[fixup mergeSimStack
  				ifNil: [self setMergeSimStackOf: fixup]
  				ifNotNil:
  					[self copySimStackToScratch: simSpillBase.
  					 self mergeCurrentSimStackWith: fixup forwards: true.
  					 self restoreSimStackFromScratch]]
  		ifFalse: 
  			[self assert: (fixup mergeSimStack isNil or: [compilationPass = 2]).
- 			 self moveVolatileSimStackEntriesToRegisters. "Is this needed here?  It is sent immediately in setMergeSimStackOf:; maybe it should be in the ifNotNil: branch only?"
  			 fixup mergeSimStack
  				ifNil: [self setMergeSimStackOf: fixup]
+ 				ifNotNil:
+ 					[self moveVolatileSimStackEntriesToRegisters.
+ 					 self assert: (self simStack: simStack isIdenticalTo: fixup mergeSimStack)]].
- 				ifNotNil: [self assert: (self simStack: simStack isIdenticalTo: fixup mergeSimStack)]].
  	^super ensureFixupAt: targetPC!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genJumpBackTo: (in category 'bytecode generator support') -----
  genJumpBackTo: targetPC
  	| target |
  	"On first pass install register allocations (if any) as of the end of the loop and back up to recompile.
  	 One the second pass generate
+ 				(any merge other than self elided because register assignments copied to loop head in first pass)
- 				(any merge elided because register assignments copied to loop head in first pass)
  				cmp stackLimit
+ 				maybe reload self
  				jumpAboveOrEqual target
  				flush
  				checkForInterrupts
  				merge from flushed (N.B. If stack was flushed before loop we could conceivably jump to the pre-loop merge code)
  				jmp target
  	 self printSimStack; printSimStack: target mergeSimStack"
  	self assert: targetPC < bytecodePC.
  	target := self fixupAt: targetPC.
  	self ensureRegisterAssignmentsAreAtHeadOfLoop: target.
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
+ 	(target isReceiverResultRegSelf
+ 	 and: [simSelf liveRegister = NoReg]) ifTrue:
+ 		[simSelf storeToReg: ReceiverResultReg].
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	self JumpAboveOrEqual: target.
  
  	self ssFlushTo: simStackPtr.
  	self CallRT: ceCheckForInterruptTrampoline.
  	self annotateBytecode: self Label.
  	self flushLiveRegistersForSuspensionPoint.
  	self mergeCurrentSimStackWith: target forwards: false.
  	self Jump: target.
  	deadCode := true. "can't fall through"
  	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genJumpTo: (in category 'bytecode generator support') -----
  genJumpTo: targetBytecodePC
  	"Overriden to avoid the flush because in this cogit stack state is merged at merge point."
+ 	| eventualTarget generator fixup |
+ 	eventualTarget := self eventualTargetOf: targetBytecodePC.
+ 	(eventualTarget > bytecodePC
+ 	 and: [self stackTopIsBoolean
+ 	 and: [(generator := self generatorForPC: eventualTarget) isConditionalBranch]])
+ 		ifTrue:
+ 			[eventualTarget := eventualTarget
+ 							  + generator numBytes
+ 							  + (generator isBranchTrue == (self ssTop constant = objectMemory trueObject)
+ 									ifTrue: [self spanFor: generator at: eventualTarget exts: 0 in: methodObj]
+ 									ifFalse: [0]).
+ 			self ssPop: 1.
+ 			fixup := self ensureFixupAt: eventualTarget.
+ 			self ssPop: -1]
+ 		ifFalse:
+ 			[fixup := self ensureFixupAt: eventualTarget].
  	deadCode := true. "can't fall through"
+ 	self Jump: fixup.
+ 	^0!
- 	self Jump: (self ensureFixupAt: (self eventualTargetOf: targetBytecodePC)).
- 	^ 0!

Item was changed:
  ----- Method: VMClass class>>initialize (in category 'initialization') -----
  initialize
  	(Utilities classPool at: #CommonRequestStrings ifAbsent: []) ifNotNil:
  		[:commonRequestStringHolder|
  		(commonRequestStringHolder contents asString includesSubstring: 'VMClass open') ifFalse:
+ 			[Utilities appendToCommonRequests: '-\VMMaker generateConfiguration\VMMaker generateAllConfigurationsUnderVersionControl\VMMaker generateAllSpurConfigurations\VMClass openCogMultiWindowBrowser\VMClass openObjectMemoriesInterpretersBrowser\VMClass openSpurMultiWindowBrowser\VMClass openCogSpurMultiWindowBrowser\VMClass openCogitMultiWindowBrowser' withCRs]].
- 			[Utilities appendToCommonRequests: '-\VMMaker generateConfiguration\VMMaker generateAllConfigurationsUnderVersionControl\VMMaker generateAllSpurConfigurations\VMClass openCogMultiWindowBrowser\VMClass openObjectMemoriesInterpretersBrowser\VMClass openSpurMultiWindowBrowser\VMClass openCogSpurMultiWindowBrowser' withCRs]].
  	ExpensiveAsserts := false!

Item was changed:
  ----- Method: VMClass class>>openCogitMultiWindowBrowser (in category 'utilities') -----
  openCogitMultiWindowBrowser
  	"Answer a new multi-window browser on the ObjectMemory classes, the Cog Interpreter classes, and the main JIT classes"
  	"self openCogitMultiWindowBrowser"
  	| b |
  	b := Browser open.
  	Cogit withAllSubclasses,
  	CogObjectRepresentation withAllSubclasses,
  	{CogMethodZone. CogRTLOpcodes },
  	(CogAbstractInstruction withAllSubclasses reject: [:c| c name endsWith: 'Tests']),
+ 	CogBytecodeFixup withAllSubclasses,
+ 	CogSimStackEntry withAllSubclasses,
  	{VMStructType. VMMaker. CCodeGenerator. TMethod}
  		do: [:class|
  			b selectCategoryForClass: class; selectClass: class]
  		separatedBy:
  			[b multiWindowState addNewWindow].
  	b multiWindowState selectWindowIndex: 1!



More information about the Vm-dev mailing list