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

commits at source.squeak.org commits at source.squeak.org
Sun Dec 13 21:57:24 UTC 2015


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

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

Name: VMMaker.oscog-eem.1593
Author: eem
Time: 13 December 2015, 1:55:38.459 pm
UUID: 27cc996b-9a33-43c3-a8ae-5f54de74f0ac
Ancestors: VMMaker.oscog-eem.1592

x64 Cogit: More C compiler warning elimination.

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

Item was changed:
  ----- Method: CogAbstractInstruction>>noteFollowingConditionalBranch: (in category 'abstract instructions') -----
  noteFollowingConditionalBranch: branch
  	"Support for processors without condition codes, such as the MIPS.
  	 Answer the branch opcode.  If there are no condition codes, modify
  	 the receiver and the branch to implement a suitable conditional
  	 branch that doesn't depend on condition codes being set by the
  	 receiver.  By default a noop. Overridden in subclasses as required."
+ 	<returnTypeC: #'AbstractInstruction *'>
  	<var: #branch type: #'AbstractInstruction *'>
  	<inline: true>
  	^branch!

Item was changed:
  ----- Method: CogMIPSELCompiler>>noteFollowingConditionalBranch: (in category 'abstract instructions') -----
  noteFollowingConditionalBranch: branch
  	"Support for processors without condition codes, such as the MIPS.
  	 Answer the branch opcode.  Modify the receiver and the branch to
  	 implement a suitable conditional branch that doesn't depend on
  	 condition codes being set by the receiver."
