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

commits at source.squeak.org commits at source.squeak.org
Fri Jun 19 16:55:04 UTC 2015


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

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

Name: VMMaker.oscog-eem.1365
Author: eem
Time: 19 June 2015, 9:53:09.405 am
UUID: a12bef68-d8c2-4546-80c5-310ef8d8cd88
Ancestors: VMMaker.oscog-eem.1364

Cogit:
Fix regression in relocateMethodsPreCompaction in
VMMaker.oscog-eem.1342.

Fix multiple annotations on the same pc now that
annotations are directly attached to instructions
by annotating a Label with the second annotation.
Affects e.g. calls through ceNonLocalReturnTrampoline.
Neaten generateMapAt:start: by moving the byte
write inside the new addToMap:instruction:byte:at:for:.

Fix addressIsInCurrentCompilation: using
youngReferrers as the upper limit.  Revise
initializeCodeZoneFrom:upTo: as a result.

ARM Cogit:
Fix relocating jumps in PICs by indirecting through the
literalsManager to skip out-of-line literals as required.

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

Item was changed:
  ----- Method: CogAbstractInstruction>>annotation: (in category 'accessing') -----
  annotation: aByte
+ 	self assert: (annotation isNil or: [annotation = aByte]).
  	^annotation := aByte!

Item was changed:
  ----- Method: CogMethodZone>>relocateMethodsPreCompaction (in category 'compaction') -----
  relocateMethodsPreCompaction
  	"All surviving methods have had the amount they are going to relocate by
  	 stored in their objectHeader fields.  Relocate all relative calls so that after
  	 the compaction of both the method containing each call and the call target
  	 the calls invoke the same target."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
+ 	[cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
- 	[cogMethod asUnsignedInteger] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmType = CMClosedPIC
  				ifTrue: [cogit relocateCallsInClosedPIC: cogMethod]
  				ifFalse: [cogit relocateCallsAndSelfReferencesInMethod: cogMethod]].
  		 cogMethod := self methodAfter: cogMethod].
  	self relocateAndPruneYoungReferrers.
  	^true!

Item was added:
+ ----- Method: Cogit>>addToMap:instruction:byte:at:for: (in category 'method map') -----
+ addToMap: annotation instruction: instruction byte: byte at: address for: mcpc
+ 	<inline: true>
+ 	objectMemory byteAt: address put: byte.
+ 	self cCode: [] inSmalltalk:
+ 		[| s bytecode |
+ 		(compilationTrace anyMask: 16) ifTrue:
+ 			[(s := coInterpreter transcript)
+ 				ensureCr;
+ 				print: annotation; nextPut: $/; nextPutAll: byte hex; space;
+ 				nextPutAll: address hex; space; nextPutAll: mcpc hex; space;
+ 				nextPutAll: (AnnotationConstantNames detect: [:name| (Cogit classPool at: name ifAbsent: []) = annotation]); cr; flush.
+ 			(instruction notNil
+ 			 and: [instruction bcpc isInteger]) ifTrue:
+ 				[s tab; print: instruction bcpc; nextPut: $/.
+ 				 instruction bcpc printOn: s base: 16.
+ 				 s space.
+ 				 instruction printStateOn: s.
+ 				 s space.
+ 				 bytecode := objectMemory fetchByte: instruction bcpc ofObject: methodObj.
+ 				 bytecode := bytecode + (self bytecodeSetOffsetForHeader: (objectMemory methodHeaderOf: methodObj)).
+ 				 (self generatorAt: bytecode) printStateOn: s.
+ 				 s cr; flush]]]!

Item was changed:
  ----- Method: Cogit>>addressIsInCurrentCompilation: (in category 'testing') -----
  addressIsInCurrentCompilation: address
  	^address asUnsignedInteger >= methodLabel address
+ 	  and: [address asUnsignedInteger < methodZone youngReferrers]!
- 	  and: [address asUnsignedInteger < (methodLabel address + (1 << 16))]!

Item was changed:
  ----- Method: Cogit>>cPIC:HasTarget: (in category 'in-line cacheing') -----
  cPIC: cPIC HasTarget: targetMethod
  	<var: #cPIC type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| pc target |
  	target := targetMethod asUnsignedInteger + cmNoCheckEntryOffset.
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	1 to: cPIC cPICNumCases do:
  		[:i|
+ 		target = (literalsManager cPICCase: i jumpTargetBefore: pc) ifTrue:
- 		target = (backEnd jumpLongTargetBeforeFollowingAddress: pc) ifTrue:
  			[^true].
  		pc := pc + cPICCaseSize].
  	^false!

