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

commits at source.squeak.org commits at source.squeak.org
Tue Jan 23 21:16:20 UTC 2018


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

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

Name: VMMaker.oscog-eem.2324
Author: eem
Time: 23 January 2018, 1:15:42.643009 pm
UUID: 904abc56-e5a8-467e-a337-880211e33805
Ancestors: VMMaker.oscog-cb.2323

Fix store check call in genPrimitiveStringReplace on RISCs (i.e. on ARM save & restore LinkReg around call).

Fix code generation for RegisterAllocatingCogit>>genJumpBackTo: (must use addressOf: simSelf).

Fix typos in CogSimStackEntry's class comment.

=============== Diff against VMMaker.oscog-cb.2323 ===============

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genPrimitiveStringReplace (in category 'primitive generators') -----
  genPrimitiveStringReplace
  	"replaceFrom: start to: stop with: replacement startingAt: repStart. 
  	
  	The primitive in the JIT tries to deal with two pathological cases, copy of arrays and byteStrings,
  	which often copies only a dozen of fields and where switching to the C runtime cost a lot.
  	
  	Based on heuristics on the method class, I generate a quick array path (typically for Array),
  	a quick byteString path (typically for ByteString, ByteArray and LargeInteger) or no quick 
  	path at all (Typically for Bitmap).
  	
  	The many tests to ensure that the primitive won't fail are not super optimised (multiple reloading
  	or stack arguments in registers) but this is still good enough and worth it since we're avoiding 
  	the Smalltalk to C stack switch. The tight copying loops are optimised. 
  	
  	It is possible to build a bigger version with the 2 different paths but I (Clement) believe this 
  	is too big machine code wise to be worth it."
  	
  	|arrayReg startReg stopReg replReg repStartReg jumpNotSmi1 jumpNotSmi2 jumpNotSmi3 jumpImm jumpEmpty jumpImmutable jumpOutOfBounds1 jumpOutOfBounds2 jumpOutOfBounds3 jumpOutOfBounds4 jumpIncorrectFormat1 jumpIncorrectFormat2 jumpIncorrectFormat3 jumpIncorrectFormat4 result jmpDestYoung jmpAlreadyRemembered instr adjust|
  	
  	<var: #jumpImm type: #'AbstractInstruction *'>
  	<var: #jumpEmpty type: #'AbstractInstruction *'>
  	<var: #jumpFinished type: #'AbstractInstruction *'>
  	<var: #jumpNotSmi1 type: #'AbstractInstruction *'>
  	<var: #jumpNotSmi2 type: #'AbstractInstruction *'>
  	<var: #jumpNotSmi3 type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jumpImmutable type: #'AbstractInstruction *'>
  	<var: #jumpOutOfBounds1 type: #'AbstractInstruction *'>
  	<var: #jumpOutOfBounds2 type: #'AbstractInstruction *'>
  	<var: #jumpOutOfBounds3 type: #'AbstractInstruction *'>
  	<var: #jumpOutOfBounds4 type: #'AbstractInstruction *'>
  	<var: #jumpIncorrectFormat1 type: #'AbstractInstruction *'>
  	<var: #jumpIncorrectFormat2 type: #'AbstractInstruction *'>
  	<var: #jumpIncorrectFormat3 type: #'AbstractInstruction *'>
  	<var: #jumpIncorrectFormat4 type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  
  	"Can I generate a quick path for this method ?"
  	((cogit seemsToBeInstantiating: objectMemory arrayFormat)
  		or: [cogit seemsToBeInstantiating: objectMemory firstByteFormat]) ifFalse: [^UnimplementedPrimitive].
  
  	"I redefine those name to ease program comprehension"
  	arrayReg := ReceiverResultReg.
  	startReg := Arg0Reg.
  	stopReg := Arg1Reg.
  	replReg := ClassReg.
  	repStartReg := SendNumArgsReg.
  	
  	"Load arguments in reg"
  	cogit genStackArgAt: 0 into: repStartReg.
  	cogit genStackArgAt: 1 into: replReg.
  	cogit genStackArgAt: 2 into: stopReg.
  	cogit genStackArgAt: 3 into: startReg.
  
  	"start,stop,repStart Smis or fail the primitive"
  	jumpNotSmi1 := self genJumpNotSmallInteger: repStartReg scratchReg: TempReg.
  	jumpNotSmi2 := self genJumpNotSmallInteger: stopReg scratchReg: TempReg.
  	jumpNotSmi3 := self genJumpNotSmallInteger: startReg scratchReg: TempReg.
  	"repl non immediate or fail the primitive"
  	jumpImm := self genJumpImmediate: replReg.
  	
  	"if start>stop primitive success"
  	cogit CmpR: startReg R: stopReg.
  	jumpEmpty := cogit JumpLess: 0.
  	
  	"If receiver immutable fail the primitive "
  	self
  		cppIf: IMMUTABILITY
  		ifTrue: [jumpImmutable := self genJumpImmutable: ReceiverResultReg scratchReg: TempReg].
  		
  	"0 >= start, fail"
  	cogit CmpCq: (objectMemory integerObjectOf: 0) R: startReg.
  	jumpOutOfBounds1 := cogit JumpLessOrEqual: 0.
  	
  	"0 >= replStart, fail"
  	cogit CmpCq: (objectMemory integerObjectOf: 0) R: repStartReg.
  	jumpOutOfBounds2 := cogit JumpLessOrEqual: 0.
  
  	"--- Pointer object version ---"
  	(cogit seemsToBeInstantiating: objectMemory arrayFormat) ifTrue:
  		["Are they both array format ?"
  		self genGetFormatOf: arrayReg into: TempReg.
  		self genGetFormatOf: replReg into: startReg.
  		cogit CmpCq: objectMemory arrayFormat R: startReg.
  		jumpIncorrectFormat1 := cogit JumpNonZero: 0.
  		cogit CmpCq: objectMemory arrayFormat R: TempReg.
  		jumpIncorrectFormat2 := cogit JumpNonZero: 0.
  	
  		"Both objects are arrays,"
  		self genGetNumSlotsOf: arrayReg into: TempReg.
  		self genConvertSmallIntegerToIntegerInReg: stopReg.
  	
  		"arr size < stop"
  		cogit CmpR: TempReg R: stopReg.
  		jumpOutOfBounds3 := cogit JumpGreater: 0.
  	
  		"rep size < repStart - start + stop"
  		self genGetNumSlotsOf: replReg into: TempReg.
  		cogit genStackArgAt: 3 into: startReg.
  		self genConvertSmallIntegerToIntegerInReg: startReg.
  		self genConvertSmallIntegerToIntegerInReg: repStartReg.
  		cogit SubR: startReg R: stopReg.
  		cogit AddR: repStartReg R: stopReg.
  		"stopReg: stop - start + repStart"
  		cogit CmpR: TempReg R: stopReg.
  		jumpOutOfBounds4 := cogit JumpGreater: 0.
  	
  		"Everything in bounds"
  		"PossibleRemembered object"
  		cogit MoveCw: objectMemory storeCheckBoundary R: TempReg.
  		cogit CmpR: TempReg R: arrayReg.
  		jmpDestYoung := cogit JumpBelow: 0.
  		self checkRememberedInTrampoline ifFalse: 
  			[jmpAlreadyRemembered := self genCheckRememberedBitOf: arrayReg scratch: TempReg].
+ 		cogit backEnd saveAndRestoreLinkRegAround:
+ 			[self callStoreCheckTrampoline].
- 		self callStoreCheckTrampoline.
  		jmpDestYoung jmpTarget: cogit Label.
  		self checkRememberedInTrampoline ifFalse: 
  			[jmpAlreadyRemembered jmpTarget: cogit Label].
  	
  		"Copy the array"
  		cogit genStackArgAt: 2 into: stopReg.
  		self genConvertSmallIntegerToIntegerInReg: stopReg.
  		"Shift replReg to read it with startReg offset"
  		cogit SubR: startReg R: repStartReg. 
  		cogit LogicalShiftLeftCq: objectMemory shiftForWord R: repStartReg.
  		cogit AddR: repStartReg R: replReg. 
  		"shift by baseHeaderSize and then move from 1 relative to zero relative"
  		adjust := (objectMemory baseHeaderSize >> objectMemory shiftForWord) - 1. 
  		adjust ~= 0 ifTrue: 
  			[ cogit AddCq: adjust R: startReg. 
  			  cogit AddCq: adjust R: stopReg ].
  	
  		"Tight copying loop"
  		instr := cogit MoveXwr: startReg R: replReg R: TempReg.
  		cogit MoveR: TempReg Xwr: startReg R: arrayReg.
  		cogit AddCq: 1 R: startReg.
  		cogit CmpR: startReg R: stopReg.
  		cogit JumpAboveOrEqual: instr.
  		
  		jumpEmpty jmpTarget: cogit genPrimReturn.
  	
  		"CANNOT REACH by falling though"
  	
  		jumpIncorrectFormat1 jmpTarget: (jumpIncorrectFormat2 jmpTarget: cogit Label)].
  	
  	"--- Byte object version ---"
  	(cogit seemsToBeInstantiating: objectMemory firstByteFormat) ifTrue:
  		["Are they both byte array format ? CompiledMethod excluded"
  		self genGetFormatOf: arrayReg into: TempReg.
  		self genGetFormatOf: replReg into: repStartReg.
  		cogit CmpCq: objectMemory firstByteFormat R: repStartReg.
  		jumpIncorrectFormat1 := cogit JumpLess: 0.
  		cogit CmpCq: objectMemory firstCompiledMethodFormat R: repStartReg.
  		jumpIncorrectFormat2 := cogit JumpGreaterOrEqual: 0.
  		cogit CmpCq: objectMemory firstByteFormat R: TempReg.
  		jumpIncorrectFormat3 := cogit JumpLess: 0.
  		cogit CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.
  		jumpIncorrectFormat4 := cogit JumpGreaterOrEqual: 0.
  		
  		"Both objects are byte arrays"
  		self genGetNumSlotsOf: arrayReg into: startReg.
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: startReg).
  		cogit AndCq: objectMemory wordSize - 1 R: TempReg R: TempReg.
  		cogit SubR: TempReg R: startReg.
  		self genConvertSmallIntegerToIntegerInReg: stopReg.
  	
  		"arr size < stop"
  		cogit CmpR: startReg R: stopReg.
  		jumpOutOfBounds3 := cogit JumpGreater: 0.
  	
  		"rep size < repStart - start + stop"
  		cogit MoveR: repStartReg R: TempReg. "TempReg holds repl format"
  		cogit genStackArgAt: 0 into: repStartReg.
  		cogit genStackArgAt: 3 into: startReg.
  		self genConvertSmallIntegerToIntegerInReg: startReg.
  		self genConvertSmallIntegerToIntegerInReg: repStartReg.
  		cogit SubR: startReg R: stopReg.
  		cogit AddR: repStartReg R: stopReg.
  		
  		self genGetNumSlotsOf: replReg into: startReg.
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: startReg).
  		cogit AndCq: objectMemory wordSize - 1 R: TempReg R: TempReg.
  		cogit SubR: TempReg R: startReg.
  		
  		"stopReg: stop - start + repStart"
  		cogit CmpR: startReg R: stopReg.
  		jumpOutOfBounds4 := cogit JumpGreater: 0.
  	
  		"Everything in bounds"
  		"Copy the bytes"
  		cogit genStackArgAt: 3 into: startReg.
  		self genConvertSmallIntegerToIntegerInReg: startReg.
  		cogit genStackArgAt: 2 into: stopReg.
  		self genConvertSmallIntegerToIntegerInReg: stopReg.
  		"Shift replReg to read it with startReg offset"
  		cogit SubR: startReg R: repStartReg. 
  		cogit AddR: repStartReg R: replReg. 
  		"shift by baseHeaderSize and then move from 1 relative to zero relative"
  		adjust := objectMemory baseHeaderSize - 1.
  		adjust ~= 0 ifTrue: 
  			[ cogit AddCq: adjust R: startReg. 
  			  cogit AddCq: adjust R: stopReg.  ].
  	
  		"Tight copying loop"
  		instr := cogit MoveXbr: startReg R: replReg R: TempReg.
  		cogit MoveR: TempReg Xbr: startReg R: arrayReg.
  		cogit AddCq: 1 R: startReg.
  		cogit CmpR: startReg R: stopReg.
  		cogit JumpAboveOrEqual: instr.
  		
  		jumpEmpty jmpTarget: cogit genPrimReturn.
  	
  		"CANNOT REACH by falling though"
  	
  		jumpIncorrectFormat4 
  			jmpTarget: (jumpIncorrectFormat3 
  				jmpTarget: (jumpIncorrectFormat2 
  					jmpTarget: (jumpIncorrectFormat1 jmpTarget: cogit Label)))].
  
  	(result := cogit compileInterpreterPrimitive) < 0 ifTrue: [^result].
  	
  	jumpImm 
  		jmpTarget: (jumpNotSmi1
  				jmpTarget: (jumpNotSmi2
  						jmpTarget: (jumpNotSmi3 jmpTarget: cogit Label))).
  	jumpOutOfBounds1 
  		jmpTarget: (jumpOutOfBounds2 
  			jmpTarget: (jumpOutOfBounds3 
  				jmpTarget: (jumpOutOfBounds4 
  					jmpTarget: jumpImm getJmpTarget))).
  	self
  		cppIf: IMMUTABILITY
  		ifTrue: [jumpImmutable jmpTarget: jumpImm getJmpTarget].
  
  	^ CompletePrimitive!

