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

commits at source.squeak.org commits at source.squeak.org
Wed Mar 18 22:47:39 UTC 2015


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

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

Name: VMMaker.oscog-eem.1099
Author: eem
Time: 18 March 2015, 3:45:44.227 pm
UUID: b8e80b54-512a-418f-8134-fc7d11e3b116
Ancestors: VMMaker.oscog-tpr.1098

Fix the traceLinkedSendOffset for ARM; it must include
the link reg push size.

Provide a hack so that ARM can use bl to call the
short-cut trampolines through bl during simulation.

Fix the ceBaseFrameReturn and ceReturnToInterpreter
trampoliners to not push the link reg; these are reached via returns.

=============== Diff against VMMaker.oscog-tpr.1098 ===============

Item was added:
+ ----- Method: CogARMCompiler>>pushLinkRegisterByteSize (in category 'accessing') -----
+ pushLinkRegisterByteSize
+ 	^4!

Item was added:
+ ----- Method: CogARMCompiler>>wantsNearAddressFor: (in category 'simulation') -----
+ wantsNearAddressFor: anObject
+ 	"A hack hook to allow ARM to override the simulated address for the short-cut trampolines"
+ 	^anObject isSymbol and: [anObject beginsWith: 'ceShortCut']!

Item was added:
+ ----- Method: CogAbstractInstruction>>wantsNearAddressFor: (in category 'simulation') -----
+ wantsNearAddressFor: anObject
+ 	"A hack hook to allow ARM to override the simulated address for the short-cut trampolines"
+ 	^false!

Item was changed:
  ----- Method: CogVMSimulator>>ceTraceBlockActivation (in category 'debug support') -----
  ceTraceBlockActivation
- 	<var: #theFP type: #'char *'>
  	cogit printOnTrace ifTrue:
  		[transcript print: byteCount; nextPut: $/; print: (sendCount := sendCount + 1); space].
  	cogit assertCStackWellAligned.
  	super ceTraceBlockActivation.
  	^#continue!

Item was added:
+ ----- Method: CogVMSimulator>>printFrameAtEachStep (in category 'testing') -----
+ printFrameAtEachStep
+ 	^printFrameAtEachStep!

Item was added:
+ ----- Method: Cogit>>genReturnTrampolineFor:called:arg: (in category 'initialization') -----
+ genReturnTrampolineFor: aRoutine  called: aString arg: regOrConst0
+ 	"Generate a trampoline for a routine used as a return address, that has one argument.
+ 	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
+ 	<var: #aRoutine type: #'void *'>
+ 	<var: #aString type: #'char *'>
+ 	^self
+ 		genTrampolineFor: aRoutine
+ 		called: aString
+ 		numArgs: 1
+ 		arg: regOrConst0
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		saveRegs: false
+ 		pushLinkReg: false "Since the routine is reached by a return instruction it should /not/ push the link register."
+ 		resultReg: nil
+ 		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>generateRunTimeTrampolines (in category 'initialization') -----
  generateRunTimeTrampolines
  	"Generate the run-time entries at the base of the native code zone and update the base."
  	
  	ceSendMustBeBooleanAddFalseTrampoline := self genMustBeBooleanTrampolineFor: objectMemory falseObject
  														called: 'ceSendMustBeBooleanAddFalseTrampoline'.
  	ceSendMustBeBooleanAddTrueTrampoline := self genMustBeBooleanTrampolineFor: objectMemory trueObject
  														called: 'ceSendMustBeBooleanAddTrueTrampoline'.
  	ceNonLocalReturnTrampoline := self genNonLocalReturnTrampoline.
- 	ceBaseFrameReturnTrampoline := self genTrampolineFor: #ceBaseFrameReturn:
- 										called: 'ceBaseFrameReturnTrampoline'
- 										arg: ReceiverResultReg.
  	ceCheckForInterruptTrampoline := self genCheckForInterruptsTrampoline.
  	ceFetchContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:
  											called: 'ceFetchContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											result: SendNumArgsReg.
  	ceStoreContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:value:
  											called: 'ceStoreContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											arg: ClassReg
