[Vm-dev] VM Maker: VMMaker.oscog-tpr.736.mcz

commits at source.squeak.org commits at source.squeak.org
Thu May 29 01:43:15 UTC 2014


tim Rowledge uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-tpr.736.mcz

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

Name: VMMaker.oscog-tpr.736
Author: tpr
Time: 28 May 2014, 9:47:52.06 am
UUID: 52dd5233-dcb9-46a7-80ce-d69b874aa615
Ancestors: VMMaker.oscog-eem.735

Merge with -eem.735
Add CogARMCompiler code to make ARM opcodes a bit easier to write (add:rn:, mov:rn: etc)
Change the return to use LR instead of popping the return address from the stack - lots of side effects to fix up

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

Item was added:
+ ----- Method: CogARMCompiler>>add:rn:rm: (in category 'ARM convenience instructions') -----
+ add: destReg rn: srcReg rm: addReg
+ "return an ADD destReg, srcReg, addReg instruction"
+ 
+ 	^self type: 0 op: 4 set: 0 rn: srcReg rd: destReg shifterOperand: addReg!

Item was removed:
- ----- Method: CogARMCompiler>>addRd:rn:imm:ror: (in category 'ARM convenience instructions') -----
- addRd: destReg rn: srcReg imm: immediate ror: rot
- "return an ADD destReg, srcReg, immediat ROR rot instruction"
- 
- 	^self type: 1 op: 4 set: 0 rn: srcReg rd: destReg shifterOperand: (rot <<8 bitOr: immediate)!

Item was removed:
- ----- Method: CogARMCompiler>>addRd:rn:rm: (in category 'ARM convenience instructions') -----
- addRd: destReg rn: srcReg rm: addReg
- "return an ADD destReg, srcReg, addReg instruction"
- 
- 	^self type: 0 op: 4 set: 0 rn: srcReg rd: destReg shifterOperand: addReg!