Item was changed:
  VMStructType subclass: #CogSimStackEntry
  	instanceVariableNames: 'cogit objectRepresentation type spilled liveRegister register offset constant bcptr'
  	classVariableNames: ''
  	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
+ !CogSimStackEntry commentStamp: 'eem 1/22/2018 17:13' prior: 0!
+ A CogSimStackEntry represents an object pushed on the stack, but during the partial evaluation that occurs as part of the StackToRegisterMappingCogit's compilation.  Bytecodes that produce operands (push items onto the stack) push suitably descriptive instances of CogSimStackEntry onto the simStack (simulation stack).  Bytecodes that consume operands (sends, assignments, returns, etc) take items off the simStack.  Hence the generated code avoids pushing items onto the real stack, and the StackToRegisterMappngCogit can put the operands found on the simStack in registers, etc.  Hence actual stack traffic is much reduced, a much more efficient calling convention is enabled, and so overall performance is increased.  This scheme is due to L. Peter Deutsch and extended here.
- !CogSimStackEntry commentStamp: 'eem 2/25/2017 11:14' prior: 0!
- A CogSimStackEntry represents an object pushed on the stack, but during the partial evaluation that occurs as part of the StackToRegisterMappingCogit's compilation.  Bytecodes that produce operands (push items onto the stack) push suitably descriptive instances of CogSimStackEntry onto the simStack (simulation stack).  Bytecodes that cnsume operands (sends, assignments, returns, etc) take items off the simStack.  Hence teh generated code avoids pushing items onto the real stack, and the StackToRegisterMappngCogit can put the operands found on the simSTack in registers, etc.  Hence actual stack raffic is much reduced, a much more efficient calling convention is enabled, and so overall performance is increased.  This scheme is due to L. Peter Deutsch and extended here.
  
  Instance Variables
  	bcptr:					<Integer>
  	cogit:					<StackToRegisterMappingCogit>
  	constant:				<Oop>
  	liveRegister:			<Integer>
  	objectRepresentation:	<CogObjectRepresentation>
  	offset:					<Integer>
  	register:				<Integer>
  	spilled:					<Boolean>
  	type:					<Integer from SSBaseOffset, SSConstant, SSRegister or SSSpill>
  
  bcptr
  	- the bytecode PC at which this particular entry was created (pushed onto the stack).
  
  cogit
  	- the StackToRegisterMappingCogit using this instance
  
  constant
  	- if type = SSConstant then this is the constant's oop
  
  liveRegister
  	- unused other than for simSelf.  This is here for simSelf and for the subclass CogRegisterAllocatingSimStackEntry
  
  objectRepresentation
  	- the CogObjectRepresentation in use for the current object model
  
  offset
  	- if type = SSBaseOffset or type = SSSpill then this is the offset from register
  
  register
  	- type = SSBaseOffset or type = SSSpill or type = SSRegister then this is the register's code (NoReg, TempReg, ReceiverResultReg et al)
  
  spilled
  	- if true, then this entry has been spilled onto the actual stack (or rather code has been generated to push the entry onto the real stack)
  
  type
  	- SSBaseOffset, SSConstant, SSRegister or SSSpill!

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)
  				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:
+ 		[(self addressOf: simSelf) storeToReg: ReceiverResultReg].
- 		[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!



More information about the Vm-dev mailing list