Item was changed:
  ----- Method: Cogit>>cPICHasFreedTargets: (in category 'in-line cacheing') -----
  cPICHasFreedTargets: cPIC
  	<var: #cPIC type: #'CogMethod *'>
  	| pc entryPoint targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	1 to: cPIC cPICNumCases do:
  		[:i|
+ 		entryPoint := literalsManager cPICCase: i jumpTargetBefore: pc.
- 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
  		"Find target from jump.  Ignore jumps to the interpret and MNU calls within this PIC"
  		(entryPoint < cPIC asInteger
  		 or: [entryPoint > (cPIC asInteger + cPIC blockSize)]) ifTrue:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  			 self assert: (targetMethod cmType = CMMethod or: [targetMethod cmType = CMFree]).
  			 targetMethod cmType = CMFree ifTrue:
  				[^true]].
  		pc := pc + cPICCaseSize].
  	^false!

Item was changed:
  ----- Method: Cogit>>closedPICRefersToUnmarkedObject: (in category 'garbage collection') -----
  closedPICRefersToUnmarkedObject: cPIC
  	"Answer if the ClosedPIC refers to any unmarked objects or freed/freeable target methods,
  	 applying markAndTraceOrFreeCogMethod:firstVisit: to those targets to determine if freed/freeable."
  	<var: #cPIC type: #'CogMethod *'>
  	| pc offsetToLiteral offsetToJump object entryPoint targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	(objectMemory isImmediate: cPIC selector) ifFalse:
  		[(objectMemory isMarked: cPIC selector) ifFalse:
  			[^true]].
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	"First jump is unconditional; subsequent ones are conditional"
  	offsetToLiteral := backEnd jumpLongByteSize.
  	offsetToJump := literalsManager literalBytesFollowingJumpInClosedPIC.
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		objectRepresentation inlineCacheTagsMayBeObjects ifTrue:
  			[object := literalsManager classRefInClosedPICAt: pc - offsetToLiteral.
  			 ((objectRepresentation couldBeObject: object)
  			  and: [(objectMemory isMarked: object) not]) ifTrue:
  				[^true]].
  		object := literalsManager objRefInClosedPICAt: pc - offsetToLiteral.
  		((objectRepresentation couldBeObject: object)
  		 and: [(objectMemory isMarked: object) not]) ifTrue:
  			[^true].
+ 		entryPoint := literalsManager cPICCase: i jumpTargetBefore: pc - offsetToJump.
- 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc - offsetToJump.
  		"Find target from jump.  Ignore jumps to the interpret and MNU calls within this PIC"
  		self assert: (entryPoint > methodZoneBase and: [entryPoint < methodZone freeStart]).
  		(entryPoint asUnsignedInteger < cPIC asUnsignedInteger
  		 or: [entryPoint asUnsignedInteger > (cPIC asUnsignedInteger + cPIC blockSize) asUnsignedInteger]) ifTrue:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  			 self assert: (targetMethod cmType = CMMethod
  						or: [targetMethod cmType = CMFree]).
  			 (self markAndTraceOrFreeCogMethod: targetMethod
  				  firstVisit: targetMethod asUnsignedInteger > pc asUnsignedInteger) ifTrue:
  				[^true]].
  		offsetToLiteral := backEnd jumpLongConditionalByteSize.
  		offsetToJump := literalsManager literalBytesFollowingBranchInClosedPIC.
  		pc := pc + cPICCaseSize].
  	^false!

Item was changed:
  ----- Method: Cogit>>collectMapEntry:address:into: (in category 'disassembly') -----
  collectMapEntry: annotation address: mcpc into: aDictionary
  	<doNotGenerate>