Item was removed:
- ----- Method: CogARMCompiler>>callsAreRelative (in category 'testing') -----
- callsAreRelative
- 	^true!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code - concretize') -----
  concretizeLoadEffectiveAddressMwrR
  	"Will get inlined into concretizeAt: switch."
  	"destReg = srcReg (which contains an address) + offset"
  	<inline: true>
  	| srcReg offset destReg instrOffset |
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	self rotateable8bitImmediate: offset
  		ifTrue: [ :rot :immediate | 
  			self machineCodeAt: 0 
  				"add destReg, srcReg, #immediate ROR rot"
  				put: (self add: destReg rn: srcReg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse: [ 
  			instrOffset := self at: 0 moveCw: offset intoR: RISCTempReg.
  			"add destReg, srcReg, RISCTempReg"
+ 			self machineCodeAt: 16 put: (self add: destReg rn: srcReg rm: RISCTempReg).
- 			self machineCodeAt: 16 put: (self addRd: destReg rn: srcReg rm: RISCTempReg).
  			^machineCodeSize := instrOffset + 4 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePopR (in category 'generate machine code - concretize') -----
  concretizePopR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| destReg |
  	destReg := self concreteRegister: (operands at: 0).
+ 	"LDR destReg, [SP], #4"
- 	"cond | 010 | 0100 | 1 | -Rn- | -Rd- | 0000 0000 0100 " "LDR destReg, [SP], #4"
  	self machineCodeAt: 0 put: (self popR: destReg).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushR (in category 'generate machine code - concretize') -----
  concretizePushR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg |
  	srcReg := self concreteRegister: (operands at: 0).
  	"cond | 010 | 1001 | 0 | -Rn- | -Rd- | 0000 0000 0100" "STR srcReg, [sp, #-4]"
+ 	self machineCodeAt: 0 put: (self pushR: srcReg).
- 	self machineCodeAt: 0 put: (self type: 2 op: 9 set: 0 rn: SP rd: srcReg shifterOperand: 4).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeRetN (in category 'generate machine code - concretize') -----
  concretizeRetN
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset |
  	offset := operands at: 0.
  	offset = 0 ifTrue:
+ 		[self machineCodeAt: 0 put: (self mov: PC rn: LR). "pop	{pc}"
- 		[self machineCodeAt: 0 put: (self popR: PC). "pop	{pc}"
  		^machineCodeSize := 4].
  	self assert: offset < 32. "We have an 8 bit immediate. If needed, we could rotate it less than 30 bit."
  	"add sp, sp, #n, ROR (15<<2) <- ie shift left 2 to convert words to bytes"
  	self machineCodeAt: 0 put: (self add: SP rn: SP imm: offset ror: 30).
+ 	self machineCodeAt: 4 put: (self mov: PC rn: LR).  "pop	{pc}"
- 	self machineCodeAt: 4 put: (self popR: PC).  "pop	{pc}"
  	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogARMCompiler>>mov:rn: (in category 'ARM convenience instructions') -----
+ mov: destReg rn: srcReg
+ "return a MOV destReg, srcReg instruction"
+ 
+ 	^self type: 0 op: 16rD set: 0 rn: 0 rd: destReg shifterOperand: srcReg!

Item was removed:
- ----- Method: CogARMCompiler>>movRd:imm:ror: (in category 'ARM convenience instructions') -----
- movRd: destReg imm: immediate8bitValue ror: rotateRightBy
- 	"return the ARM instruction MOV destReg, #immediate8BitValue ROR rotateRightBy"
- 	^self type: 1 op: 16rD set: 0 rn: destReg rd: destReg shifterOperand: (rotateRightBy <<8 bitOr: immediate8bitValue)!

Item was added:
+ ----- Method: CogARMCompiler>>movs:rn: (in category 'ARM convenience instructions') -----
+ movs: destReg rn: srcReg
+ "return a MOV destReg, srcReg instruction"
+ 
+ 	^self type: 0 op: 16rD set: 1 rn: 0 rd: destReg shifterOperand: srcReg!

Item was removed:
- ----- Method: CogARMCompiler>>orrRd:imm:ror: (in category 'ARM convenience instructions') -----
- orrRd: destReg imm: immediate8bitValue ror: rotateRightBy
- 	"return the ARM instruction ORR destReg, #immediate8BitValue ROR rotateRightBy"
- 	^self type: 1 op: 16rB set: 0 rn: destReg rd: destReg shifterOperand: (rotateRightBy <<8 bitOr: immediate8bitValue)!

Item was added:
+ ----- Method: CogARMCompiler>>setsConditionCodesFor: (in category 'testing') -----
+ setsConditionCodesFor: aConditionalJumpOpcode
+ 	<inline: false> "to save Slang from having to be a real compiler (it can't inline switches that return)"
+ 	"Answer if the receiver's opcode sets the condition codes correctly for the given conditional jump opcode.
+ 	ARM has to check carefully since the V flag is not affected by non-comparison instructions"
+ 	^opcode caseOf:
+ 		{	[ArithmeticShiftRightCqR]	->	[self shiftSetsConditionCodesFor: aConditionalJumpOpcode].
+ 			[ArithmeticShiftRightRR]	->	[self shiftSetsConditionCodesFor: aConditionalJumpOpcode].
+ 			[LogicalShiftLeftCqR]		->	[self shiftSetsConditionCodesFor: aConditionalJumpOpcode].
+ 			[LogicalShiftLeftRR]		->	[self shiftSetsConditionCodesFor: aConditionalJumpOpcode].
+ 			[XorRR]					->	[true]
+ 		}
+ 		otherwise: [self halt: 'unhandled opcode in setsConditionCodesFor:'. false]!

Item was added:
+ ----- Method: CogARMCompiler>>shiftSetsConditionCodesFor: (in category 'testing') -----
+ shiftSetsConditionCodesFor: aConditionalJumpOpcode
+ 	"check what flags the opcdoe needs setting - ARM doesn't set V when simply MOVing"
+ 		^aConditionalJumpOpcode caseOf:
+ 		{	[JumpNegative]	->	[true].
+ 			[JumpZero]	->	[true].
+ 		}
+ 		otherwise: [self halt: 'unhandled opcode in setsConditionCodesFor:'. false]!

Item was changed:
  ----- Method: Cogit>>genCheckForInterruptsTrampoline (in category 'initialization') -----
  genCheckForInterruptsTrampoline
  	opcodeIndex := 0.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceCheckForInterrupts
  		called: 'ceCheckForInterruptsTrampoline'
  		callJumpBar: true
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:and:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 and: regArg3 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it."
  	<returnTypeC: 'void (*genEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg3.
  	self PopR: regArg2.
  	self PopR: regArg1.
  	backEnd hasLinkRegister ifTrue:
  		[self PopR: LinkReg].
  	self RetN: 0.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it."
  	<returnTypeC: 'void (*genEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg2.
  	self PopR: regArg1.
  	backEnd hasLinkRegister ifTrue:
  		[self PopR: LinkReg].
  	self RetN: 0.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:called: (in category 'initialization') -----
  genEnilopmartFor: regArg called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it."
  	<returnTypeC: 'void (*genEnilopmartForcalled(sqInt regArg, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
  	backEnd genLoadStackPointers.
  	self PopR: regArg.
  	backEnd hasLinkRegister ifTrue:
  		[self PopR: LinkReg].
  	self RetN: 0.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genExternalizePointersForPrimitiveCall (in category 'trampoline support') -----
  genExternalizePointersForPrimitiveCall
  	backEnd hasLinkRegister
  		ifTrue: [self PushR: LinkReg]
  		ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
  	self MoveR: FPReg Aw: coInterpreter framePointerAddress.
  	"Set coInterpreter stackPointer to the topmost argument, skipping the return address."
  	self LoadEffectiveAddressMw: BytesPerWord r: SPReg R: TempReg.
  	backEnd hasLinkRegister
  		ifTrue: [self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse: [self MoveR: ClassReg Aw: coInterpreter instructionPointerAddress].
  	self MoveR: TempReg Aw: coInterpreter stackPointerAddress.
  	^0!

Item was changed:
  ----- Method: Cogit>>genNonLocalReturnTrampoline (in category 'initialization') -----
  genNonLocalReturnTrampoline
  	opcodeIndex := 0.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceNonLocalReturn:
  		called: 'ceNonLocalReturnTrampoline'
  		callJumpBar: true
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genReturnTopFromBlock (in category 'bytecode generators') -----
  genReturnTopFromBlock
  	self assert: inBlock.
  	self flag: 'currently caller pushes result'.
  	self PopR: ReceiverResultReg.
  	needsFrame ifTrue:
  		[self MoveR: FPReg R: SPReg.
  		 self PopR: FPReg].
  	backEnd hasLinkRegister ifTrue:
  		[self PopR: LinkReg].
  	self RetN: methodOrBlockNumArgs + 1 * BytesPerWord.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genUpArrowReturn (in category 'bytecode generators') -----
  genUpArrowReturn
  	"Generate a method return from within a method or a block.
  	 Frameless method activation looks like
  				receiver
  				args
  		sp->	ret pc.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
  	self flag: 'currently caller pushes result'.
  	inBlock ifTrue:
  		[self assert: needsFrame.
  		 self annotateBytecode: (self CallRT: ceNonLocalReturnTrampoline).
  		 ^0].
  	needsFrame ifTrue:
  		[self MoveR: FPReg R: SPReg.
  		 self PopR: FPReg].
  	backEnd hasLinkRegister ifTrue:
  		[self PopR: LinkReg].
  	self RetN: methodOrBlockNumArgs + 1 * BytesPerWord.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMethodAbortTrampolineFor: (in category 'initialization') -----
  genMethodAbortTrampolineFor: numArgs
+ 	
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
  	"on machines with a link register, pop the stack if the ReceiverResultReg = 0,
  	 i.e. if coming through the stack check abort; frame build has already pushed it."
  	backEnd hasLinkRegister ifTrue:
  		[self AddCq: BytesPerWord R: SPReg].
  
  	self compileTrampolineFor: #ceStackOverflow:
  		callJumpBar: true
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genTrampolineFor: #ceSICMiss:
  		called: (self trampolineName: 'ceMethodAbort' numArgs: (numArgs <= self numRegArgs ifTrue: [numArgs] ifFalse: [-1]))
  		callJumpBar: true
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genReturnTopFromBlock (in category 'bytecode generators') -----
  genReturnTopFromBlock
  	self assert: inBlock.
  	self ssTop popToReg: ReceiverResultReg.
  	self ssPop: 1.
  	needsFrame ifTrue:
  		[self MoveR: FPReg R: SPReg.
  		 self PopR: FPReg].
  	backEnd hasLinkRegister ifTrue:
  		[self PopR: LinkReg].
  	self RetN: methodOrBlockNumArgs + 1 * BytesPerWord.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genUpArrowReturn (in category 'bytecode generators') -----
  genUpArrowReturn
  	"Generate a method return from within a method or a block.
  	 Frameless method activation looks like
  				receiver
  				args
  		sp->	ret pc.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
  	inBlock ifTrue:
  		[self assert: needsFrame.
  		 self annotateBytecode: (self CallRT: ceNonLocalReturnTrampoline).
  		 ^0].
  	needsFrame
  		ifTrue:
  			[self MoveR: FPReg R: SPReg.
  			 self PopR: FPReg.
  			 backEnd hasLinkRegister ifTrue:
  				[self PopR: LinkReg].
  			 self RetN: methodOrBlockNumArgs + 1 * BytesPerWord]
  		ifFalse:
  			[backEnd hasLinkRegister ifTrue:
  				[self PopR: LinkReg].
  			 self RetN: ((methodOrBlockNumArgs > self numRegArgs
  						"A method with an interpreter prim will push its register args for the prim.  If the failure
  						 body is frameless the args must still be popped, see e.g. Behavior>>nextInstance."
  						or: [regArgsHaveBeenPushed])
  							ifTrue: [methodOrBlockNumArgs + 1 * BytesPerWord]
  							ifFalse: [0])].
  	^0!



More information about the Vm-dev mailing list