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

commits at source.squeak.org commits at source.squeak.org
Sat Apr 25 13:19:50 UTC 2015


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

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

Name: VMMaker.oscog-cb.1255
Author: cb
Time: 25 April 2015, 3:17:57.287 pm
UUID: 939d4856-6309-444c-9ed9-32caf51a7001
Ancestors: VMMaker.oscog-cb.1254

Improved readability by using even more #genMoveConstant:R: instead of:
 (objectRepresentation shouldAnnotateObjectReference: constant)
		ifTrue: [ (self annotate: (self MoveCw: constant R: reg) objRef: constant) ]
		ifFalse: [ self MoveCq: constant R: reg ]

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

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>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;
  		MoveCq: (self low32BitsOf: header) R: TempReg;
  		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
  		MoveCq: header >> 32 R: TempReg;
  		MoveR: TempReg Mw: 4 r: ReceiverResultReg;
  		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 - 4 (1 each for saved pc, method, context, receiver) + 1 (1-relative) + numArgs"
  	"TPR note - the code here is actually doing
  	context stackPointer := ((((fp - sp) / 4) - [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 genMoveConstant: objectMemory nilObject R: TempReg].
- 			[cogit MoveCw: 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) * BytesPerWord)). +2 for saved pc and savedfp
  		longAtput(FPReg + FoxMFReceiver + (i * BytesPerWord), 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 - 4.
  	  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: CogObjectRepresentationFor32BitSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
  genNewArrayOfSize: size initialized: initialized
  	"Generate a call to code that allocates a new Array of size.
  	 The Array should be initialized with nils iff initialized is true.
  	 The size arg is passed in SendNumArgsReg, the result
  	 must come back in ReceiverResultReg."
  	| header skip |
  	<var: #skip type: #'AbstractInstruction *'>
  	self assert: size < objectMemory numSlotsMask.
  	header := objectMemory
  					headerForSlots: size
  					format: objectMemory arrayFormat
  					classIndex: ClassArrayCompactIndex.
  	self flag: #endianness.
  	cogit
  		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
  		MoveCq: (self low32BitsOf: header) R: TempReg;
  		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
  		MoveCq: header >> 32 R: TempReg;
  		MoveR: TempReg Mw: 4 r: ReceiverResultReg.
  	(initialized and: [size > 0]) ifTrue:
+ 		[cogit genMoveConstant: objectMemory nilObject R: TempReg.
- 		[cogit MoveCw: objectMemory nilObject R: TempReg.
  		 1 to: size do:
  			[:i| cogit MoveR: TempReg Mw: i * 4 + 4 r: ReceiverResultReg]].
  	cogit
  		MoveR: ReceiverResultReg R: TempReg;
  		AddCq: (objectMemory smallObjectBytesForSlots: size) R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	skip := cogit JumpBelow: 0.
  	cogit CallRT: ceScheduleScavengeTrampoline.
  	skip jmpTarget: cogit Label.
  	^0!

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."
  	| methodHeader jumpSkip |
  	<inline: false>
  	<var: #jumpSkip type: #'AbstractInstruction *'>
  	needsFrame ifFalse: [^0].
  	methodHeader := objectMemory methodHeaderOf: methodObj.
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  		(self PushCw: methodLabel asInteger)). "method"
+ 	self genMoveConstant: objectMemory nilObject R: SendNumArgsReg.
- 	self annotate: (self MoveCw: objectMemory nilObject R: SendNumArgsReg)
- 		objRef: objectMemory nilObject.
  	self PushR: SendNumArgsReg. "context"
  	self PushR: ReceiverResultReg.
  	methodOrBlockNumArgs + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
  	(primitiveIndex > 0
  	 and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)
  			= (objectMemory
  				fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
  				ofObject: methodObj)]) ifTrue:
  		[self compileGetErrorCode.
  		 initialPC := initialPC
  				   + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
  				   + (coInterpreter sizeOfLongStoreTempBytecode: methodHeader)].
  	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.
  	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs > 0 ifTrue:
  		 	[self PrefetchAw: theIRCs]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genDoubleComparison:invert: (in category 'primitive generators') -----
  genDoubleComparison: jumpOpcodeGenerator invert: invertComparison
  	"Stack looks like
  		receiver (also in ResultReceiverReg)
  		arg
  		return address"
  	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
  	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpNonInt type: #'AbstractInstruction *'>
  	<var: #jumpCond type: #'AbstractInstruction *'>
  	<var: #compare type: #'AbstractInstruction *'>
  	<var: #jumpFail type: #'AbstractInstruction *'>
  
  	self MoveMw: objectMemory wordSize r: SPReg R: TempReg.
  	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  	self MoveR: TempReg R: ClassReg.
  	jumpImmediate := objectRepresentation genJumpImmediateInScratchReg: TempReg.
  	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
  	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
  	jumpFail := self JumpNonZero: 0.
  	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
  	invertComparison "May need to invert for NaNs"
  		ifTrue: [compare := self CmpRd: DPFPReg0 Rd: DPFPReg1]
  		ifFalse: [compare := self CmpRd: DPFPReg1 Rd: DPFPReg0].
  	jumpCond := self perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
