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

commits at source.squeak.org commits at source.squeak.org
Fri Apr 8 19:24:27 UTC 2016


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

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

Name: VMMaker.oscog-cb.1786
Author: cb
Time: 8 April 2016, 12:20:06.531273 pm
UUID: bb4e05ae-a8a5-4615-8a4a-d07948350a58
Ancestors: VMMaker.oscog-eem.1785

Almost finished the abstraction over constants I added months ago.

I would like to check once the simulator works again on my machine about the SubCW instruction used in must be boolean to understand why SubCq was not working, and add the proper comment if SubCq can't be used, or use it if possible.

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

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetActiveContextLarge:inBlock: (in category 'initialization') -----
  genGetActiveContextLarge: isLarge inBlock: isInBlock
  	"Create a trampoline to answer the active context that will
  	 answer it if a frame is already married, and create it otherwise.
  	 Assume numArgs is in SendNumArgsReg and ClassReg is free."
  	| header slotSize jumpSingle loopHead jumpNeedScavenge continuation exit |
  	<var: #jumpNeedScavenge type: #'AbstractInstruction *'>
  	<var: #continuation type: #'AbstractInstruction *'>
  	<var: #jumpSingle type: #'AbstractInstruction *'>
  	<var: #loopHead type: #'AbstractInstruction *'>
  	<var: #exit type: #'AbstractInstruction *'>
  	cogit "load the flag; stash it in both TempReg & ClassReg; do the compare (a prime candidated for use of AndCq:R:R:)"
  		MoveMw: FoxMethod r: FPReg R: ClassReg;
  		AndCq: MFMethodFlagHasContextFlag R: ClassReg R: TempReg.
  	jumpSingle := cogit JumpZero: 0. "jump if flag bit not set"
  	cogit "since the flag bit was set, get the context in the receiver reg and return"
  		MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
  		RetN: 0.
  	jumpSingle jmpTarget: cogit Label.
  
  	"OK, it doesn't exist; instantiate and initialize it"
  	"set the hasContext flag; See CoInterpreter class>>initializeFrameIndices"
  	cogit
  		OrCq: MFMethodFlagHasContextFlag R: ClassReg;
  		MoveR: ClassReg Mw: FoxMethod r: FPReg.
  	"now get the home CogMethod into ClassReg and save for post-instantiation."
  	isInBlock
  		ifTrue:
  			[cogit
  				SubCq: 3 R: ClassReg; "-3 is -(hasContext+isBlock) flags"
  				MoveM16: 0 r: ClassReg R: TempReg;
  				SubR: TempReg R: ClassReg]
  		ifFalse:
  			[cogit SubCq: 1 R: ClassReg]. "-1 is hasContext flag"
  
  	"instantiate the context..."
  	slotSize := isLarge ifTrue: [LargeContextSlots] ifFalse: [SmallContextSlots].
  	header := objectMemory
  					headerForSlots: slotSize
  					format: objectMemory indexablePointersFormat
  					classIndex: ClassMethodContextCompactIndex.
  	self flag: #endianness.
  	cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
  	self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
  	cogit
  		MoveR: ReceiverResultReg R: TempReg;
  		AddCq: (objectMemory smallObjectBytesForSlots: slotSize) R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	jumpNeedScavenge := cogit JumpAboveOrEqual: 0.
  
  	"Now initialize the fields of the context.  See CoInterpreter>>marryFrame:SP:copyTemps:"
  	"sender gets frame pointer as a SmallInteger"
  	continuation :=
  	cogit MoveR: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (SenderIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"pc gets frame caller as a SmallInteger"
  	cogit MoveMw: FoxSavedFP r: FPReg R: TempReg.
  	self genSetSmallIntegerTagsIn: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (InstructionPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the method field, freeing up ClassReg again, and frame's context field,"
  	cogit
  		MoveMw: (cogit offset: CogMethod of: #methodObject) r: ClassReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (MethodIndex * objectMemory wordSize) r: ReceiverResultReg;
  		MoveR: ReceiverResultReg Mw: FoxThisContext r: FPReg.
  
  	"Now compute stack pointer; this is stackPointer (- 1 for return pc if a CISC) - framePointer - wordSize (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
  	"TPR note - the code here is actually doing
  	context stackPointer := ((((fp - sp) / wordSize) - [3|4]) + num args) asSmallInteger"
  	cogit
  		MoveR: FPReg R: TempReg;
  		SubR: SPReg R: TempReg;
  		LogicalShiftRightCq: self log2BytesPerWord R: TempReg;
  		SubCq: (cogit backEnd hasLinkRegister ifTrue: [3] ifFalse: [4]) R: TempReg;
  		AddR: SendNumArgsReg R: TempReg.
  	self genConvertIntegerToSmallIntegerInReg: TempReg.
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (StackPointerIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set closureOrNil to either the stacked receiver or nil"
  	isInBlock
  		ifTrue:
  			[cogit
  				MoveR: SendNumArgsReg R: TempReg;
  				AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  				MoveXwr: TempReg R: FPReg R: TempReg]
  		ifFalse:
+ 			[cogit genMoveNilR: TempReg].
- 			[cogit genMoveConstant: objectMemory nilObject R: TempReg].
  	cogit MoveR: TempReg Mw: objectMemory baseHeaderSize + (ClosureIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Set the receiver"
  	cogit
  		MoveMw: FoxMFReceiver r: FPReg R: TempReg;
  		MoveR: TempReg Mw: objectMemory baseHeaderSize + (ReceiverIndex * objectMemory bytesPerOop) r: ReceiverResultReg.
  
  	"Now copy the arguments.  This is tricky because of the shortage of registers,.  ClassReg ranges
  	 from 1 to numArgs (SendNumArgsReg), and from ReceiverIndex + 1 to ReceiverIndex + numArgs.
  	 1 to: numArgs do:
  		[:i|
  		temp := longAt(FPReg + ((SendNumArgs - i + 2) * wordSize)). +2 for saved pc and savedfp
  		longAtput(FPReg + FoxMFReceiver + (i * wordSize), temp)]"
  	"TPR note: this is a prime candidate for passing off to the backend to do at least faintly optimal code"
  	cogit MoveCq: 1 R: ClassReg.
  	loopHead := cogit CmpR: SendNumArgsReg R: ClassReg.
  	exit := cogit JumpGreater: 0.
  	cogit
  		MoveR: SendNumArgsReg R: TempReg;
  		SubR: ClassReg R: TempReg;
  		AddCq: 2 R: TempReg; "+2 for saved fp and saved pc"
  		MoveXwr: TempReg R: FPReg R: TempReg;
  		AddCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) R: ClassReg; "Now convert ClassReg from frame index to context index"
  		MoveR: TempReg Xwr: ClassReg R: ReceiverResultReg;
  		SubCq: ReceiverIndex + (objectMemory baseHeaderSize / objectMemory wordSize) - 1 R: ClassReg; "convert back adding 1 ;-)"
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
  	"Finally nil or copy the non-argument temps.
  	 ClassReg := FPReg + FoxMFReceiver.
  	 SendNumArgsReg := SendNumArgsReg+ReceiverIndex.
  	 [ClassReg := ClassReg - wordSize.
  	  backEnd hasLinkRegister
  			ifTrue: [ClassReg > SPReg]
  			ifFalse: [ClassReg >= SPReg]] whileTrue:
  		[receiver[SendNumArgsReg] := *ClassReg.
  		 SendNumArgsReg := SendNumArgsReg + 1]]"
  	coInterpreter marryFrameCopiesTemps ifFalse:
  		[cogit MoveCq: objectMemory nilObject R: TempReg].
  	cogit
  		MoveR: FPReg R: ClassReg;
  		AddCq: FoxMFReceiver R: ClassReg;
  		AddCq: ReceiverIndex + 1 + (objectMemory baseHeaderSize / objectMemory wordSize) R: SendNumArgsReg.
  	loopHead :=
  	cogit SubCq: objectMemory wordSize R: ClassReg.
  	cogit CmpR: SPReg R: ClassReg.
  	"If on a CISC there's a retpc for the trampoline call on top of stack; if on a RISC there isn't."
  	exit := cogit backEnd hasLinkRegister
  				ifTrue: [cogit JumpBelow: 0]
  				ifFalse: [cogit JumpBelowOrEqual: 0].
  	coInterpreter marryFrameCopiesTemps ifTrue:
  		[cogit MoveMw: 0 r: ClassReg R: TempReg].
  	cogit
  		MoveR: TempReg Xwr: SendNumArgsReg R: ReceiverResultReg;
  		AddCq: 1 R: SendNumArgsReg;
  		Jump: loopHead.
  	exit jmpTarget: cogit Label.
  
  	cogit RetN: 0.
  	
  	jumpNeedScavenge jmpTarget: cogit Label.
  	cogit backEnd saveAndRestoreLinkRegAround:
  		[cogit CallRT: ceScheduleScavengeTrampoline].
  	cogit Jump: continuation.
  	^0!

Item was changed:
  ----- Method: CogSimStackEntry>>ensureSpilledAt:from: (in category 'compile abstract instructions') -----
  ensureSpilledAt: baseOffset from: baseRegister
  	| inst |
  	<var: #inst type: #'AbstractInstruction *'>
  	spilled ifTrue:
  		[type = SSSpill ifTrue:
  			[self assert: (offset = baseOffset and: [register = baseRegister]).
  			 ^self]].
  	self assert: type ~= SSSpill.
  	cogit traceSpill: self.
  	type = SSConstant
  		ifTrue:
+ 			[inst := self genPushConstant: constant]
- 			[inst := cogit annotate: (cogit PushCw: constant) objRef: constant]
  		ifFalse:
  			[type = SSBaseOffset
  				ifTrue:
  					[cogit MoveMw: offset r: register R: TempReg.
  					 inst := cogit PushR: TempReg]
  				ifFalse:
  					[self assert: type = SSRegister.
  					 inst := cogit PushR: register].
  			 type := SSSpill.
  			 offset := baseOffset.
  			 register := baseRegister].
  	spilled := true.
  	annotateUse ifTrue:
  		[cogit annotateBytecode: inst.
  		 annotateUse := false]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
  compileFrameBuild
  	"Build a frame for a CogMethod activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		receiver (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	If there is a primitive and an error code the Nth temp is the error code.
  	Ensure SendNumArgsReg is set early on (incidentally to nilObj) because
  	it is the flag determining whether context switch is allowed on stack-overflow."
  	| jumpSkip |
  	<inline: false>
  	<var: #jumpSkip type: #'AbstractInstruction *'>
  	needsFrame ifFalse: [^self].
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  		(self PushCw: methodLabel asInteger)). "method"
+ 	self genMoveNilR: SendNumArgsReg.
- 	self genMoveConstant: objectMemory nilObject R: SendNumArgsReg.
  	self PushR: SendNumArgsReg. "context"
  	self PushR: ReceiverResultReg.
  	methodOrBlockNumArgs + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
  	(self methodUsesPrimitiveErrorCode: methodObj header: methodHeader) ifTrue:
  		[self compileGetErrorCode].
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	"If we can't context switch for this method, use a slightly
  	 slower overflow check that clears SendNumArgsReg."
  	(coInterpreter canContextSwitchIfActivating: methodObj header: methodHeader)
  		ifTrue:
  			[self JumpBelow: stackOverflowCall.
  			 stackCheckLabel := self Label]
  		ifFalse:
  			[jumpSkip := self JumpAboveOrEqual: 0.
  			 self MoveCq: 0 R: SendNumArgsReg.
  			 self Jump: stackOverflowCall.
  			 jumpSkip jmpTarget: (stackCheckLabel := self Label)].
  	self annotateBytecode: stackCheckLabel.
  	NewspeakVM ifTrue:
  		[numIRCs > 0 ifTrue:
  		 	[self PrefetchAw: theIRCs]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
  compileFullBlockMethodFrameBuild: numCopied
  	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		closure (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	Avoid use of SendNumArgsReg which is the flag determining whether
  	context switch is allowed on stack-overflow."
  	<inline: false>
  	needsFrame ifFalse: [^self].
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	"Think of ClassReg as ClosureReg"
  	self MoveR: ReceiverResultReg R: ClassReg.
  	"The block method field must have its MFMethodFlagIsBlockFlag bit set.
  	 We arrange this using a labelOffset.  A hack, but it works."
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  			(self PushCw: methodLabel asInteger));
  			setLabelOffset: MFMethodFlagIsBlockFlag.. "method"
+ 	self genMoveNilR: SendNumArgsReg.
- 	self genMoveConstant: objectMemory nilObject R: SendNumArgsReg.
  	self PushR: SendNumArgsReg. "context"
  	"Closure is on stack and initially in ReceiverResultReg.
  	 It is safe to use Arg0Reg because reg args are pushed by the value primitives if there are any.".
  
  	self flag: #TODO. "we could follow the receiver only if the block has inst var ref. Currently we use scanMethod for fullBlock 
  	and that scanner does not provide this information. We could extend it based on the scanBlock: method"
  	"Use ReceiverResultReg for the closure to agree with store check trampoline"
  	objectRepresentation
  		genLoadSlot: FullClosureReceiverIndex
  			sourceReg: ClassReg
  				destReg: Arg0Reg.
  	objectRepresentation
  		genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: FullClosureReceiverIndex in: ReceiverResultReg.
  	self MoveR: Arg0Reg R: ReceiverResultReg.
  
  	self PushR: ReceiverResultReg. "closure receiver"
  	"Push copied values"
  	0 to: numCopied - 1 do:
  		[:i|
  		objectRepresentation
  			genLoadSlot: i + FullClosureFirstCopiedValueIndex
  			sourceReg: ClassReg
  			destReg: TempReg.
  		self PushR: TempReg].
  	"Push slots for temps"
  	methodOrBlockNumArgs + numCopied + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
  	
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	self JumpBelow: stackOverflowCall.
  	stackCheckLabel := (self annotateBytecode: self Label)!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genAnnotatedSubCw:R: (in category 'constant support') -----
+ genAnnotatedSubCw: constant R: reg
+ 	"generates a SubCW instruction with an explicit annotation. This is called (as of today) only by the branch generation methods.
+ 	The annotation needs to be there for some reasons unknown to me (removing the annotation crashes the must be boolean trampolines)"
+ 	<inline: true>
+ 	self flag: #TOCHECK. "We will check with eliot if this could be a SubCq, and if not, put the proper comment"
+ 	self annotate: (self SubCw: constant R: TempReg) objRef: reg.
+ 	!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genCmpConstant:R: (in category 'constant support') -----
+ genCmpConstant: constant R: register
+ 	"If the objectMemory allows it, generates a quick constant cmp, else generates a word constant cmp"
+ 	<inline: true>
+ 	^ (objectRepresentation shouldAnnotateObjectReference: constant)
+ 		ifTrue: [ self annotate: (self CmpCw: constant R: register) objRef: constant ]
+ 		ifFalse: [ self CmpCq: constant R: register ]
+ 	!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genCompConstant:R: (in category 'bytecode generator support') -----
- genCompConstant: constant R: register
- 	<inline: true>
- 	^ (objectRepresentation shouldAnnotateObjectReference: constant)
- 		ifTrue: [ self annotate: (self CmpCw: constant R: register) objRef: constant ]
- 		ifFalse: [ self CmpCq: constant R: register ]
- 	!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	<inline: false>
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	| ok |
  	<var: #ok type: #'AbstractInstruction *'>
  	extA := 0.
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self PopR: TempReg.
+ 	self genAnnotatedSubCw: boolean R: TempReg.
- 	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self CallRT: (boolean == objectMemory falseObject
  					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  	ok jmpTarget: (self annotateBytecode: self Label).
  	^0!

Item was changed:
+ ----- Method: SimpleStackBasedCogit>>genMoveConstant:R: (in category 'constant support') -----
- ----- Method: SimpleStackBasedCogit>>genMoveConstant:R: (in category 'bytecode generator support') -----
  genMoveConstant: constant R: reg
+ 	"If the objectMemory allows it, generates a quick constant move, else generates a word constant move"
  	<inline: true>
  	^ (objectRepresentation shouldAnnotateObjectReference: constant)
+ 		ifTrue: [ self annotate: (self MoveCw: constant R: reg) objRef: constant ]
- 		ifTrue: [ (self annotate: (self MoveCw: constant R: reg) objRef: constant) ]
  		ifFalse: [ self MoveCq: constant R: reg ]
  	
  	!

Item was changed:
+ ----- Method: SimpleStackBasedCogit>>genMoveFalseR: (in category 'constant support') -----
- ----- Method: SimpleStackBasedCogit>>genMoveFalseR: (in category 'bytecode generator support') -----
  genMoveFalseR: reg
  	<inline: true>
  	^ self genMoveConstant: objectMemory falseObject R: reg
  	!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genMoveNilR: (in category 'constant support') -----
+ genMoveNilR: reg
+ 	<inline: true>
+ 	^ self genMoveConstant: objectMemory nilObject R: reg
+ 	!

Item was changed:
+ ----- Method: SimpleStackBasedCogit>>genMoveTrueR: (in category 'constant support') -----
- ----- Method: SimpleStackBasedCogit>>genMoveTrueR: (in category 'bytecode generator support') -----
  genMoveTrueR: reg
  	<inline: true>
  	^ self genMoveConstant: objectMemory trueObject R: reg
  	!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPushConstant: (in category 'constant support') -----
+ genPushConstant: constant
+ 	"If the objectMemory allows it, generates a quick constant push, else generates a word constant push"
+ 	<inline: true>
+ 	^ (objectRepresentation shouldAnnotateObjectReference: constant)
+ 		ifTrue: [ self annotate: (self PushCw: constant) objRef: constant ]
+ 		ifFalse: [ self PushCq: constant ]
+ 	!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushLiteral: (in category 'bytecode generator support') -----
  genPushLiteral: literal
+ 	self genPushConstant: literal.
- 	self annotate: (self PushCw: literal) objRef: literal.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genQuickReturnConst (in category 'primitive generators') -----
  genQuickReturnConst
  	<api> "because selected by CoInterpreter>>quickPrimitiveGeneratorFor:"
  	| constant |
  	constant := coInterpreter quickPrimitiveConstantFor: primitiveIndex.
+ 	self genMoveConstant: constant R: ReceiverResultReg.
- 	self annotate:
- 			((objectRepresentation isImmediate: constant)
- 				ifTrue: [self MoveCq: constant R: ReceiverResultReg]
- 				ifFalse: [self MoveCw: constant R: ReceiverResultReg])
- 		objRef: constant.
  	self genUpArrowReturn.
  	^UnfailingPrimitive!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genReturnNil (in category 'bytecode generators') -----
  genReturnNil
+ 	self genMoveNilR: ReceiverResultReg.
- 	self genMoveConstant: objectMemory nilObject R: ReceiverResultReg.
  	^self genUpArrowReturn!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genReturnNilFromBlock (in category 'bytecode generators') -----
  genReturnNilFromBlock
  	self assert: inBlock.
+ 	self genMoveNilR: ReceiverResultReg.
- 	self genMoveConstant: objectMemory nilObject R: ReceiverResultReg.
  	^self genBlockReturn!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genCounterTripOnlyJumpIf:to: (in category 'bytecode generator support') -----
  genCounterTripOnlyJumpIf: boolean to: targetBytecodePC 
  	"Specific version if the branch is only reached while falling through if the counter trips after an inlined #== branch. We do not regenerate the counter logic in this case to avoid 24 bytes instructions."
  	
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #mustBeBooleanTrampoline type: #'AbstractInstruction *'>
  
  	| ok mustBeBooleanTrampoline |
  
  	extA := 0.
  
  	self ssFlushTo: simStackPtr - 1.
  	
  	self ssTop popToReg: TempReg.
  	
  	self ssPop: 1.
  
  	counterIndex := counterIndex + 1. "counters are increased / decreased in the inlined branch"
  
  	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
  	self ssAllocateRequiredReg: SendNumArgsReg.
  	self MoveCq: 1 R: SendNumArgsReg.
  	
  	"The first time this is reached, it calls necessarily the counter trip for the trampoline because SendNumArgsReg is non zero"
  	mustBeBooleanTrampoline := self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  
  	self annotateBytecode: self Label.
  
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
+ 	self genAnnotatedSubCw: boolean R: TempReg.
- 	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  		
  	ok := self JumpZero: 0.
  	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."		
  
  	self Jump: mustBeBooleanTrampoline.
  	
  	ok jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	"The heart of performance counting in Sista.  Conditional branches are 6 times less
  	 frequent than sends and can provide basic block frequencies (send counters can't).
  	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
  	 and a lower half counting untaken executions of the branch.  Executing the branch
  	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
  	 decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)
  	 so that scanning for send and branch data is simplified and that branch data is correct."
  	<inline: false>
  	| ok counterAddress countTripped retry nextPC nextDescriptor |
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #nextDescriptor type: #'AbstractInstruction *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
  	
  	branchReachedOnlyForCounterTrip ifTrue: 
  		[ branchReachedOnlyForCounterTrip := false.
  		^ self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC ].
  	
  	boolean == objectMemory falseObject ifTrue:
  		[ "detection of and: / or:"
  		nextPC := bytecodePC + (self generatorAt: byte0) numBytes.
  		nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.
  		nextDescriptor generator ==  #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
  		nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset.
  		nextDescriptor generator ==  #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].  ].
  
  	extA := 0.
  
  	self ssFlushTo: simStackPtr - 1.
  	self ssTop popToReg: TempReg.
  	self ssPop: 1.
  
  	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
  	self ssAllocateRequiredReg: SendNumArgsReg.
  
  	retry := self Label.
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: SendNumArgsReg.
  	counterIndex := counterIndex + 1.
  
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
+ 	self genAnnotatedSubCw: boolean R: TempReg.
- 	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
  	self genFallsThroughCountLogicCounterReg: SendNumArgsReg counterAddress: counterAddress.
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."
  	
  	countTripped jmpTarget:
  		(self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
  						
  	"If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:
  	 trampoline will return directly to machine code, returning the boolean.  So the code should
  	 jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."
  	self annotateBytecode: self Label.
  
  	self Jump: retry.
  	
  	ok jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileBlockFrameBuild: (in category 'compile abstract instructions') -----
  compileBlockFrameBuild: blockStart
  	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
  	 Override to push the register receiver and register arguments, if any, and to correctly
  	 initialize the explicitly nilled/pushed temp entries (they are /not/ of type constant nil)."
  	super compileBlockFrameBuild: blockStart.
  	methodOrBlockNumTemps := blockStart numArgs + blockStart numCopied + blockStart numInitialNils.
  	self initSimStackForFramefulMethod: blockStart startpc.
  	blockStart numInitialNils > 0 ifTrue:
  		[blockStart numInitialNils > 1
  			ifTrue:
+ 				[self genMoveNilR: TempReg.
- 				[self genMoveConstant: objectMemory nilObject R: TempReg.
  				 1 to: blockStart numInitialNils do:
  					[:ign| self PushR: TempReg]]
  			ifFalse:
+ 				[self genPushConstant: objectMemory nilObject].
- 				[self
- 					annotate: (self PushCw: objectMemory nilObject)
- 					objRef: objectMemory nilObject].
  		 methodOrBlockNumTemps := blockStart numArgs + blockStart numCopied]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genEqualsEqualsComparisonArgIsConstant:rcvrIsConstant:argReg:rcvrReg: (in category 'bytecode generator support') -----
  genEqualsEqualsComparisonArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg
  	"Generates the Cmp instruction for #==. The instruction is different if one of the operands is a constant.
  	In the case of the v3 memory manager, the constant could be annotable." 
  	<inline: true>
  	argIsConstant 
+ 		ifTrue: [ self genCmpConstant: self ssTop constant R: rcvrReg ]
- 		ifTrue: [ self genCompConstant: self ssTop constant R: rcvrReg ]
  		ifFalse: [ rcvrIsConstant
+ 			ifTrue: [ self genCmpConstant: (self ssValue: 1) constant R: argReg ]
- 			ifTrue: [ self genCompConstant: (self ssValue: 1) constant R: argReg ]
  			ifFalse: [ self CmpR: argReg R: rcvrReg ] ].!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	<inline: false>
  	| desc fixup ok |
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #ok type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	(desc type == SSConstant
  	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
  		["Must arrange there's a fixup at the target whether it is jumped to or
  		  not so that the simStackPtr can be kept correct."
  		 fixup := self ensureFixupAt: targetBytecodePC - initialPC.
  		 "Must enter any annotatedConstants into the map"
  		 desc annotateUse ifTrue:
  			[self annotateBytecode: (self prevInstIsPCAnnotated
  											ifTrue: [self Nop]
  											ifFalse: [self Label])].
  		 "Must annotate the bytecode for correct pc mapping."
  		 self annotateBytecode: (desc constant = boolean
  									ifTrue: [self Jump: fixup]
  									ifFalse: [self prevInstIsPCAnnotated
  												ifTrue: [self Nop]
  												ifFalse: [self Label]]).
  		 ^0].
  	desc popToReg: TempReg.
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
+ 	self genAnnotatedSubCw: boolean R: TempReg.
- 	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  	
  	self extASpecifiesNoMustBeBoolean ifTrue: 
  		[ extA := 0. 
  		self annotateBytecode: self lastOpcode.
  		^ 0].
  	extA := 0.
  	
  .	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self CallRT: (boolean == objectMemory falseObject
  					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  	ok jmpTarget: (self annotateBytecode: self Label).
  	^0!



More information about the Vm-dev mailing list