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

commits at source.squeak.org commits at source.squeak.org
Thu Jul 26 00:17:42 UTC 2018


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

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

Name: VMMaker.oscog-eem.2421
Author: eem
Time: 25 July 2018, 5:17:07.310927 pm
UUID: f273bc45-113b-4685-822c-f0db0293c206
Ancestors: VMMaker.oscog-eem.2420

Cogits.
Fix bad bug in pc mapping of methods containing primitives.  methodUsesPrimitiveErrorCode:header: used the initialPC inst var, rather than deriving the initialPC of the method parameter.  initialPC is stale/over ripe, being that of the last JITTED method.  So many methods containing primitives get their PC mapping wrong.  We haven't noticed this much because primiitves typically succeed.  Nuke an obsolete version of the method.

Have the Spur immutability store generators voidReceiverOptStatus, since with immutability, stores are suspension pioints (when an immutability check fails) and so receiverResultReg cannot be assumed to be live after a store.  Hence also implement SimpleStackBasedCogit>>voidReceiverOptStatus for compatibility ()a noop).

Cleanups:
Extend the comment for genGenericStorePop:slotIndex:destReg:needsStoreCheck:needsRestoreRcvr:needsImmutabilityCheck: (and hence also (forgive me!) reformat to fix confusing indentation).

Remove ssAllocateRequiredRegMask:upThrough:, inlining it into its callers, ssAllocateCall/RequiredReg:...

Clean up the computation of the register mask in SistaCogit>>genForwardersInlinedIdenticalOrNotIf:

Add a helpful comment to genCallMustBeBooleanFor: (I can never remember the selector the trampoline invokes).

Eliminate cr & lf in literal printing when decorating disassembly.

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

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreWithImmutabilityAndStoreCheckSourceReg:slotIndex:destReg:scratchReg:needRestoreRcvr: (in category 'compile abstract instructions') -----
  genStoreWithImmutabilityAndStoreCheckSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg needRestoreRcvr: needRestoreRcvr 
  	"Store check code is duplicated to use a single trampoline"
  	<option: #IMMUTABILITY>
  	| immutableJump jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered |
  	<var: #immutableJump type: #'AbstractInstruction *'>
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  
  	immutableJump := self genJumpImmutable: destReg scratchReg: scratchReg.
  	
  	cogit genTraceStores.
  	
  	"do the store"
  	cogit MoveR: sourceReg
  		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		   r: destReg.
  	
  	"store check"
  	jmpImmediate := self genJumpImmediate: sourceReg.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveCw: objectMemory storeCheckBoundary 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 := valueReg - 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."
  	CheckRememberedInTrampoline ifFalse:
  		[jmpAlreadyRemembered := self genCheckRememberedBitOf: destReg scratch: scratchReg].
  	"Set the inst var index for the benefit of the immutability check. The trampoline will
  	 repeat the check to choose between the immutbality violation and the store check."
  	immutableJump jmpTarget: cogit Label.
  	self genStoreTrampolineCall: index.
+ 	cogit voidReceiverOptStatus.
+ 	needRestoreRcvr ifTrue:
+ 		[cogit putSelfInReceiverResultReg].
- 	needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
  
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  		cogit Label)).
  	CheckRememberedInTrampoline ifFalse:
  		[jmpAlreadyRemembered jmpTarget: jmpSourceOld getJmpTarget].
  	^ 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreWithImmutabilityButNoStoreCheckSourceReg:slotIndex:destReg:scratchReg:needRestoreRcvr: (in category 'compile abstract instructions') -----
  genStoreWithImmutabilityButNoStoreCheckSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg needRestoreRcvr: needRestoreRcvr
  	"Gen an immutability check with no store check (e.g. assigning an immediate literal)"
  	<option: #IMMUTABILITY>
  	<var: #mutableJump type: #'AbstractInstruction *'>
  	<var: #immutabilityFailure type: #'AbstractInstruction *'>
  	| immutabilityFailure mutableJump |
  	
  	"imm check has its own trampoline"
  	mutableJump := self genJumpMutable: destReg scratchReg: scratchReg.
  	self genStoreTrampolineCall: index.
+ 	cogit voidReceiverOptStatus.
+ 	needRestoreRcvr ifTrue:
+ 		[cogit putSelfInReceiverResultReg].
- 	needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
  	immutabilityFailure := cogit Jump: 0.
  	mutableJump jmpTarget: cogit Label.
  
  	cogit genTraceStores.
  	
  	"do the store"
  	cogit MoveR: sourceReg
  		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		   r: destReg.
  		
  	immutabilityFailure jmpTarget: cogit Label.
  
  	^ 0!