+ 	self genMoveFalseR: ReceiverResultReg.
- 	self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 		objRef: objectMemory falseObject.
  	self flag: 'currently caller pushes result'.
  	self RetN: objectMemory wordSize * 2.
+ 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	jumpCond jmpTarget: (self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 							objRef: objectMemory trueObject).
  	self RetN: objectMemory wordSize * 2.
  	jumpImmediate jmpTarget: self Label.
  	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
  		[jumpNonInt := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg].
  	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
  	self ConvertR: ClassReg Rd: DPFPReg1.
  	self Jump: compare.
  	jumpFail jmpTarget: self Label.
  	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
  		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
  	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genMoveConstant:R: (in category 'bytecode generator support') -----
+ genMoveConstant: constant R: reg
+ 	<inline: true>
+ 	^ (objectRepresentation shouldAnnotateObjectReference: constant)
+ 		ifTrue: [ (self annotate: (self MoveCw: constant R: reg) objRef: constant) ]
+ 		ifFalse: [ self MoveCq: constant R: reg ]
+ 	
+ 	!

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

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

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushLiteralVariable: (in category 'bytecode generator support') -----
  genPushLiteralVariable: literalIndex
  	<inline: false>
  	| association |
  	association := self getLiteral: literalIndex.
  	"N.B. Do _not_ use ReceiverResultReg to avoid overwriting receiver in assignment in frameless methods."
+ 	self genMoveConstant: association R: ClassReg.
- 	self annotate: (self MoveCw: association R: ClassReg) objRef: association.
  	objectRepresentation
  		genEnsureObjInRegNotForwarded: ClassReg
  		scratchReg: TempReg.
  	objectRepresentation
  		genLoadSlot: ValueIndex
  		sourceReg: ClassReg
  		destReg: TempReg.
  	self PushR: TempReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genReturnFalse (in category 'bytecode generators') -----
  genReturnFalse
+ 	self genMoveFalseR: ReceiverResultReg.
- 	self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 		objRef: objectMemory falseObject.
  	^self genUpArrowReturn!

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

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genReturnNilFromBlock (in category 'bytecode generators') -----
  genReturnNilFromBlock
  	self assert: inBlock.
  	self flag: 'currently caller pushes result'.
+ 	self genMoveConstant: objectMemory nilObject R: ReceiverResultReg.
- 	self annotate: (self MoveCw: objectMemory nilObject R: ReceiverResultReg)
- 		objRef: objectMemory nilObject.
  	^self genBlockReturn!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genReturnTrue (in category 'bytecode generators') -----
  genReturnTrue