+ 	aDictionary
+ 		at: mcpc
+ 		ifPresent:
+ 			[:extant|
+ 			aDictionary
+ 				at: mcpc
+ 				put: extant, ':\' withCRs, (self class annotationConstantNames at: annotation + 1)]
+ 		ifAbsentPut: [self class annotationConstantNames at: annotation + 1].
- 	aDictionary at: mcpc put: (self class annotationConstantNames at: annotation + 1).
  	^0!

Item was changed:
  ----- Method: Cogit>>generateMapAt:start: (in category 'method map') -----
  generateMapAt: addressOrNull start: startAddress
  	"Generate the method map at addressrNull (or compute it if addressOrNull is null).
  	 Answer the length of the map in byes.  Each entry in the map is in two parts.  In the
  	 least signficant bits are a displacement of how far from the start or previous entry,
  	 unless it is an IsAnnotationExtension byte, in which case those bits are the extension.
  	 In the most signficant bits are the type of annotation at the point reached.  A null
  	 byte ends the map."
  	| length location |
  	<var: #instruction type: #'AbstractInstruction *'>
  	length := 0.
  	location := startAddress.
  	0 to: opcodeIndex - 1 do:
  		[:i| | instruction mcpc delta maxDelta mapEntry |
  		instruction := self abstractInstructionAt: i.
  		instruction annotation ifNotNil:
  			[:annotation|
  			 literalsManager assertValidAnnotation: annotation for: instruction.
  			 mcpc := instruction mapEntryAddress.
  			 [(delta := mcpc - location / backEnd codeGranularity) > DisplacementMask] whileTrue:
  				[maxDelta := (delta min: MaxX2NDisplacement) bitClear: DisplacementMask.
  				 self assert: maxDelta >> AnnotationShift <= DisplacementMask.
  				 addressOrNull ifNotNil:
+ 					[self addToMap: IsDisplacementX2N
- 					[objectMemory
- 						byteAt: addressOrNull - length
- 						put: maxDelta >> AnnotationShift + DisplacementX2N.
- 					 self traceMap: IsDisplacementX2N
  						instruction: instruction
  						byte: maxDelta >> AnnotationShift + DisplacementX2N
  						at: addressOrNull - length
  						for: mcpc].
  				 location := location + (maxDelta * backEnd codeGranularity).
  				 length := length + 1].
  			 addressOrNull ifNotNil:
  				[mapEntry := delta + ((annotation min: IsSendCall) << AnnotationShift).
+ 				 self addToMap: annotation instruction: instruction byte: mapEntry at: addressOrNull - length for: mcpc].
- 				 objectMemory byteAt: addressOrNull - length put: mapEntry.
- 				 self traceMap: annotation
- 					instruction: instruction
- 					byte: mapEntry
- 					at: addressOrNull - length
- 					for: mcpc].
  			 location := location + (delta * backEnd codeGranularity).
  			 length := length + 1.
  			 annotation > IsSendCall ifTrue: "Add the necessary IsAnnotationExtension"
  				[addressOrNull ifNotNil:
  					[mapEntry := IsAnnotationExtension << AnnotationShift + (annotation - IsSendCall).
+ 					 self addToMap: annotation instruction: instruction byte: mapEntry at: addressOrNull - length for: mcpc].
- 					 objectMemory byteAt: addressOrNull - length put: mapEntry.
- 					 self traceMap: annotation
- 						instruction: instruction
- 						byte: mapEntry
- 						at: addressOrNull - length
- 						for: mcpc].
  				 length := length + 1]]].
  	addressOrNull ifNotNil:
+ 		[self addToMap: MapEnd instruction: nil byte: MapEnd at: addressOrNull - length for: 0].
- 		[objectMemory byteAt: addressOrNull - length put: MapEnd.
- 		 self traceMap: MapEnd
- 			instruction: nil
- 			byte: MapEnd
- 			at: addressOrNull - length
- 			for: 0].
  	^length + 1!

Item was changed:
  ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress
  	<api>
  	self cCode: [self sqMakeMemoryExecutableFrom: startAddress To: endAddress]
  		inSmalltalk: [self initializeProcessor].
  	codeBase := methodZoneBase := startAddress.
  	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
  								min: coInterpreter primitiveFailAddress.
  	self initializeBackend.
+ 	methodZone manageFrom: methodZoneBase to: endAddress.
  	self maybeGenerateCheckFeatures.
  	self maybeGenerateICacheFlush.
  	self generateVMOwnerLockFunctions.
  	ceGetSP := self cCoerceSimple: self genGetLeafCallStackPointer to: #'unsigned long (*)(void)'.
  	self generateStackPointerCapture.
  	self generateTrampolines.
- 	self cCode: '' inSmalltalk: [methodZone zoneEnd: endAddress]. "so that simulator works"
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	self computeEntryOffsets.
  	self generateClosedPICPrototype.
  	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
  	self generateOpenPICPrototype!