Item was changed:
  ----- Method: Cogit>>genCallMustBeBooleanFor: (in category 'trampoline support') -----
  genCallMustBeBooleanFor: boolean
+ 	"Call ceSendMustBeBooleanTo: via the relevant trampoline."
  	^self CallRT: (boolean = objectMemory falseObject
  					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>lookupAddress: (in category 'labels') -----
  lookupAddress: address
  	| thing |
  	thing := objectMap
  				keyAtValue: address
  				ifAbsent:
  					[variables
  						keyAtValue: address
  						ifAbsent: [^nil]].
+ 	^(((thing isLiteral
- 	^(thing isLiteral
  		ifTrue: [thing storeString]
+ 		ifFalse: [thing asString]) contractTo: 64)
+ 			copyReplaceAll: String cr with: '\r')
+ 				copyReplaceAll: String lf with: '\n'!
- 		ifFalse: [thing asString]) contractTo: 64!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>methodUsesPrimitiveErrorCode (in category 'compile abstract instructions') -----
- methodUsesPrimitiveErrorCode
- 	"Answer if methodObj contains a primitive and uses the primitive error code."
- 	^(coInterpreter primitiveIndexOfMethod: methodObj header: methodHeader) > 0
- 	  and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)
- 			= (objectMemory
- 				fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
- 				ofObject: methodObj)]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>methodUsesPrimitiveErrorCode:header: (in category 'compile abstract instructions') -----
  methodUsesPrimitiveErrorCode: aMethodObj header: aMethodHeader
  	"Answer if aMethodObj contains a primitive and uses the primitive error code."
  	<inline: true>
  	^(coInterpreter primitiveIndexOfMethod: aMethodObj header: aMethodHeader) > 0
  	  and: [(coInterpreter longStoreBytecodeForHeader: aMethodHeader)
  			= (objectMemory
+ 				fetchByte: (coInterpreter startPCOfMethod: aMethodObj) + (coInterpreter sizeOfCallPrimitiveBytecode: aMethodHeader)
- 				fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: aMethodHeader)
  				ofObject: aMethodObj)]!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>voidReceiverOptStatus (in category 'bytecode generator support') -----
+ voidReceiverOptStatus
+ 	"No op in this cogit. Provided for compatibility with the cleverer subclasses."
+ 	<inline: true>!

Item was changed:
  ----- Method: SistaCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual
  	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask |
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #label type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpEqual type: #'AbstractInstruction *'>
  	<var: #jumpNotEqual type: #'AbstractInstruction *'>
  
  	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue:
  		[^super genForwardersInlinedIdenticalOrNotIf: orNot].
  
  	regMask := 0.
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
  	
  	"If an operand is an annotable constant, it may be forwarded, so we need to store it into a 
  	register so the forwarder check can jump back to the comparison after unforwarding the constant.
  	However, if one of the operand is an unnanotable constant, does not allocate a register for it 
  	(machine code will use operations on constants)."
- 	rcvrReg:= argReg := NoReg.
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
  		rcvrNeedsReg: unforwardRcvr 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
+ 
- 		
- 	argReg ~= NoReg ifTrue: [ regMask := self registerMaskFor: argReg ].
- 	rcvrReg ~= NoReg ifTrue: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
- 	
  	"Only interested in inlining if followed by a conditional branch."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[^ self 
  			genIdenticalNoBranchArgIsConstant: unforwardArg not
  			rcvrIsConstant: unforwardRcvr not
  			argReg: argReg 
  			rcvrReg: rcvrReg 
  			orNotIf: orNot].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ].
  	unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ].
  	