+ 	self genMoveTrueR: ReceiverResultReg.
- 	self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 		objRef: objectMemory trueObject.
  	^self genUpArrowReturn!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  genSend: selector numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	self assert: (numArgs between: 0 and: 255). "say"
  	self assert: (objectMemory addressCouldBeOop: selector).
  	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
  	"Deal with stale super sends; see SpurMemoryManager's class comment."
  	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
  	 and: [annotation = IsDirectedSuperSend]) ifTrue:
+ 		[self genMoveConstant: tempOop R: TempReg].
- 		[self annotate: (self MoveCw: tempOop R: TempReg) objRef: tempOop].
  	self MoveCw: selector R: ClassReg.
  	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
  		with: annotation.
  	self flag: 'currently caller pushes result'.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSmallIntegerComparison: (in category 'primitive generators') -----
  genSmallIntegerComparison: jumpOpcode
  	"Stack looks like
  		receiver (also in ResultReceiverReg)
  		arg
  		return address"
  	| jumpFail jumpTrue |
  	<var: #jumpFail type: #'AbstractInstruction *'>
  	<var: #jumpTrue type: #'AbstractInstruction *'>
  	self MoveMw: objectMemory wordSize r: SPReg R: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	jumpFail := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	self CmpR: ClassReg R: ReceiverResultReg. "N.B. FLAGS := RRReg - ClassReg"
  	jumpTrue := self gen: jumpOpcode.
+ 	self genMoveFalseR: ReceiverResultReg.
- 	self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 		objRef: objectMemory falseObject.
  	self flag: 'currently caller pushes result'.
  	self RetN: objectMemory wordSize * 2.
+ 	jumpTrue jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	jumpTrue jmpTarget: (self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 						objRef: objectMemory trueObject).
  	self RetN: objectMemory wordSize * 2.
  	jumpFail jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSmallIntegerComparison:orDoubleComparison: (in category 'primitive generators') -----
  genSmallIntegerComparison: jumpOpcode orDoubleComparison: jumpFPOpcodeGenerator
  	"Stack looks like
  		receiver (also in ResultReceiverReg)
  		arg
  		return address"
  	| jumpDouble jumpNonInt jumpFail jumpTrue jumpCond |
  	<var: #jumpFPOpcodeGenerator declareC: 'AbstractInstruction *(*jumpFPOpcodeGenerator)(void *)'>
  	<var: #jumpDouble type: #'AbstractInstruction *'>
  	<var: #jumpNonInt type: #'AbstractInstruction *'>
  	<var: #jumpCond type: #'AbstractInstruction *'>
  	<var: #jumpTrue type: #'AbstractInstruction *'>
  	<var: #jumpFail type: #'AbstractInstruction *'>
  	backEnd hasDoublePrecisionFloatingPointSupport ifFalse:
  		[^self genSmallIntegerComparison: jumpOpcode].
  	self MoveMw: objectMemory wordSize r: SPReg R: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	jumpDouble := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	self CmpR: ClassReg R: ReceiverResultReg. "N.B. FLAGS := RRReg - ClassReg"
  	jumpTrue := self gen: jumpOpcode.
+ 	self genMoveFalseR: ReceiverResultReg.
- 	self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 		objRef: objectMemory falseObject.
  	self flag: 'currently caller pushes result'.
  	self RetN: objectMemory wordSize * 2.
+ 	jumpTrue jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	jumpTrue jmpTarget: (self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 						objRef: objectMemory trueObject).
  	self RetN: objectMemory wordSize * 2.
  	
  	"Argument may be a Float : let us check or fail"
  	jumpDouble jmpTarget: self Label.
  	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
  		[self MoveR: ClassReg R: TempReg.
  		 jumpNonInt := objectRepresentation genJumpImmediateInScratchReg: TempReg].
  	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
  	objectRepresentation genCmpClassFloatCompactIndexR: SendNumArgsReg.
  	jumpFail := self JumpNonZero: 0.
  
  	"It was a Float, so convert the receiver to double and perform the operation"
  	self MoveR: ReceiverResultReg R: TempReg.
  	objectRepresentation genConvertSmallIntegerToIntegerInReg: TempReg.
  	self ConvertR: TempReg Rd: DPFPReg0.
  	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
  	self CmpRd: DPFPReg1 Rd: DPFPReg0.
  	jumpCond := self perform: jumpFPOpcodeGenerator with: 0. "FP jumps are a little weird"
