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

commits at source.squeak.org commits at source.squeak.org
Fri Jun 12 00:57:21 UTC 2015


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

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

Name: VMMaker.oscog-eem.1350
Author: eem
Time: 11 June 2015, 5:54:31.583 pm
UUID: ae606b2c-4dc1-4c8f-9f69-793010abbd03
Ancestors: VMMaker.oscog-eem.1349

ARM Cogit:
Move the calculation of which address to annotate
for an annotated instruction into the instruction,
allowing CogOutOfLineLiteralsARMCompiler to
annotate the out-of-line literal, rather than the
instruction following, and implement literal update
on GC for out-of-line literals.

Slang:
Eliminate blank lines coming from conditional dead
code elimination.

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

Item was added:
+ ----- Method: CogAbstractInstruction>>mapEntryAddress (in category 'generate machine code') -----
+ mapEntryAddress
+ 	"Typically map entries apply to the end of an instruction, for two reasons:
+ 	  a)	to cope with literals embedded in variable-length instructions, since, e.g.
+ 		on x86, the literal typically comes at the end of the instruction.
+ 	  b)	in-line cache detection is based on return addresses, which are typically
+ 		to the instruction following a call."
+ 	<inline: true>
+ 	^address + machineCodeSize!

Item was added:
+ ----- Method: CogOutOfLineLiteralsARMCompiler>>mapEntryAddress (in category 'generate machine code') -----
+ mapEntryAddress
+ 	"Typically map entries apply to the end of an instruction, for two reasons:
+ 	  a)	to cope with literals embedded in variable-length instructions, since, e.g.
+ 		on x86, the literal typically comes at the end of the instruction.
+ 	  b)	in-line cache detection is based on return addresses, which are typically
+ 		to the instruction following a call.
+ 	 But with out-of-line literals it is more convenient to annotate the literal itself."
+ 	<inline: true>
+ 	^opcode = Literal
+ 		ifTrue: [address]
+ 		ifFalse: [address + machineCodeSize]!

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRef: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
+ 		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
- 		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation checkValidOopReference: literal) ifFalse:
  			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
  
  	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache enclosingObject |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			[(objectRepresentation checkValidOopReference: nsSendCache selector) ifFalse:
  				[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  				^1]].
  			(enclosingObject := nsSendCache enclosingObject) ~= 0 ifTrue:
  				[[(objectRepresentation checkValidOopReference: enclosingObject) ifFalse:
  					[coInterpreter print: 'enclosing object leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[| entryPoint selectorOrCacheTag offset |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint <= methodZoneBase
  			ifTrue:
  				[offset := entryPoint]
  			ifFalse:
  				[self
  					offsetAndSendTableFor: entryPoint
  					annotation: annotation
  					into: [:off :table| offset := off]].
  		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
  		 (entryPoint > methodZoneBase
  		  and: [offset ~= cmNoCheckEntryOffset
  		  and: [(self cCoerceSimple: entryPoint - offset to: #'CogMethod *') cmType ~= CMOpenPIC]])
  			ifTrue: "linked non-super send, cacheTag is a cacheTag"
  				[(objectRepresentation validInlineCacheTag: selectorOrCacheTag) ifFalse:
  					[coInterpreter print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]
  			ifFalse: "unlinked send or super send; cacheTag is a selector"
  				[(objectRepresentation checkValidOopReference: selectorOrCacheTag) ifFalse:
  					[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRefAndTarget:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRefAndTarget: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal entryPoint |
  	annotation = IsObjectReference ifTrue:
+ 		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (self asserta: (objectRepresentation checkValidOopReference: literal)) ifFalse:
  			[^1].
  		((objectRepresentation couldBeObject: literal)
  		 and: [objectMemory isReallyYoungObject: literal]) ifTrue:
  			[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  				[^2]]].
  
  	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache classTag enclosingObject nsTargetMethod |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(self asserta: (objectRepresentation checkValidOopReference: nsSendCache selector)) ifFalse:
  				[^9].
  			classTag := nsSendCache classTag.
  			(self asserta: (classTag = 0 or: [objectRepresentation validInlineCacheTag: classTag])) ifFalse:
  				[^10].
  			enclosingObject := nsSendCache enclosingObject.
  			(self asserta: (enclosingObject = 0 or: [objectRepresentation checkValidOopReference: enclosingObject])) ifFalse:
  				[^11].
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: [
  				nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				(self asserta: (nsTargetMethod cmType = CMMethod)) ifFalse:
  					[^12]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmType = CMMethod) ifFalse:
  			[^3].
  		 self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:offset :cacheTag :tagCouldBeObject|
  			tagCouldBeObject
  				ifTrue:
  					[(objectRepresentation couldBeObject: cacheTag)
  						ifTrue:
  							[(self asserta: (objectRepresentation checkValidOopReference: cacheTag)) ifFalse:
  								[^4]]
  						ifFalse:
  							[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  								[^5]].
  					((objectRepresentation couldBeObject: cacheTag)
  					 and: [objectMemory isReallyYoungObject: cacheTag]) ifTrue:
  						[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  							[^6]]]
  				ifFalse:
  					[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  						[^7]]].
  		entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint > methodZoneBase ifTrue:
  			["It's a linked send; find which kind."
  			 self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable|
  					 (self asserta: (targetMethod cmType = CMMethod
  								   or: [targetMethod cmType = CMClosedPIC
  								   or: [targetMethod cmType = CMOpenPIC]])) ifFalse:
  						[^8]]]].
  	^0 "keep scanning"!

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.
- 			 self flag: 'if this is moved into e.g. CogAbstractInstruction>>annotationAddress then e.g. a push const can annotate the lit synth instr, not the reg push'.
- 			 mcpc := instruction address + instruction machineCodeSize.
  			 [(delta := mcpc - location / backEnd codeGranularity) > DisplacementMask] whileTrue:
  				[maxDelta := (delta min: MaxX2NDisplacement) bitClear: DisplacementMask.
  				 self assert: maxDelta >> AnnotationShift <= DisplacementMask.
  				 addressOrNull ifNotNil:
  					[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).
  				 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).
  					 objectMemory byteAt: addressOrNull - length put: mapEntry.
  					 self traceMap: annotation
  						instruction: instruction
  						byte: mapEntry
  						at: addressOrNull - length
  						for: mcpc].
  				 length := length + 1]]].
  	addressOrNull ifNotNil:
  		[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>>markLiterals:pc:method: (in category 'garbage collection') -----
  markLiterals: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.
  	 Additionally in Newspeak, void push implicits that have unmarked classes."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
+ 		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
  	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			sel := nsSendCache selector.
  				(objectMemory isForwarded: sel)
  					ifFalse: [objectMemory markAndTrace: sel]
  					ifTrue: [sel := objectMemory followForwarded: literal.
  							nsSendCache selector: sel.
  							self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[(objectRepresentation
  						markAndTraceCacheTagLiteral: cacheTag
  						in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  						atpc: mcpc asUnsignedInteger) ifTrue:
  					["cacheTag is selector" codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
+ 		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
  	self cppIf: NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache entryPoint targetMethod sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: "Send is linked"
  				[targetMethod := entryPoint - cmNoCheckEntryOffset.
  				 (self markAndTraceOrFreeCogMethod: targetMethod
  					firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger) ifTrue:	
  						[self voidNSSendCache: nsSendCache]].
  			sel := nsSendCache selector.
  			(objectMemory isForwarded: sel)
  				ifFalse: [objectMemory markAndTrace: sel]
  				ifTrue: [sel := objectMemory followForwarded: literal.
  						nsSendCache selector: sel.
  						self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :sendTable| 
  						 (cacheTagMarked not
  						  or: [self markAndTraceOrFreeCogMethod: targetMethod
  								firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
  							 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable.
  							 objectRepresentation
  								markAndTraceLiteral: targetMethod selector
  								in: targetMethod
  								at: (self addressOf: targetMethod selector put: [:val| targetMethod selector: val])]]]
  				ifFalse:  "cacheTag is selector"
  					[(objectRepresentation
  							markAndTraceCacheTagLiteral: cacheTag
  							in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  							atpc: mcpc asUnsignedInteger) ifTrue:
  						[codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markYoungObjects:pc:method: (in category 'garbage collection') -----
  markYoungObjects: annotation pc: mcpc method: cogMethod
  	"Mark and trace young literals."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
+ 		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteralIfYoung: literal].
  
  	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[| nsSendCache |
  		 nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteralIfYoung: nsSendCache selector.
  		 nsSendCache enclosingObject ~= 0 ifTrue:
  			[objectRepresentation markAndTraceLiteralIfYoung: nsSendCache enclosingObject]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[objectRepresentation markAndTraceLiteralIfYoung: cacheTag]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>remapIfObjectRef:pc:hasYoung: (in category 'garbage collection') -----
  remapIfObjectRef: annotation pc: mcpc hasYoung: hasYoungPtr
  	<var: #mcpc type: #'char *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
+ 		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
- 		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
+ 				[literalsManager storeLiteral: mappedLiteral atAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
- 				[backEnd storeLiteral: mappedLiteral beforeFollowingAddress: mcpc asInteger.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  
  	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[| nsSendCache oop mappedOop |
  		nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  		oop := nsSendCache selector.	
  		mappedOop := objectRepresentation remapObject: oop.
  		oop ~= mappedOop ifTrue:
  			[nsSendCache selector: mappedOop.
  			(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  		oop := nsSendCache enclosingObject.	
  		oop ~= 0 ifTrue: [
  			mappedOop := objectRepresentation remapObject: oop.
  			oop ~= mappedOop ifTrue:
  				[nsSendCache enclosingObject: mappedOop.
  				(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  		^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | mappedCacheTag |
  			 (tagCouldBeObj
  			  and: [objectRepresentation couldBeObject: cacheTag]) ifTrue:
  				[mappedCacheTag := objectRepresentation remapObject: cacheTag.
  				 cacheTag ~= mappedCacheTag ifTrue:
  					[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asInteger.
  					 codeModified := true].
  				 (hasYoungPtr ~= 0
  				  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  			hasYoungPtr ~= 0 ifTrue:
  				["Since the unlinking routines may rewrite the cacheTag to the send's selector, and
  				  since they don't have the cogMethod to hand and can't add it to youngReferrers,
  				  the method must remain in youngReferrers if the targetMethod's selector is young."
  				 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :ignored|
  						 (objectMemory isYoung: targetMethod selector) ifTrue:
  							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]].
  	^0 "keep scanning"!

Item was added:
+ ----- Method: InLineLiteralsManager>>assertValidAnnotation:for: (in category 'generate machine code') -----
+ assertValidAnnotation: annotation for: instruction
+ 	<var: #instruction type: #'AbstractInstruction *'>
+ 	<inline: true>!

Item was added:
+ ----- Method: InLineLiteralsManager>>fetchLiteralAtAnnotatedAddress:using: (in category 'garbage collection') -----
+ fetchLiteralAtAnnotatedAddress: address using: instruction
+ 	"Normally literals are embedded in instructions and the annotation is at the start of
+ 	 the following instruction, to cope with literals embedded in variable-length instructions,
+ 	 since, e.g. on x86, the literal typically comes at the end of the instruction."
+ 	<var: 'instruction' type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	^instruction literalBeforeFollowingAddress: address!

Item was added:
+ ----- Method: InLineLiteralsManager>>storeLiteral:atAnnotatedAddress:using: (in category 'garbage collection') -----
+ storeLiteral: literal atAnnotatedAddress: address using: instruction
+ 	"Normally literals are embedded in instructions and the annotation is at the start of
+ 	 the following instruction, to cope with literals embedded in variable-length instructions,
+ 	 since, e.g. on x86, the literal typically comes at the end of the instruction."
+ 	<var: 'address' type: #usqInt>
+ 	<var: 'instruction' type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	^instruction storeLiteral: literal beforeFollowingAddress: address!

Item was changed:
  VMClass subclass: #OutOfLineLiteralsManager
+ 	instanceVariableNames: 'cogit objectMemory firstOpcodeIndex nextLiteralIndex lastDumpedLiteralIndex literals literalsSize'
- 	instanceVariableNames: 'cogit firstOpcodeIndex nextLiteralIndex lastDumpedLiteralIndex literals literalsSize'
  	classVariableNames: ''
  	poolDictionaries: 'CogCompilationConstants CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !OutOfLineLiteralsManager commentStamp: 'eem 6/7/2015 12:10' prior: 0!
  An OutOfLineLiteralsManager manages the dumping of literals for backends that wat to keep literals out-of-line, accessed by pc-relative addressing.
  
  Instance Variables
  	cogit:		<Cogit>!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>assertValidAnnotation:for: (in category 'generate machine code') -----
+ assertValidAnnotation: annotation for: instruction
+ 	"Insist that the IsObjectReference applies only to out-of-line literals."
+ 	<var: #instruction type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	self assert: (annotation ~= cogit getIsObjectReference or: [instruction opcode = Literal])!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>cogit: (in category 'initialization') -----
  cogit: aCogit
  	<doNotGenerate>
  	cogit := aCogit.
+ 	objectMemory := aCogit objectMemory.
  	literalsSize := 0!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>fetchLiteralAtAnnotatedAddress:using: (in category 'garbage collection') -----
+ fetchLiteralAtAnnotatedAddress: address using: instruction
+ 	"With out-of-line literals, the IsObjectReference annotation refers to
+ 	 the start of the literal and hence access the memory directly."
+ 	<var: 'instruction' type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	^objectMemory longAt: address!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>storeLiteral:atAnnotatedAddress:using: (in category 'garbage collection') -----
+ storeLiteral: literal atAnnotatedAddress: address using: instruction
+ 	"With out-of-line literals, the IsObjectReference annotation refers to
+ 	 the start of the literal and hence access the memory directly."
+ 	<var: 'address' type: #usqInt>
+ 	<var: 'instruction' type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	objectMemory longAt: address put: literal!

Item was changed:
  ----- Method: TStmtListNode>>emitCCodeOn:prependToEnd:level:generator: (in category 'C code generation') -----
  emitCCodeOn: aStream prependToEnd: aNodeOrNil level: level generator: aCodeGen
  	self emitCCommentOn: aStream level: level.
  	statements withIndexDo:
  		[:s :idx|
  		s isStmtList ifFalse:
  			[s emitCCommentOn: aStream level: level].
  		aStream peekLast ~~ Character tab ifTrue:
  			[aStream tab: level].
  		(aNodeOrNil notNil
  		 and: [idx = statements size])
  			ifTrue:
  				[s emitCCodeOn: aStream prependToEnd: aNodeOrNil level: level generator: aCodeGen]
  			ifFalse:
  				[s emitCCodeOn: aStream level: level generator: aCodeGen].
  		(self stream: aStream endsWithAnyOf: '};') ifFalse:
  			[s needsTrailingSemicolon ifTrue:
  				[aStream nextPut: $;]].
+ 		aStream peekLast ~~ Character cr ifTrue:
+ 			[aStream cr]].
- 		aStream cr].
  !



More information about the Vm-dev mailing list