[Vm-dev] VM Maker: VMMaker.oscog-cb.2201.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 26 07:54:27 UTC 2017


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2201.mcz

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

Name: VMMaker.oscog-cb.2201
Author: cb
Time: 26 April 2017, 9:53:43.043521 am
UUID: 65ff8b98-5c2c-4f50-b534-20acfb44f425
Ancestors: VMMaker.oscog-eem.2200

Added unsafe array copy (even though I am not using it right now, just not to loose the code).

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

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>callStoreCheckTrampoline (in category 'sista support') -----
+ callStoreCheckTrampoline
+ 	cogit CallRT: ceStoreCheckTrampoline!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>checkRememberedInTrampoline (in category 'sista support') -----
+ checkRememberedInTrampoline
+ 	<inline: true>
+ 	^ CheckRememberedInTrampoline!

Item was changed:
  ----- Method: SistaCogit>>genByteEqualsInlinePrimitive: (in category 'inline primitive generators') -----
  genByteEqualsInlinePrimitive: prim
  
  	"3021	Byte Object >> equals:length:	
  	The receiver and the arguments are both byte objects and have both the same size (length in bytes). 
  	The length argument is a smallinteger. 
  	Answers true if all fields are equal, false if not. 
  	Comparison is bulked to word comparison."
  	
  	"Overview: 
  	 1.	The primitive is called like that: [byteObj1 equals: byteObj2 length: length].
  	  	In the worst case we use 5 registers including TempReg 
  		and we produce a loop bulk comparing words.
  	 2.	The common case is a comparison against a cst: [byteString = 'foo'].
  		which produces in Scorch [byteString equals: 'foo' length: 3].
  		We try to generate fast code for this case with 3 heuristics:
  		- specific fast code if len is a constant
  		- unroll the loop if len < 2 * wordSize
  		- compile-time reads if str1 or str2 is a constant and loop is unrolled.
  		We use 3 registers including TempReg in the common case. 
  		We could use 1 less reg if the loop is unrolled, the instr is followed by a branch
  		AND one operand is a constant, but this is complicated enough.
  	3.	We ignore the case where all operands are constants 
  		(We assume Scorch simplifies it, it works but it is not optimised)"
  		
  	| str1Reg str2Reg lenReg extraReg jmp jmp2 needjmpZeroSize needLoop unroll jmpZeroSize instr lenCst mask |
  	<var: #jmp type: #'AbstractInstruction *'>
  	<var: #instr type: #'AbstractInstruction *'>
  	<var: #jmp2 type: #'AbstractInstruction *'>
  	<var: #jmpZeroSize type: #'AbstractInstruction *'>
  
  	"--- quick path for empty string---"
  	"This path does not allocate registers and right shift on negative int later in the code.
  	 Normally this is resolved by Scorch but we keep it for correctness and consistency"
  	self ssTop type = SSConstant ifTrue: 
  		[ lenCst := objectMemory integerValueOf: self ssTop constant.
  		  lenCst = 0 ifTrue: [ self ssPop: 3. self ssPushConstant: objectMemory trueObject. ^ 0 ] ].
  
  	"--- Allocating & loading registers --- "
  	needLoop := (self ssTop type = SSConstant and: [ lenCst <= (objectMemory wordSize * 2) ]) not.
  	unroll := needLoop not and: [lenCst > objectMemory wordSize ].
  	needLoop 
  		ifTrue: 