+ 											result: ReceiverResultReg. "to keep ReceiverResultReg live.".
- 											result: ReceiverResultReg. "to keep ReceiverResultReg live."
- 	ceReturnToInterpreterTrampoline := self genTrampolineFor: #ceReturnToInterpreter:
- 											called: 'ceReturnToInterpreterTrampoline'
- 											arg: ReceiverResultReg.
  	ceCannotResumeTrampoline := self genTrampolineFor: #ceCannotResume
+ 											called: 'ceCannotResumeTrampoline'.
+ 	"These two are unusual; they are reached by return instructions."
+ 	ceBaseFrameReturnTrampoline := self genReturnTrampolineFor: #ceBaseFrameReturn:
+ 											called: 'ceBaseFrameReturnTrampoline'
+ 											arg: ReceiverResultReg.
+ 	ceReturnToInterpreterTrampoline := self
+ 											genReturnTrampolineFor: #ceReturnToInterpreter:
+ 											called: 'ceReturnToInterpreterTrampoline'
+ 											arg: ReceiverResultReg!
- 											called: 'ceCannotResumeTrampoline'!

Item was changed:
  ----- Method: Cogit>>shortcutTrampoline:to: (in category 'simulation only') -----
  shortcutTrampoline: aProcessorSimulationTrap to: aBlock
  	<doNotGenerate>
+ 	coInterpreter printFrameAtEachStep ifTrue:
+ 		[coInterpreter
+ 			printFrame: processor fp
+ 			WithSP: processor sp].
  	processor
  		simulateLeafCallOf: aProcessorSimulationTrap address
  		nextpc: aProcessorSimulationTrap nextpc
  		memory: coInterpreter memory.
  	coInterpreter
  		stackPointer: processor sp;
  		framePointer: processor fp.
  	processor
  		sp: self getCStackPointer;
  		fp: self getCFramePointer.
  	aBlock value.
  	processor
  		sp: coInterpreter stackPointer;
  		fp: coInterpreter framePointer;
+ 		simulateLeafReturnIn: coInterpreter memory.
+ 	coInterpreter printFrameAtEachStep ifTrue:
+ 		[coInterpreter
+ 			printFrame: processor fp
+ 			WithSP: processor sp]!
- 		simulateLeafReturnIn: coInterpreter memory!

Item was changed:
  ----- Method: Cogit>>simulatedAddressFor: (in category 'initialization') -----
  simulatedAddressFor: anObject
  	"Answer a simulated address for a block or a symbol.  This is an address that
  	 can be called, read or written by generated machine code, and will be mapped
  	 into a Smalltalk message send or block evaluation.
  
  	 N.B. These addresses are at the top end of the bottom half of the address space
+ 	 so that they don't have the sign bit set and so will not look like negative numbers,
+ 	 unless they're the short-cut routines on ARM, where we want to use a bl, not a blx."
- 	 so that they don't have the sign bit set and so will not look like negative numbers."
  	<doNotGenerate>
  	^simulatedAddresses
  		at: anObject
+ 		ifAbsentPut:
+ 			[(simulatedAddresses size + 101 * objectMemory wordSize) negated
+ 				bitAnd: ((backEnd wantsNearAddressFor: anObject)
+ 							ifTrue: [self addressSpaceMask]
+ 							ifFalse: [self allButTopBitOfAddressSpaceMask])]!
- 		ifAbsentPut: [(simulatedAddresses size + 101 * objectMemory wordSize) negated bitAnd: self allButTopBitOfAddressSpaceMask]!

Item was changed:
  ----- Method: Cogit>>traceLinkedSendOffset (in category 'debugging') -----
  traceLinkedSendOffset
  	<api>
+ 	^cmNoCheckEntryOffset
+ 	 + backEnd callInstructionByteSize
+ 	 + (backEnd hasLinkRegister
+ 		ifTrue: [backEnd pushLinkRegisterByteSize]
+ 		ifFalse: [0])!
- 	^cmNoCheckEntryOffset + backEnd callInstructionByteSize!



More information about the Vm-dev mailing list