Item was changed:
  ----- Method: Cogit>>noTargetsFreeInClosedPIC: (in category 'compaction') -----
  noTargetsFreeInClosedPIC: cPIC
  	"Answerr if all targets in the PIC are in-use methods."
  	<var: #cPIC type: #'CogMethod *'>
  	| pc entryPoint targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	1 to: cPIC cPICNumCases do:
  		[:i|
+ 		entryPoint := literalsManager cPICCase: i jumpTargetBefore: pc.
- 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
  		"Find target from jump.  Ignore jumps to the interpret and MNU calls within this PIC"
  		(entryPoint < cPIC asInteger
  		 or: [entryPoint > (cPIC asInteger + cPIC blockSize)]) ifTrue:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  			 targetMethod cmType ~= CMMethod ifTrue:
  				[^false]].
  		i < cPIC cPICNumCases ifTrue:
  			[pc := pc + cPICCaseSize]].
  	^true!

Item was changed:
  ----- Method: Cogit>>relocateCallsInClosedPIC: (in category 'compaction') -----
  relocateCallsInClosedPIC: cPIC
  	<var: #cPIC type: #'CogMethod *'>
  	| delta pc entryPoint targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	delta := cPIC objectHeader.
  	self assert: (backEnd callTargetFromReturnAddress: cPIC asInteger + missOffset)
  					= (self picAbortTrampolineFor: cPIC cmNumArgs).
  	backEnd relocateCallBeforeReturnPC: cPIC asInteger + missOffset by: delta negated.
  
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	1 to: cPIC cPICNumCases do:
  		[:i|
+ 		entryPoint := literalsManager cPICCase: i jumpTargetBefore: pc.
- 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
  		"Find target from jump.  Ignore jumps to the interpret and MNU calls within this PIC"
  		(entryPoint < cPIC asInteger
  		 or: [entryPoint > (cPIC asInteger + cPIC blockSize)]) ifTrue:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  			 self assert: targetMethod cmType = CMMethod.
+ 			 literalsManager
+ 				cPICCase: i
+ 				relocateJumpLongBefore: pc
- 			 backEnd
- 				relocateJumpLongBeforeFollowingAddress: pc
  				by: (delta - targetMethod objectHeader) negated].
  		pc := pc + cPICCaseSize].
  	self assert: cPIC cPICNumCases > 0.
  	pc := pc - cPICCaseSize.
  	"Finally relocate the load of the PIC and the jump to the overflow routine ceCPICMiss:receiver:"
  	backEnd relocateMethodReferenceBeforeAddress: pc + backEnd loadPICLiteralByteSize by: delta.
  	backEnd relocateJumpLongBeforeFollowingAddress: pc + cPICEndSize by: delta negated!

Item was removed:
- ----- Method: Cogit>>traceMap:instruction:byte:at:for: (in category 'method map') -----
- traceMap: annotation instruction: instruction byte: byte at: address for: mcpc
- 	<cmacro: '(ig,no,r,e,d) 0'>
- 	| s bytecode |
- 	(compilationTrace anyMask: 16) ifTrue:
- 		[(s := coInterpreter transcript)
- 			ensureCr;
- 			print: annotation; nextPut: $/; nextPutAll: byte hex; space;
- 			nextPutAll: address hex; space; nextPutAll: mcpc hex; space;
- 			nextPutAll: (AnnotationConstantNames detect: [:name| (Cogit classPool at: name ifAbsent: []) = annotation]); cr; flush.
- 		(instruction notNil
- 		 and: [instruction bcpc isInteger]) ifTrue:
- 			[s tab; print: instruction bcpc; nextPut: $/.
- 			 instruction bcpc printOn: s base: 16.
- 			 s space.
- 			 instruction printStateOn: s.
- 			 s space.
- 			 bytecode := objectMemory fetchByte: instruction bcpc ofObject: methodObj.
- 			 bytecode := bytecode + (self bytecodeSetOffsetForHeader: (objectMemory methodHeaderOf: methodObj)).
- 			 (self generatorAt: bytecode) printStateOn: s.
- 			 s cr; flush]]!

Item was added:
+ ----- Method: InLineLiteralsManager>>cPICCase:jumpTargetBefore: (in category 'closed PIC parsing') -----
+ cPICCase: caseIndex jumpTargetBefore: pc
+ 	<inline: true>
+ 	^cogit backEnd jumpLongTargetBeforeFollowingAddress: pc!