+ 			[ self assert: self ssTop spilled not.
+ 			  str1Reg := self allocateRegForStackEntryAt: 1 notConflictingWith: self emptyRegisterMask.
- 			[ str1Reg := self allocateRegForStackEntryAt: 1 notConflictingWith: self emptyRegisterMask.
  			  str2Reg := self allocateRegForStackEntryAt: 2 notConflictingWith: (self registerMaskFor: str1Reg).
+ 			  lenReg := self allocateRegForStackEntryAt: 0 notConflictingWith: (self registerMaskFor: str1Reg and: str2Reg).
- 			  lenReg := self allocateRegForStackEntryAt: 0 notConflictingWith: (self registerMaskFor:str1Reg and: str2Reg).
  			  (self ssValue: 1) popToReg: str1Reg.
  			  (self ssValue: 2) popToReg: str2Reg.
  			  extraReg := self allocateRegNotConflictingWith: (self registerMaskFor: str1Reg and: str2Reg and: lenReg)]
  		ifFalse: 
  			[ mask := self emptyRegisterMask.
  			  (self ssValue: 1) type = SSConstant ifFalse: 
  				[ str1Reg := self allocateRegForStackEntryAt: 1 notConflictingWith: mask.
  				  (self ssValue: 1) popToReg: str1Reg.
  				  mask := mask bitOr: (self registerMaskFor: str1Reg) ].
  			  (self ssValue: 2) type = SSConstant ifFalse: 
  				[ str2Reg := self allocateRegForStackEntryAt: 2 notConflictingWith: mask.
  				  (self ssValue: 2) popToReg: str2Reg.
  				  mask := mask bitOr: (self registerMaskFor: str2Reg) ].
  			  extraReg := self allocateRegNotConflictingWith: mask].
  	
  	"--- Loading LenReg (or statically resolving it) --- "
  	"LenReg is loaded with (lenInBytes + objectMemory baseHeaderSize - 1 >> shiftForWord)
  	 LenReg is the index for the last word to compare with MoveXwr:r:R:.
  	 The loop iterates from LenReg to first word of ByteObj"
  	self ssTop type = SSConstant 
  		ifTrue: "common case, str = 'foo'. We can precompute lenReg."
  			[ lenCst := lenCst + objectMemory baseHeaderSize - 1 >> objectMemory shiftForWord.
  			  needLoop ifTrue: [self MoveCq: lenCst R: lenReg ].
  			  needjmpZeroSize := false] 
  		ifFalse: "uncommon case, str = str2. lenReg in word computed at runtime."
  			[ self ssTop popToReg: lenReg.
  			  objectRepresentation genConvertSmallIntegerToIntegerInReg: lenReg.
  			  self CmpCq: 0 R: lenReg.
  			  jmpZeroSize := self JumpZero: 0.
  			  needjmpZeroSize := true.
  			  self AddCq: objectMemory baseHeaderSize - 1 R: lenReg.
  			  self ArithmeticShiftRightCq: objectMemory shiftForWord R: lenReg ].
  	
  	"--- Comparing the strings --- "
  	"LenReg has the index of the last word to read (unless no loop). 
  	 We decrement it to adjust -1 (0 in 64 bits) while comparing"
  	needLoop 
  		ifTrue:
  			[instr := self MoveXwr: lenReg R: str1Reg R: extraReg.
  			self MoveXwr: lenReg R: str2Reg R: TempReg.
  			self CmpR: extraReg R: TempReg.
  			jmp := self JumpNonZero: 0. "then string are not equal (jmp target)"
  			self AddCq: -1 R: lenReg.
  			self CmpCq: (objectMemory baseHeaderSize >> objectMemory shiftForWord) - 1 R: lenReg. "first word of ByteObj, stop looping."
  			self JumpNonZero: instr]
  		ifFalse: "Common case, only 1 or 2 word to check: no lenReg allocation, cst micro optimisations"
  			[self genByteEqualsInlinePrimitiveCmp: str1Reg with: str2Reg scratch1: extraReg scratch2: TempReg field: 0.
  			jmp := self JumpNonZero: 0. "then string are not equal (jmp target)"
  			unroll ifTrue: "unrolling more than twice generate more instructions than the loop so we don't do it"
  				[self genByteEqualsInlinePrimitiveCmp: str1Reg with: str2Reg scratch1: extraReg scratch2: TempReg field: 1.
  				jmp2 := self JumpNonZero: 0. "then string are not equal (jmp target)"]].
  	needjmpZeroSize ifTrue: [ jmpZeroSize jmpTarget: self Label ].
  	"fall through, strings are equal"
  	
  	"--- Pushing the result or pipelining a branch --- "	
  	self ssPop: 3.
  	self genByteEqualsInlinePrimitiveResult: jmp returnReg: extraReg.
  	unroll ifTrue: [jmp2 jmpTarget: jmp getJmpTarget].
  	^0!

Item was added:
+ ----- Method: SistaCogit>>genMoveAndAdjustSSEntry:into: (in category 'inline primitive generators') -----
+ genMoveAndAdjustSSEntry: ssEntry into: reg
+ 	<var: #ssEntry type: #'SimStackEntry *'>
+ 	<inline: true>
+ 	| adjust |
+ 	adjust := (objectMemory baseHeaderSize >> objectMemory shiftForWord) - 1. "shift by baseHeaderSize and then move from 1 relative to zero relative"
+ 	ssEntry type = SSConstant 
+ 		ifTrue: [self MoveCq: (objectMemory integerValueOf: ssEntry constant) + adjust R: reg.
+ 			      ssEntry spilled ifTrue: [self AddCq: objectMemory wordSize R: SPReg]]
+ 		ifFalse: 
+ 			[ssEntry popToReg: reg.
+ 			 objectRepresentation genConvertSmallIntegerToIntegerInReg: reg.
+ 			 adjust ~= 0 ifTrue: [ self AddCq: adjust R: reg. ]].	!

Item was changed:
  ----- Method: SistaCogit>>genQuinaryInlinePrimitive: (in category 'inline primitive generators') -----
  genQuinaryInlinePrimitive: prim
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#quaternaryInlinePrimitive:"
+ 	| srcReg destReg destIterator srcIterator limitReg jmpDestYoung instr jmpAlreadyRemembered jumpFinished singleIterator |
+ 	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
+ 	<var: #jmpDestYoung type: #'AbstractInstruction *'>
+ 	<var: #jumpFinished type: #'AbstractInstruction *'>
+ 	<var: #instr type: #'AbstractInstruction *'>
+ 	prim ~= 0 ifTrue: [^EncounteredUnknownBytecode].
+ 	
+ 	"5000	Pointer Object>> replaceFrom: srcPos to: srcLast with: startingAt: 
+ 	Src and dest are pointer objects. 
+ 	ScrPos, scrLast and destLast are smallintegers. 
+ 	Receiver is guaranteed to be mutable.  
+ 	Both ranges are in-bounds. 
+ 	The pointer accesses are raw (no inst var check). 
+ 	As for the normal primitive, the copy is linear from the first field to the last field (legacy code relies on it). 
+ 	Answers the receiver."
+ 	singleIterator := self ssTop type = SSConstant 
+ 						and: [(self ssValue: 3) type = SSConstant 
+ 						and: [self ssTop constant = (self ssValue: 3) constant]].
+ 	 srcIterator :=  self allocateRegForStackEntryAt: 0 notConflictingWith: self emptyRegisterMask.
+ 	 self genMoveAndAdjustSSEntry: (self ssValue: 0) into: srcIterator. 
+ 	 srcReg := self allocateRegForStackEntryAt: 1 notConflictingWith: (self registerMaskFor: srcIterator).
+ 	 (self ssValue: 1) popToReg: srcReg.
+ 	 limitReg := self allocateRegForStackEntryAt: 2 notConflictingWith: (self registerMaskFor: srcIterator and: srcReg).
+ 	 self genMoveAndAdjustSSEntry: (self ssValue: 2) into: limitReg.
+ 	singleIterator
+ 		ifTrue: 
+ 			[ destIterator := srcIterator ]
+ 		ifFalse: 
+ 			[ destIterator := self allocateRegForStackEntryAt: 3 notConflictingWith: (self registerMaskFor: srcIterator and: srcReg and: limitReg).
+ 			  self genMoveAndAdjustSSEntry: (self ssValue: 3) into: destIterator ].
+ 	 destReg := self allocateRegForStackEntryAt: 4 notConflictingWith: (self registerMaskFor: srcIterator and: srcReg and: limitReg and: destIterator).
+ 	 (self ssValue: 4) popToReg: destReg.
+ 	
+ 	"store check"
+ 	extB > 0 ifFalse:
+ 		[self MoveCw: objectMemory storeCheckBoundary R: TempReg.
+ 		 self CmpR: TempReg R: destReg.
+ 		 jmpDestYoung := self JumpBelow: 0.
+ 		 objectRepresentation checkRememberedInTrampoline ifFalse: 
+ 			[jmpAlreadyRemembered := objectRepresentation genCheckRememberedBitOf: destReg scratch: TempReg].
+ 		 objectRepresentation callStoreCheckTrampoline.
+ 		 jmpDestYoung jmpTarget: self Label.
+ 		 objectRepresentation checkRememberedInTrampoline ifFalse: 
+ 			[jmpAlreadyRemembered jmpTarget: self Label]].
+ 	extB := 0.
+ 	
+ 	"Fast copy - no store check"
+ 	instr := self CmpR: destIterator R: limitReg.
+ 	jumpFinished := self JumpBelow: 0.
+ 	self MoveXwr: srcIterator R: srcReg R: TempReg.
+ 	self MoveR: TempReg Xwr: destIterator R: destReg.
+ 	self AddCq: 1 R: srcIterator.
+ 	srcIterator ~= destIterator ifTrue: [ self AddCq: 1 R: destIterator ].
+ 	self Jump: instr.
+ 	jumpFinished jmpTarget: self Label.
+ 	
+ 	self ssPop: 5.
+ 	self ssPushRegister: destReg.
+ 	^ 0!
- 	^EncounteredUnknownBytecode!

Item was changed:
  ----- Method: StackInterpreter>>callPrimitiveBytecode (in category 'miscellaneous bytecodes') -----
  callPrimitiveBytecode
  	"V4:			249		11111001	i i i i i i i i	jjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjjj * 256)
  	 SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 V3/Spur:	139		10001011	i i i i i i i i	jjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
  	"Note that we simply skip a callPrimitiveBytecode at the start of a method
  	 that contains a primitive.  This because methods like Context(Part)>>reset
  	 have to be updated to skip the callPrimtiive bytecode otherwise."
  	SistaVM
  		ifTrue:
  			[| byte1 byte2 prim primSet header |
  			 byte1 := self fetchByte.
  			 byte2 := self fetchByte.
  			 self fetchNextBytecode.
  			 byte2 < 128 ifTrue:
  				[header := objectMemory methodHeaderOf: method.
  				 ((self methodHeaderHasPrimitive: header)
  				  and: [localIP asUnsignedInteger
  						= (self initialIPForHeader: header method: method) + (self sizeOfCallPrimitiveBytecode: header)]) ifTrue:
  					[^self].
  				 localIP := localIP - 3.
  				 ^self respondToUnknownBytecode].
  			 prim := byte2 - 128 << 8 + byte1.
  			 primSet := prim >> 13 bitAnd: 3.
  			 prim := prim bitAnd: 8191.
  			 primSet = 0 ifTrue: [
  				
  				 prim < 1000 ifTrue:
  					[^self nullaryInlinePrimitive: prim].
  
  				 prim < 2000 ifTrue:
  					[^self unaryInlinePrimitive: prim - 1000].
  				
  				 prim < 3000 ifTrue:
  					[^self binaryInlinePrimitive: prim - 2000].
+ 				
- 
  				 prim < 4000 ifTrue:
  					[^self trinaryInlinePrimitive: prim - 3000].
+ 
+ 				 prim < 5000 ifTrue:
+ 					[^self quaternaryInlinePrimitive: prim - 4000].
+ 
+ 				 prim < 6000 ifTrue:
+ 					[^self quinaryInlinePrimitive: prim - 5000].
+ 				
  			 ].
  		
  			LowcodeVM ifTrue: [
  				primSet = 1 ifTrue: [
  					prim < 1000 ifTrue:
  						[^self lowcodeNullaryInlinePrimitive: prim].
  
  					prim < 2000 ifTrue:
  						[^self lowcodeUnaryInlinePrimitive: prim - 1000].
  				
  					prim < 3000 ifTrue:
  						[^self lowcodeBinaryInlinePrimitive: prim - 2000].
  
  					prim < 4000 ifTrue:
  						[^self lowcodeTrinaryInlinePrimitive: prim - 3000].
  				].
  			].
  		
  			localIP := localIP - 3.
  			^self respondToUnknownBytecode]
  		ifFalse:
  			[| header |
  			 header := objectMemory methodHeaderOf: method.
  			 ((self methodHeaderHasPrimitive: header)
  			  and: [localIP asInteger = (self initialIPForHeader: header method: method)])
  				ifTrue:
  					[localIP := localIP + (self sizeOfCallPrimitiveBytecode: header) - 1.
  					 ^self fetchNextBytecode]
  				ifFalse:
  					[^self respondToUnknownBytecode]]!

Item was added:
+ ----- Method: StackInterpreter>>quaternaryInlinePrimitive: (in category 'miscellaneous bytecodes') -----
+ quaternaryInlinePrimitive: primIndex
+ 	"SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
+ 	<option: #SistaVM>
+ 	self respondToUnknownBytecode!

Item was added:
+ ----- Method: StackInterpreter>>quinaryInlinePrimitive: (in category 'miscellaneous bytecodes') -----
+ quinaryInlinePrimitive: primIndex
+ 	"SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
+ 	| src srcIndex dest destIndex destLimit oop |
+ 	<option: #SistaVM>
+ 	primIndex = 0 ifFalse: [self respondToUnknownBytecode].
+ 	dest := self internalStackValue: 4.
+ 	destIndex := (objectMemory integerValueOf: (self internalStackValue: 3)) - 1.
+ 	destLimit := (objectMemory integerValueOf: (self internalStackValue: 2)) - 1.
+ 	src := self internalStackValue: 1.
+ 	srcIndex := (objectMemory integerValueOf: (self internalStackValue: 0)) - 1.
+ 	self internalPop: 4.
+ 	destLimit < destIndex ifTrue: [^self].
+ 	(objectMemory isYoung: dest) ifFalse: [objectMemory possibleRootStoreInto: dest].
+ 	0 to: destLimit - destIndex do: [:i |
+ 		oop := objectMemory fetchPointer: srcIndex + i ofObject: src.
+ 		objectMemory storePointerUnchecked: destIndex + i ofObject: dest withValue: oop ].
+ 	!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>allocateRegForStackEntryAt:notConflictingWith: (in category 'simulation stack') -----
  allocateRegForStackEntryAt: index notConflictingWith: regMask
  	"If the stack entry is already in a register not conflicting with regMask, answers it,
  	else allocate a new register not conflicting with reg mask"
  	<var: #stackEntry type: #'CogSimStackEntry *'>
  	| stackEntry mask |
  	stackEntry := self ssValue: index.
  	mask := stackEntry registerMaskOrNone.
  	(mask ~= 0 and: [mask noMask: regMask]) ifTrue: 
+ 		[self flag: #TODO.
+ 		"When one does pushDup on a SSRegister
+ 		 followed by an operation reusing the register 
+ 		 but mutating the value of the register, then the value that was 
+ 		 dup is now refering to the register with a mutated value which
+ 		 is incorrect. This problem is serious as it can happen also with 
+ 		 multiple unsafe instructions (no dup involved)
+ 		 This is not a problem if the operation reusing the register is not 
+ 		 mutating the value of if all the dup values are used in the same 
+ 		 operation.
+ 		 => I think we should introduce allocateRegMutatingStackEntryAt:
+ 		notConflictingWith:upThrough:, used by operations mutating the reg
+ 		value and flushing partially the stack if somewhere between simSpill
+ 		and the ssEntries used by the operation someone uses also the same
+ 		register."
+ 		 ^stackEntry registerOrNone].
- 		[^stackEntry registerOrNone].
  	^self allocateRegNotConflictingWith: regMask!



More information about the Vm-dev mailing list