+ 	self genMoveFalseR: ReceiverResultReg.
- 	self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 		objRef: objectMemory falseObject.
  	self flag: 'currently caller pushes result'.
  	self RetN: objectMemory wordSize * 2.
+ 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
- 	jumpCond jmpTarget: (self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 							objRef: objectMemory trueObject).
  	self RetN: objectMemory wordSize * 2.
  
  	objectRepresentation smallIntegerIsOnlyImmediateType
  		ifTrue: [jumpFail jmpTarget: self Label]
  		ifFalse: [jumpNonInt jmpTarget: (jumpFail jmpTarget: self Label)].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
  genSpecialSelectorEqualsEquals
  	| jumpNotEqual jumpPush |
  	<var: #jumpNotEqual type: #'AbstractInstruction *'>
  	<var: #jumpPush type: #'AbstractInstruction *'>
  	self PopR: Arg0Reg.
  	objectRepresentation
  		genEnsureObjInRegNotForwarded: Arg0Reg
  		scratchReg: TempReg.
  	self MoveMw: 0 r: SPReg R: ClassReg.
  	objectRepresentation
  		genEnsureObjInRegNotForwarded: ClassReg
  		scratchReg: TempReg.
  	self CmpR: Arg0Reg R: ClassReg.
  	jumpNotEqual := self JumpNonZero: 0.
+ 	self annotate: (self genMoveTrueR: Arg0Reg)
- 	self annotate: (self MoveCw: objectMemory trueObject R: Arg0Reg)
  		objRef: objectMemory trueObject.
  	jumpPush := self Jump: 0.
+ 	jumpNotEqual jmpTarget: (self genMoveFalseR: Arg0Reg).
- 	jumpNotEqual jmpTarget: (self annotate: (self MoveCw: objectMemory falseObject R: Arg0Reg)
- 							objRef: objectMemory falseObject).
  	jumpPush jmpTarget: (self MoveR: Arg0Reg Mw: 0 r: SPReg).
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genStorePop:LiteralVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean LiteralVariable: litVarIndex
  	<inline: false>
  	| association |
  	"The only reason we assert needsFrame here is that in a frameless method
  	 ReceiverResultReg must and does contain only self, but the ceStoreCheck
  	 trampoline expects the target of the store to be in ReceiverResultReg.  So
  	 in a frameless method we would have a conflict between the receiver and
  	 the literal store, unless we we smart enough to realise that ReceiverResultReg
  	 was unused after the literal variable store, unlikely given that methods
  	 return self by default."
  	self assert: needsFrame.
  	association := self getLiteral: litVarIndex.
+ 	self genMoveConstant: association R: ReceiverResultReg.
- 	self annotate: (self MoveCw: association R: ReceiverResultReg) objRef: association.
  	objectRepresentation
  		genEnsureObjInRegNotForwarded: ReceiverResultReg
  		scratchReg: TempReg.
  	popBoolean
  		ifTrue: [self PopR: ClassReg]
  		ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
  	traceStores > 0 ifTrue:
  		[self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: ClassReg
  		slotIndex: ValueIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: needsFrame!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genMoveConstant:R: (in category 'bytecode generator support') -----
- genMoveConstant: constant R: reg
- 	<inline: true>
- 	^ (objectRepresentation shouldAnnotateObjectReference: constant)
- 		ifTrue: [ (self annotate: (self MoveCw: constant R: reg) objRef: constant) ]
- 		ifFalse: [ self MoveCq: constant R: reg ]
- 	
- 	!

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

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



More information about the Vm-dev mailing list