+ 	<returnTypeC: #'AbstractInstruction *'>
  	<var: #branch type: #'AbstractInstruction *'>
  	| newBranchLeft newBranchOpcode newBranchRight |
  	
  	((branch opcode = JumpOverflow) or: [branch opcode = JumpNoOverflow]) 
  		ifTrue: [^self noteFollowingOverflowBranch: branch].
  
  	newBranchOpcode := branch opcode caseOf: {
  		[JumpZero] 			-> [BrEqualRR].
  		[JumpNonZero]			-> [BrNotEqualRR].
  		[JumpBelow]			-> [BrUnsignedLessRR].
  		[JumpBelowOrEqual]	-> [BrUnsignedLessEqualRR].
  		[JumpAbove]			-> [BrUnsignedGreaterRR].
  		[JumpAboveOrEqual]	-> [BrUnsignedGreaterEqualRR].
  		[JumpLess]				-> [BrSignedLessRR].
  		[JumpLessOrEqual]		-> [BrSignedLessEqualRR].
  		[JumpGreater]			-> [BrSignedGreaterRR].
  		[JumpGreaterOrEqual]	-> [BrSignedGreaterEqualRR].
  		[JumpLongZero] 		-> [BrLongEqualRR].
  		[JumpLongNonZero]	-> [BrLongNotEqualRR].
  		
  		[JumpNegative]			-> [BrSignedLessRR].
  	} otherwise: [self unreachable].
  	
  	opcode caseOf: {
  		[BrEqualRR]	->	["I.e., two jumps after a compare."
  						newBranchLeft := operands at: 1.
  						newBranchRight := operands at: 2].
  		[BrUnsignedLessRR]	->	["I.e., two jumps after a compare."
  						newBranchLeft := operands at: 1.
  						newBranchRight := operands at: 2].
  
  		[CmpRR] 	-> 	[newBranchLeft := operands at: 1.
  						 newBranchRight := operands at: 0.
  						 opcode := Label].
  		[CmpCqR]	-> 	[newBranchLeft := operands at: 1.
  						 newBranchRight := AT.
  						 opcode := MoveCqR.
  						 operands at: 1 put: AT].
  		[CmpCwR]	-> 	[newBranchLeft := operands at: 1.
  						 newBranchRight := AT.
  						 opcode := MoveCwR.
  						 operands at: 1 put: AT].
  		[TstCqR]	->	[newBranchLeft := Cmp.
  						 newBranchRight := ZR].
  		[AndCqR]	->	[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[AndCqRR]	->	[newBranchLeft := operands at: 2.
  						 newBranchRight := ZR].
  		[OrRR]	->		[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[XorRR]	->		[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[SubCwR]	->	[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[SubCqR]	->	[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[ArithmeticShiftRightCqR]	->	[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  	} otherwise: [self unreachable].
  
  	branch rewriteOpcode: newBranchOpcode with: newBranchLeft with: newBranchRight.
  	^branch!

Item was added:
+ ----- Method: CogObjectRepresentation>>genJumpNotSmallIntegerInScratchReg: (in category 'compile abstract instructions') -----
+ genJumpNotSmallIntegerInScratchReg: aRegister
+ 	"Generate a test for aRegister containing an integer value outside the SmallInteger range, and a jump if so, answering the jump."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentation>>genJumpSmallInteger:scratchReg: (in category 'compile abstract instructions') -----
  genJumpSmallInteger: aRegister scratchReg: scratch
  	"Generate a compare and branch to test if aRegister contains a SmallInteger.
  	 Answer the jump.  Use scratch if required.  Subclasses will override if scratch is needed."
  	<returnTypeC: #'AbstractInstruction *'>
  	^self genJumpSmallInteger: aRegister!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpNotSmallInteger:scratchReg: (in category 'compile abstract instructions') -----
  genJumpNotSmallInteger: reg scratchReg: scratch
  	"Generate a compare and branch to test if aRegister contains other than a SmallInteger.
  	 Answer the jump.  Override since scratch is needed."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit
+ 		AndCq: objectMemory tagMask R: reg R: scratch;
+ 		CmpCq: objectMemory smallIntegerTag R: scratch;
+ 		JumpNonZero: 0!
- 	cogit AndCq: objectMemory tagMask R: reg R: scratch.
- 	cogit CmpCq: objectMemory smallIntegerTag R: scratch.
- 	^cogit JumpNonZero: 0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpSmallInteger:scratchReg: (in category 'compile abstract instructions') -----
  genJumpSmallInteger: reg scratchReg: scratch
  	"Generate a compare and branch to test if aRegister contains a SmallInteger.
  	 Answer the jump.  Override since scratch is needed."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit
+ 		AndCq: objectMemory tagMask R: reg R: scratch;
+ 		CmpCq: objectMemory smallIntegerTag R: scratch;
+ 		JumpZero: 0!
- 	cogit AndCq: objectMemory tagMask R: reg R: scratch.
- 	cogit CmpCq: objectMemory smallIntegerTag R: scratch.
- 	^cogit JumpZero: 0!

Item was changed:
  ----- Method: Cogit>>configureCPIC:Case0:Case1Method:tag:isMNUCase:numArgs:delta: (in category 'in-line cacheing') -----
  configureCPIC: cPIC Case0: case0CogMethod Case1Method: case1Method tag: case1Tag isMNUCase: isMNUCase numArgs: numArgs delta: addrDelta
  	"Configure a copy of the prototype CPIC for a two-case PIC for 
  	case0CogMethod and
  	case1Method
  	case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; jump to its unchecked entry-point
  		- a CompiledMethod; jump to the ceInterpretFromPIC trampoline
  		- nil; call ceMNUFromPIC
  	addDelta is the address change from the prototype to the new CPIC location, needed
  	because the loading of the CPIC label at the end may use a literal instead of a pc relative load."
  	"self disassembleFrom: cPIC asInteger + (self sizeof: CogMethod) to: cPIC asInteger + closedPICSize"
  	<var: #cPIC type: #'CogMethod *'>
  	<var: #case0CogMethod type: #'CogMethod *'>
+ 	| operand targetEntry caseEndAddress |
- 	| operand targetEntry caseEndAddress|
- 	<var: #targetEntry type: #'void *'>
  	self assert: case1Method notNil.
  
  	"adjust the call at missOffset, the ceAbortXArgs"
  	backEnd rewriteCallAt: cPIC asInteger + missOffset target: (self picAbortTrampolineFor: numArgs).
  	
  	self assert: (objectRepresentation inlineCacheTagIsYoung: case1Tag) not.
  	(isMNUCase not
  	 and: [coInterpreter methodHasCogMethod: case1Method])
  		ifTrue:
  			[operand := 0.
+ 			 targetEntry := (coInterpreter cogMethodOf: case1Method) asInteger + cmNoCheckEntryOffset]
- 			 targetEntry := ((coInterpreter cogMethodOf: case1Method) asInteger + cmNoCheckEntryOffset) asVoidPointer]
  		ifFalse: "We do not scavenge PICs, hence we cannot cache the MNU method if it is in new space."
  			[operand := (case1Method isNil or: [objectMemory isYoungObject: case1Method])
  							ifTrue: [0]
  							ifFalse: [case1Method].
  			 targetEntry := case1Method ifNil: [cPIC asInteger + (self sizeof: CogMethod)] ifNotNil: [cPIC asInteger + self picInterpretAbortOffset]].
  
  	"set the jump to the case0 method"
  	backEnd rewriteJumpLongAt: cPIC asInteger + firstCPICCaseOffset target: case0CogMethod asInteger + cmNoCheckEntryOffset.
  
  	caseEndAddress := self addressOfEndOfCase: 2 inCPIC: cPIC.
  
  	"update the cpic case"
  	self
  		rewriteCPICCaseAt: caseEndAddress
  		tag: case1Tag
  		objRef: operand
  		target: (isMNUCase ifTrue: [cPIC asInteger + (self sizeof: CogMethod)] ifFalse: [targetEntry]) asInteger.
  
  	"update the loading of the CPIC address"
  	backEnd relocateMethodReferenceBeforeAddress: cPIC asInteger + cPICEndOfCodeOffset - backEnd jumpLongByteSize by: addrDelta.
  
  	"write the final desperate jump to cePICMissXArgs"
  	backEnd rewriteJumpLongAt: cPIC asInteger + cPICEndOfCodeOffset target: (self cPICMissTrampolineFor: numArgs).
  	^0
  	"self disassembleFrom: cPIC + (self sizeof: CogMethod) to: cPIC + closedPICSize - 1."!



More information about the Vm-dev mailing list