+ 	regMask := argReg = NoReg
+ 					ifTrue: [self registerMaskFor: rcvrReg]
+ 					ifFalse:
+ 						[rcvrReg = NoReg
+ 							ifTrue: [self registerMaskFor: argReg]
+ 							ifFalse: [self registerMaskFor: rcvrReg and: argReg]].
  	counterReg := self allocateRegNotConflictingWith: regMask.
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  	
  	self assert: (unforwardArg or: [ unforwardRcvr ]).
  	self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  	
  	orNot == branchDescriptor isBranchTrue "orNot is true for ~~"
  		ifFalse:
  			[ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger.
  			self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ]
  		ifTrue:
  			[ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger.
  			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ].
  	
  	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	self Jump: fixup.
  	
  	countTripped jmpTarget: self Label.
  	
  	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
  	self ssPop: -2. 
  	self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2. 
  	
  	"This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. 
  	We therefore directly assign the result to TempReg to save one move instruction"
  	jumpEqual := orNot ifFalse: [self JumpZero: 0] ifTrue: [self JumpNonZero: 0].
  	self genMoveFalseR: TempReg.
  	jumpNotEqual := self Jump: 0.
  	jumpEqual jmpTarget: (self genMoveTrueR: TempReg).
  	jumpNotEqual jmpTarget: self Label.
  	self ssPushRegister: TempReg.
  	
  	(self fixupAt: nextPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ].
  	
  	^ 0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genGenericStorePop:slotIndex:destReg:needsStoreCheck:needsRestoreRcvr:needsImmutabilityCheck: (in category 'bytecode generator stores') -----
  genGenericStorePop: popBoolean slotIndex: slotIndex destReg: destReg needsStoreCheck: needsStoreCheck needsRestoreRcvr: needsRestoreReceiver needsImmutabilityCheck: needsImmCheck
  	"Generates a store into an object that *cannot* be a context.
  	 This code is common between multiple stores (litVar, instVar, remoteInstVar, RemoteTemp)
  	 Multiple settings:
  	- needsStoreCheck (young into old object check)
  	- needRestoreRcvr (ensures the receiver is live across the store)
  	- needsImmCheck (do the call-back if the receiver is immutable)"
  	"We have two very different paths as only the immutability path requires a specific register 
+ 	for the value on top of stack as well as the stack flush.
+ 	N.B. If IMMUTABILITY then ReceiverResultReg/destReg will be smashed if needsImmCheck.
+ 		If not IMMUTABILITY then ReceiverResultReg will be preserved by the ceStoreCheck trampoline."
- 	for the value on top of stack as well as the stack flush"
  	| topReg |
  	<inline: true>
+ 	self cppIf: IMMUTABILITY ifTrue:
+ 		[needsImmCheck ifTrue: 
+ 			[self ssAllocateRequiredReg: ClassReg upThrough: simStackPtr - 1. "If already classReg don't spill it"
+ 			 "we replace the top value for the flush"
+ 			 self ssStoreAndReplacePop: popBoolean toReg: ClassReg.
+ 			 self ssFlushTo: simStackPtr.
+ 			 ^objectRepresentation 
+ 				genStoreWithImmutabilityCheckSourceReg: ClassReg 
+ 				slotIndex: slotIndex 
+ 				destReg: destReg 
+ 				scratchReg: TempReg 
+ 				needsStoreCheck: needsStoreCheck 
+ 				needRestoreRcvr: needsRestoreReceiver]].
+ 	topReg := self 
+ 				allocateRegForStackEntryAt: 0 
+ 				notConflictingWith: (self registerMaskFor: destReg). 
+ 	self ssStorePop: popBoolean toReg: topReg.
+ 	^objectRepresentation
+ 		genStoreSourceReg: topReg
+ 		slotIndex: slotIndex
+ 		destReg: destReg
+ 		scratchReg: TempReg
+ 		inFrame: needsFrame
+ 		needsStoreCheck: needsStoreCheck!
- 	self 
- 		cppIf: IMMUTABILITY
- 		ifTrue:
- 			[needsImmCheck
- 				ifTrue: 
- 					[self ssAllocateRequiredReg: ClassReg upThrough: simStackPtr - 1. "If already classReg don't spill it"
- 					 "we replace the top value for the flush"
- 					 self ssStoreAndReplacePop: popBoolean toReg: ClassReg.
- 					 self ssFlushTo: simStackPtr.
- 					 ^objectRepresentation 
- 						genStoreWithImmutabilityCheckSourceReg: ClassReg 
- 						slotIndex: slotIndex 
- 						destReg: destReg 
- 						scratchReg: TempReg 
- 						needsStoreCheck: needsStoreCheck 
- 						needRestoreRcvr: needsRestoreReceiver]].
- 		 topReg := self 
- 					allocateRegForStackEntryAt: 0 
- 					notConflictingWith: (self registerMaskFor: destReg). 
- 		 self ssStorePop: popBoolean toReg: topReg.
- 		 ^objectRepresentation
- 			genStoreSourceReg: topReg
- 			slotIndex: slotIndex
- 			destReg: destReg
- 			scratchReg: TempReg
- 			inFrame: needsFrame
- 			needsStoreCheck: needsStoreCheck
- 	!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateCallReg: (in category 'simulation stack') -----
  ssAllocateCallReg: requiredReg
  	"Allocate a register needed in a run-time call (i.e. flush uses of the
  	 register to the real stack).  Since the run-time can smash any and
  	 all caller-saved registers also flush all caller-saved registers."