Item was added:
+ ----- Method: InLineLiteralsManager>>cPICCase:relocateJumpLongBefore:by: (in category 'closed PIC parsing') -----
+ cPICCase: caseIndex relocateJumpLongBefore: pc by: delta
+ 	<inline: true>
+ 	cogit backEnd
+ 		relocateJumpLongBeforeFollowingAddress: pc
+ 		by: delta!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>cPICCase:jumpTargetBefore: (in category 'closed PIC parsing') -----
+ cPICCase: caseIndex jumpTargetBefore: pc
+ 	<inline: true>
+ 	"With Spur the class tag is always 32-bits and the literal is bytesPerOop.
+ 	 With V3 the class and literal are both bytesPerOop."
+ 	^cogit backEnd jumpLongTargetBeforeFollowingAddress: pc - (caseIndex <= 1
+ 																		ifTrue: [objectMemory bytesPerOop]
+ 																		ifFalse: [objectRepresentation inlineCacheTagsMayBeObjects
+ 																					ifTrue: [objectMemory bytesPerOop * 2]
+ 																					ifFalse: [objectMemory bytesPerOop + 4]])!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>cPICCase:relocateJumpLongBefore:by: (in category 'closed PIC parsing') -----
+ cPICCase: caseIndex relocateJumpLongBefore: pc by: delta
+ 	<inline: true>
+ 	"With Spur the class tag is always 32-bits and the literal is bytesPerOop.
+ 	 With V3 the class and literal are both bytesPerOop."
+ 	cogit backEnd
+ 		relocateJumpLongBeforeFollowingAddress: pc - (caseIndex <= 1
+ 															ifTrue: [objectMemory bytesPerOop]
+ 															ifFalse: [objectRepresentation inlineCacheTagsMayBeObjects
+ 																		ifTrue: [objectMemory bytesPerOop * 2]
+ 																		ifFalse: [objectMemory bytesPerOop + 4]])
+ 		by: delta!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genJumpBackTo: (in category 'bytecode generator support') -----
  genJumpBackTo: targetBytecodePC
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	self JumpAboveOrEqual: (self fixupAt: targetBytecodePC - initialPC).
+ 	self CallRT: ceCheckForInterruptTrampoline.
+ 	self annotateBytecode: self Label.
- 	self annotateBytecode: (self CallRT: ceCheckForInterruptTrampoline).
  	self Jump: (self fixupAt: targetBytecodePC - initialPC).
  	^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."
  	inBlock ifTrue:
  		[self assert: needsFrame.
+ 		 self CallRT: ceNonLocalReturnTrampoline.
+ 		 self annotateBytecode: self Label.
- 		 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 * objectMemory wordSize.
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>populate:withPICInfoFor:firstCacheTag: (in category 'method introspection') -----
  populate: tuple withPICInfoFor: cPIC firstCacheTag: firstCacheTag
  	"Populate tuple (which must be large enough) with the ClosedPIC's target method class pairs.
  	 The first entry in tuple contains the bytecode pc for the send, so skip the tuple's first field."
  	<var: #cPIC type: #'CogMethod *'>
  	| pc cacheTag classOop entryPoint targetMethod value |
  	<var: #targetMethod type: #'CogMethod *'>
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		cacheTag := i = 1
  						ifTrue: [firstCacheTag]
  						ifFalse: [backEnd literalBeforeFollowingAddress: pc
  																		- backEnd jumpLongConditionalByteSize
  																		- backEnd loadLiteralByteSize].
  		classOop := objectRepresentation classForInlineCacheTag: cacheTag.
  		objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.
+ 		entryPoint := literalsManager cPICCase: i jumpTargetBefore: pc.
- 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
  		"Find target from jump.  A jump to the MNU entry-point should collect #doesNotUnderstand:"
  		(entryPoint asUnsignedInteger < cPIC asUnsignedInteger
  		 or: [entryPoint asUnsignedInteger > (cPIC asUnsignedInteger + cPIC blockSize) asUnsignedInteger])
  			ifTrue:
  				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				 self assert: targetMethod cmType = CMMethod.
  				 value := targetMethod methodObject]
  			ifFalse:
  				[value := objectMemory splObj: SelectorDoesNotUnderstand].
  		objectMemory storePointer: i * 2 ofObject: tuple withValue: value.
  		pc := pc + cPICCaseSize]!

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
  	 CISCs (x86):
  				receiver
  				args
  		sp->	ret pc.
  	 RISCs (ARM):
  				receiver
  				args
  				ret pc in LR.
  	 A fully framed activation is described in CoInterpreter class>initializeFrameIndices.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
  	inBlock ifTrue:
  		[self assert: needsFrame. 
+ 		 self CallRT: ceNonLocalReturnTrampoline.
+ 		 self annotateBytecode: self Label.
- 		 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 * objectMemory wordSize]
  		ifFalse:
  			[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 * objectMemory wordSize]
  							ifFalse: [0])].
  	^0!



More information about the Vm-dev mailing list