+ 	<inline: true>
  	self ssAllocateRequiredRegMask: (CallerSavedRegisterMask
  										bitOr: (self registerMaskFor: requiredReg))
+ 		upThrough: simStackPtr
+ 		upThroughNative: simNativeStackPtr!
- 		upThrough: simStackPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateCallReg:and: (in category 'simulation stack') -----
  ssAllocateCallReg: requiredReg1 and: requiredReg2
  	"Allocate registers needed in a run-time call (i.e. flush uses of the
  	 registers to the real stack).  Since the run-time can smash any and
  	 all caller-saved registers also flush all caller-saved registers."
+ 	<inline: true>
  	self ssAllocateRequiredRegMask: (CallerSavedRegisterMask
  										bitOr: ((self registerMaskFor: requiredReg1)
  										bitOr: (self registerMaskFor: requiredReg2)))
+ 		upThrough: simStackPtr
+ 		upThroughNative: simNativeStackPtr!
- 		upThrough: simStackPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateCallReg:and:and: (in category 'simulation stack') -----
  ssAllocateCallReg: requiredReg1 and: requiredReg2 and: requiredReg3
  	"Allocate registers needed in a run-time call (i.e. flush uses of the
  	 registers to the real stack).  Since the run-time can smash any and
  	 all caller-saved registers also flush all caller-saved registers."
+ 	<inline: true>
  	self ssAllocateRequiredRegMask: (CallerSavedRegisterMask bitOr:
  										(self registerMaskFor: requiredReg1 and: requiredReg2 and: requiredReg3))
+ 		upThrough: simStackPtr
+ 		upThroughNative: simNativeStackPtr!
- 		upThrough: simStackPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateCallReg:and:and:and: (in category 'simulation stack') -----
  ssAllocateCallReg: requiredReg1 and: requiredReg2 and: requiredReg3 and: requiredReg4
  	"Allocate registers needed in a run-time call (i.e. flush uses of the
  	 registers to the real stack).  Since the run-time can smash any and
  	 all caller-saved registers also flush all caller-saved registers."
+ 	<inline: true>
  	self ssAllocateRequiredRegMask: (CallerSavedRegisterMask
  										bitOr: ((self registerMaskFor: requiredReg1)
  										bitOr: ((self registerMaskFor: requiredReg2)
  										bitOr: ((self registerMaskFor: requiredReg3)
  										bitOr: (self registerMaskFor: requiredReg4)))))
+ 		upThrough: simStackPtr
+ 		upThroughNative: simNativeStackPtr!
- 		upThrough: simStackPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateRequiredReg: (in category 'simulation stack') -----
  ssAllocateRequiredReg: requiredReg
+ 	<inline: true>
  	self ssAllocateRequiredRegMask: (self registerMaskFor: requiredReg)
+ 		upThrough: simStackPtr
+ 		upThroughNative: simNativeStackPtr!
- 		upThrough: simStackPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateRequiredReg:and: (in category 'simulation stack') -----
  ssAllocateRequiredReg: requiredReg1 and: requiredReg2
+ 	<inline: true>
  	self ssAllocateRequiredRegMask: ((self registerMaskFor: requiredReg1)
  										bitOr: (self registerMaskFor: requiredReg2))
+ 		upThrough: simStackPtr
+ 		upThroughNative: simNativeStackPtr!
- 		upThrough: simStackPtr!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateRequiredReg:upThrough: (in category 'simulation stack') -----
  ssAllocateRequiredReg: requiredReg upThrough: stackPtr
+ 	<inline: true>
  	self ssAllocateRequiredRegMask: (self registerMaskFor: requiredReg)
+ 		upThrough: stackPtr
+ 		upThroughNative: simNativeStackPtr!
- 		upThrough: stackPtr!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>ssAllocateRequiredRegMask:upThrough: (in category 'simulation stack') -----
- ssAllocateRequiredRegMask: requiredRegsMask upThrough: stackPtr
- 	<inline: true>
- 	self ssAllocateRequiredRegMask: requiredRegsMask upThrough: stackPtr upThroughNative: simNativeStackPtr.
- !



More information about the Vm-dev mailing list