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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 10 16:42:26 UTC 2015


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

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

Name: VMMaker.oscog-eem.1573
Author: eem
Time: 10 December 2015, 8:40:40.846 am
UUID: f73bf5a8-7b52-4be3-8983-50f7a73d45a8
Ancestors: VMMaker.oscog-rmacnak.1572

Refactor a few ifNil ifTrue:'s to ifNil: et al.  Slang is happy with this form.

=============== Diff against VMMaker.oscog-rmacnak.1572 ===============

Item was changed:
  ----- Method: CoInterpreter>>ceCheckProfileTick (in category 'cog jit support') -----
  ceCheckProfileTick
  	"Check if the profile timer has expired and if so take a sample.
  	 If the primitive has failed sample the profileMethod as nil.
  	 As a courtesy to compileInterpreterPrimitive: map NULL to nilObj."
  	<api>
+ 	newMethod ifNil: [newMethod := objectMemory nilObject].
- 	newMethod isNil ifTrue: [newMethod := objectMemory nilObject].
  	self cCode: [] inSmalltalk:
  		[newMethod = 0 ifTrue: [newMethod := objectMemory nilObject]].
  	self checkProfileTick: newMethod!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveCollectCogCodeConstituents (in category 'process primitives') -----
  primitiveCollectCogCodeConstituents
  	"Answer the contents of the code zone as an array of pair-wise element, address in ascending address order.
  	 Answer a string for a runtime routine or abstract label (beginning, end, etc), a CompiledMethod for a CMMethod,
  	 or a selector (presumably a Symbol) for a PIC."
  	| constituents |
  	constituents := cogit cogCodeConstituents.
+ 	constituents ifNil:
- 	constituents isNil ifTrue:
  		[^self primitiveFailFor: PrimErrNoMemory].
  	self pop: 1 thenPush: constituents!

Item was changed:
  ----- Method: CogAbstractInstruction>>addDependent: (in category 'accessing') -----
  addDependent: anInstruction
  	<var: #anInstruction type: #'AbstractInstruction *'>
  	<returnTypeC: #'AbstractInstruction *'>
+ 	dependent ifNotNil:
- 	dependent notNil ifTrue:
  		[anInstruction dependent: dependent].
  	^dependent := anInstruction!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
  	opcode ifNil:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	format := [CogRTLOpcodes printFormatForOpcodeName: opcodeName]
  				on: Error
  				do: [:ex| ].
  	orneryOperands withIndexDo:
  		[:operand :index|
+ 		operand ifNotNil:
- 		operand notNil ifTrue:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 (format notNil and: [(format at: index ifAbsent: nil) = $r])
  				ifTrue: [aStream nextPutAll: (self nameForRegister: operand)]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
  						[(operand allMask: 16r80000000) ifTrue:
  							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize ifNotNil:
  		[(machineCodeSize between: 1 and: machineCode size) ifTrue:
  			[0 to: machineCodeSize - 1 by: self codeGranularity do:
  				[:i|
  				 aStream space.
  				 (self machineCodeAt: i)
  					ifNil: [aStream nextPut: $.]
  					ifNotNil:
  						[:mc|
  						mc isInteger
  							ifTrue: [mc printOn: aStream base: 16]
  							ifFalse: [mc printOn: aStream]]]]].
  	address ifNotNil:
  		[aStream nextPut: $@.
  		 address printOn: aStream base: 16].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogAbstractInstruction>>symbolicOn: (in category 'printing') -----
  symbolicOn: aStream
  	| orneryOperands |
  	<doNotGenerate> "Smalltalk-side only"
  	(machineCodeSize isNil
  	 or: [opcode = 16rAAA]) ifTrue:
  		[^aStream nextPut: 'uninitialized opcode'].
  	aStream space; nextPut: $(; nextPutAll: (self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	orneryOperands withIndexDo:
  		[:operand :index|
+ 		operand ifNotNil:
- 		operand notNil ifTrue:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 operand class == self class
  				ifTrue:
  					[operand symbolicOn: aStream]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16]) ifTrue:
  						[(operand allMask: 16r80000000) ifTrue:
  							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize > 0 ifTrue:
  		[machineCodeSize > machineCode size
  			ifTrue: [aStream nextPutAll: ' no mcode']
  			ifFalse:
  				[0 to: machineCodeSize - 1 by: self codeGranularity do:
  					[:i|
  					 aStream space.
  					 (self machineCodeAt: i) printOn: aStream base: 16]]].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogVMSimulator>>mapFunctionToAddress: (in category 'cog jit support') -----
  mapFunctionToAddress: aSymbolOrIndexOrBlock
  	"Hackery to deal with the plugin primitive simulation hoops.
  	 aSymbolOrIndex is either a Symbol (#primitiveExternalCall) or an
  	 index above 1001 (an index + 1000 into the externalPrimitiveTable)."
  	| sobui symbolOrBlock |
  	aSymbolOrIndexOrBlock = 0 ifTrue: [^0].
  	self assert: (aSymbolOrIndexOrBlock isSymbol
  				or: [aSymbolOrIndexOrBlock isBlock
  				or: [aSymbolOrIndexOrBlock isInteger
  					and: [aSymbolOrIndexOrBlock between: 1001 and: 2000]]]).
  	symbolOrBlock := aSymbolOrIndexOrBlock isInteger
  						ifTrue: [(self pluginEntryFor: aSymbolOrIndexOrBlock) at: 3]
  						ifFalse: [aSymbolOrIndexOrBlock].
+ 	uniqueIndices ifNil:
- 	uniqueIndices isNil ifTrue:
  		[uniqueIndices := Dictionary new.
  		 uniqueIndex := 65535].
  	sobui := uniqueIndices at: symbolOrBlock ifAbsentPut: [uniqueIndex := uniqueIndex + 1].
  	^cogit
  		mapPrimitive: symbolOrBlock
  		withIndexToUniqueAddress: sobui!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack asUnsignedInteger.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop asUnsignedInteger.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
+ 	pic ifNil:
- 	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: targetMethod selector
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
  	processor flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>cogCodeConstituents (in category 'profiling primitives') -----
  cogCodeConstituents
  	"Answer the contents of the code zone as an array of pair-wise element, address in ascending address order.
  	 Answer a string for a runtime routine or abstract label (beginning, end, etc), a CompiledMethod for a CMMethod,
  	 or a selector (presumably a Symbol) for a PIC."
  	<api>
  	| count cogMethod constituents label value |
  	<var: #cogMethod type: #'CogMethod *'>
  	count := trampolineTableIndex / 2 + 3. "+ 3 for start, freeStart and end"
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[count := count + 1].
  		cogMethod := methodZone methodAfter: cogMethod].
  	constituents := coInterpreter instantiateClass: coInterpreter classArray indexableSize: count * 2.
+ 	constituents ifNil:
- 	constituents isNil ifTrue:
  		[^constituents].
  	coInterpreter pushRemappableOop: constituents.
  	((label := objectMemory stringForCString: 'CogCode') isNil
  	 or: [(value := self positiveMachineIntegerFor: codeBase) isNil]) ifTrue:
  		[^nil].
  	coInterpreter
  		storePointerUnchecked: 0 ofObject: coInterpreter topRemappableOop withValue: label;
  		storePointerUnchecked: 1 ofObject: coInterpreter topRemappableOop withValue: value.
  	0 to: trampolineTableIndex - 1 by: 2 do:
  		[:i|
  		((label := objectMemory stringForCString: (trampolineAddresses at: i)) isNil
  		 or: [(value := self positiveMachineIntegerFor: (trampolineAddresses at: i + 1) asUnsignedInteger) isNil]) ifTrue:
  			[coInterpreter popRemappableOop.
  			 ^nil].
  		coInterpreter
  			storePointerUnchecked: 2 + i ofObject: coInterpreter topRemappableOop withValue: label;
  			storePointerUnchecked: 3 + i ofObject: coInterpreter topRemappableOop withValue: value].
  	count := trampolineTableIndex + 2.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[coInterpreter
  				storePointerUnchecked: count
  				ofObject: coInterpreter topRemappableOop
  				withValue: (cogMethod cmType = CMMethod
  								ifTrue: [cogMethod methodObject]
  								ifFalse: [cogMethod selector]).
+ 			 (value := self positiveMachineIntegerFor: cogMethod asUnsignedInteger) ifNil:
- 			 (value := self positiveMachineIntegerFor: cogMethod asUnsignedInteger) isNil ifTrue:
  				[coInterpreter popRemappableOop.
  				 ^nil].
  			 coInterpreter
  				storePointerUnchecked: count + 1
  				ofObject: coInterpreter topRemappableOop
  				withValue: value.
  			 count := count + 2].
  		cogMethod := methodZone methodAfter: cogMethod].
  	((label := objectMemory stringForCString: 'CCFree') isNil
  	 or: [(value := self positiveMachineIntegerFor: methodZone zoneFree) isNil]) ifTrue:
  		[coInterpreter popRemappableOop.
  		 ^nil].
  	coInterpreter
  		storePointerUnchecked: count ofObject: coInterpreter topRemappableOop withValue: label;
  		storePointerUnchecked: count + 1 ofObject: coInterpreter topRemappableOop withValue: value.
  	((label := objectMemory stringForCString: 'CCEnd') isNil
  	 or: [(value := self positiveMachineIntegerFor: methodZone zoneEnd) isNil]) ifTrue:
  		[coInterpreter popRemappableOop.
  		 ^nil].
  	coInterpreter
  		storePointerUnchecked: count + 2 ofObject: coInterpreter topRemappableOop withValue: label;
  		storePointerUnchecked: count + 3 ofObject: coInterpreter topRemappableOop withValue: value.
  	constituents := coInterpreter popRemappableOop.
  	coInterpreter beRootIfOld: constituents.
  	^constituents!

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|
  	<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) 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]].
- 			 targetEntry := case1Method isNil ifTrue: [cPIC asInteger + (self sizeof: CogMethod)] ifFalse: [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."!

Item was changed:
  ----- Method: Cogit>>initialMethodUsageCount (in category 'generate machine code') -----
  initialMethodUsageCount
  	"Answer a usage count that reflects likely long-term usage.
  	 Answer 1 for non-primitives or quick primitives (inst var accessors),
  	 2 for methods with interpreter primitives, and 3 for compiled primitives."
  	(primitiveIndex = 1
  	 or: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^1].
+ 	self primitiveGeneratorOrNil ifNil:
- 	self primitiveGeneratorOrNil isNil ifTrue:
  		[^2].
  	^3!

Item was changed:
  ----- Method: Cogit>>patchToOpenPICFor:numArgs:receiver: (in category 'in-line cacheing') -----
  patchToOpenPICFor: selector numArgs: numArgs receiver: receiver
  	"Code entry closed PIC full or miss to an instance of a young class or to a young target method.
  	 Attempt to patch the send site to an open PIC.  Answer if the attempt succeeded; in fact it will
  	 only return if the attempt failed.
  	 The stack looks like:
  			receiver
  			args
  	 sp=>	sender return address"
  	<api>
  	| oPIC outerReturn extent |
  	<var: #oPIC type: #'CogMethod *'>
  	outerReturn := coInterpreter stackTop.
  	"See if an Open PIC is already available."
  	oPIC := methodZone openPICWithSelector: selector.
+ 	oPIC ifNil:
- 	oPIC isNil ifTrue:
  		["otherwise attempt to create an Open PIC."
  		oPIC := self cogOpenPICSelector: selector numArgs: numArgs.
  		(oPIC asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory."
  			oPIC asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^false]].
  	extent := backEnd
  				rewriteInlineCacheAt: outerReturn
  				tag: selector
  				target: oPIC asInteger + cmEntryOffset.
  	processor
  		flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger;
  		flushICacheFrom: oPIC asUnsignedInteger to: oPIC asUnsignedInteger + openPICSize.
  	"Jump into the oPIC at its entry"
  	coInterpreter executeCogMethod: oPIC fromLinkedSendWithReceiver: receiver.
  	"NOTREACHED"
  	^true!

Item was changed:
  ----- Method: Cogit>>unlinkAllSends (in category 'jit - api') -----
  unlinkAllSends
  	<api>
  	"Unlink all sends in cog methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	methodZoneBase ifNil: [^self].
- 	methodZoneBase isNil ifTrue: [^self].
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSend:pc:ignored:
  					 arg: 0]
  			ifFalse:
  				[cogMethod cmType ~= CMFree ifTrue:
  					[methodZone freeMethod: cogMethod]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	"After updating inline caches we need to flush the icache."
  	processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger!

Item was changed:
  ----- Method: Cogit>>unlinkSendsOf:isMNUSelector: (in category 'jit - api') -----
  unlinkSendsOf: selector isMNUSelector: isMNUSelector
  	<api>
  	"Unlink all sends in cog methods. Free all Closed PICs with the selector,
  	 or with an MNU case if isMNUSelector.  First check if any method actually
  	 has the selector; if not there can't be any linked send to it.  This routine
  	 (including descendents) is performance critical.  It contributes perhaps
  	 30% of entire execution time in Compiler recompileAll."
  	| cogMethod mustScanAndUnlink |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	methodZoneBase ifNil: [^self].
- 	methodZoneBase isNil ifTrue: [^self].
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	mustScanAndUnlink := false.
  	isMNUSelector
  		ifTrue:
  			[[cogMethod < methodZone limitZony] whileTrue:
  				[cogMethod cmType ~= CMFree ifTrue:
  					[cogMethod cpicHasMNUCase
  						ifTrue:
  							[self assert: cogMethod cmType = CMClosedPIC.
  							 methodZone freeMethod: cogMethod.
  							 mustScanAndUnlink := true]
  						ifFalse:
  							[cogMethod selector = selector ifTrue:
  								[mustScanAndUnlink := true.
  								 cogMethod cmType = CMClosedPIC ifTrue:
  									[methodZone freeMethod: cogMethod]]]].
  				 cogMethod := methodZone methodAfter: cogMethod]]
  		ifFalse:
  			[[cogMethod < methodZone limitZony] whileTrue:
  				[(cogMethod cmType ~= CMFree
  				  and: [cogMethod selector = selector]) ifTrue:
  					[mustScanAndUnlink := true.
  					 cogMethod cmType = CMClosedPIC ifTrue:
  						[methodZone freeMethod: cogMethod]].
  				 cogMethod := methodZone methodAfter: cogMethod]].
  	mustScanAndUnlink ifFalse:
  		[^self].
  	codeModified := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod ifTrue:
  			[self mapFor: cogMethod
  				 performUntil: #unlinkIfFreeOrLinkedSend:pc:of:
  				 arg: selector].
  		cogMethod := methodZone methodAfter: cogMethod].
  	codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>unlinkSendsTo:andFreeIf: (in category 'jit - api') -----
  unlinkSendsTo: targetMethodObject andFreeIf: freeIfTrue
  	<api>
  	"Unlink all sends in cog methods to a particular target method.
  	 If targetMethodObject isn't actually a method (perhaps being
  	 used via invokeAsMethod) then there's nothing to do."
  	| cogMethod targetMethod freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	((objectMemory isOopCompiledMethod: targetMethodObject)
  	and: [coInterpreter methodHasCogMethod: targetMethodObject]) ifFalse:
  		[^self].
  	targetMethod := coInterpreter cogMethodOf: targetMethodObject.
+ 	methodZoneBase ifNil: [^self].
- 	methodZoneBase isNil ifTrue: [^self].
  	codeModified := freedPIC := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSend:pc:to:
  					 arg: targetMethod asInteger]
  			ifFalse:
  				[(cogMethod cmType = CMClosedPIC
  				  and: [self cPIC: cogMethod HasTarget: targetMethod]) ifTrue:
  					[methodZone freeMethod: cogMethod.
  					 freedPIC := true]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	freeIfTrue ifTrue: [self freeMethod: targetMethod].
  	freedPIC
  		ifTrue: [self unlinkSendsToFree]
  		ifFalse:
  			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  				[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]!

Item was changed:
  ----- Method: Cogit>>unlinkSendsToFree (in category 'garbage collection') -----
  unlinkSendsToFree
  	<api>
  	"Unlink all sends in cog methods to free methods and/or pics."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	methodZoneBase ifNil: [^self].
- 	methodZoneBase isNil ifTrue: [^self].
  	codeModified := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSendToFree:pc:ignored:
  					 arg: 0]
  			ifFalse:
  				[cogMethod cmType = CMClosedPIC ifTrue:
  					[self assert: (self noTargetsFreeInClosedPIC: cogMethod)]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine
  	"Compile a call to an interpreter primitive.  Call the C routine with the
  	 usual stack-switching dance, test the primFailCode and then either
  	 return on success or continue to the method body."
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| flags jmp jmpSamplePrim retry continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
  	<var: #jmp type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	<var: #jmpSamplePrim type: #'AbstractInstruction *'>
  	<var: #continuePostSamplePrim type: #'AbstractInstruction *'>
  	<var: #jmpSampleNonPrim type: #'AbstractInstruction *'>
  	<var: #continuePostSampleNonPrim type: #'AbstractInstruction *'>
  
  	"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
  	self genExternalizePointersForPrimitiveCall.
  	"Switch to the C stack."
  	self genLoadCStackPointersForPrimCall.
  
  	flags := coInterpreter primitivePropertyFlags: primitiveIndex.
  	(flags anyMask: PrimCallDoNotJIT) ifTrue:
  		[^ShouldNotJIT].
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick if so"
  		objectMemory wordSize = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
  				 self OrR: TempReg R: ClassReg]
  			ifFalse:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self CmpCq: 0 R: TempReg].
  		"If set, jump to record sample call."
  		jmpSampleNonPrim := self JumpNonZero: 0.
  		continuePostSampleNonPrim := self Label].
  
  	"Old full prim trace is in VMMaker-eem.550 and prior"
  	self recordPrimTrace ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	retry := self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self MoveCq: methodOrBlockNumArgs R: TempReg].
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  
  	"If required, set primitiveFunctionPointer and newMethod"
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[self MoveCw: primitiveRoutine asInteger R: TempReg.
  		 primSetFunctionLabel :=
  		 self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  	(flags anyMask: PrimCallNeedsNewMethod+PrimCallMayCallBack) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags anyMask: PrimCallMayCallBack) ifTrue:
  			[needsFrame := true].
  		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		 self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter newMethodAddress].
  
  	"Invoke the primitive"
  	self PrefetchAw: coInterpreter primFailCodeAddress.
  	(flags anyMask: PrimCallMayCallBack)
  		ifTrue: "Sideways call the C primitive routine so that we return through cePrimReturnEnterCogCode."
  			["On Spur ceActivateFailingPrimitiveMethod: would like to retry if forwarders
  			  are found. So insist on PrimCallNeedsPrimitiveFunction being set too."
  			 self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction).
  			 backEnd genSubstituteReturnAddress:
  				((flags anyMask: PrimCallCollectsProfileSamples)
  					ifTrue: [cePrimReturnEnterCogCodeProfiling]
  					ifFalse: [cePrimReturnEnterCogCode]).
  			 primInvokeInstruction := self JumpFullRT: primitiveRoutine asInteger.
  			 jmp := jmpSamplePrim := continuePostSamplePrim := nil]
  		ifFalse:
  			["Call the C primitive routine."
  			primInvokeInstruction := self CallFullRT: primitiveRoutine asInteger.
  			(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  				[self assert: (flags anyMask: PrimCallNeedsNewMethod).
  				"Test nextProfileTick for being non-zero and call checkProfileTick if so"
  				objectMemory wordSize = 4
  					ifTrue:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
  						 self OrR: TempReg R: ClassReg]
  					ifFalse:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self CmpCq: 0 R: TempReg].
  				"If set, jump to record sample call."
  				jmpSamplePrim := self JumpNonZero: 0.
  				continuePostSamplePrim := self Label].
  			objectRepresentation maybeCompileRetry: retry onPrimitiveFail: primitiveIndex.
  			self maybeCompileAllocFillerCheck.
  			"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  				success:	stackPointer ->	result (was receiver)
  											arg1
  											...
  											argN
  											return pc
  				failure:						receiver
  											arg1
  											...
  							stackPointer ->	argN
  											return pc
  			In either case we can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
  			self MoveAw: coInterpreter instructionPointerAddress
  				R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  			backEnd genLoadStackPointers.
  			"Test primitive failure"
  			self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  			backEnd hasLinkRegister ifFalse: [self PushR: ClassReg]. "Restore return pc on CISCs"
  			self flag: 'ask concrete code gen if move sets condition codes?'.
  			self CmpCq: 0 R: TempReg.
  			jmp := self JumpNonZero: 0.
  			"Fetch result from stack"
  			self MoveMw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
  				r: SPReg
  				R: ReceiverResultReg.
  			self RetN: objectMemory wordSize].	"return to caller, popping receiver"
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["The sample is collected by cePrimReturnEnterCogCode for external calls"
+ 		jmpSamplePrim ifNotNil:
- 		jmpSamplePrim notNil ifTrue:
  			["Call ceCheckProfileTick: to record sample and then continue."
  			jmpSamplePrim jmpTarget: self Label.
  			self assert: (flags anyMask: PrimCallNeedsNewMethod).
  			self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedLong]
  							   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  			"reenter the post-primitive call flow"
  			self Jump: continuePostSamplePrim].
  		"Null newMethod and call ceCheckProfileTick: to record sample and then continue.
  		 ceCheckProfileTick will map null/0 to coInterpreter nilObject"
  		jmpSampleNonPrim jmpTarget: self Label.
  		self MoveCq: 0 R: TempReg.
  		self MoveR: TempReg Aw: coInterpreter newMethodAddress.
  		self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedLong]
  						   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		"reenter the post-primitive call flow"
  		self Jump: continuePostSampleNonPrim].
  
+ 	jmp ifNotNil:
- 	jmp notNil ifTrue:
  		["Jump to restore of receiver reg and proceed to frame build for failure."
  		 jmp jmpTarget: self Label.
  		 "Restore receiver reg from stack.  If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
  		 self MoveMw: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
  			r: SPReg
  			R: ReceiverResultReg].
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>picDataFor:Annotation:Mcpc:Bcpc:Method: (in category 'method introspection') -----
  picDataFor: descriptor Annotation: annotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #mcpc type: #'char *'>
  	<var: #cogMethodArg type: #'void *'>
  	| entryPoint tuple counter |
  	<var: #counter type: #'unsigned long'>
  
+ 	descriptor ifNil:
- 	descriptor isNil ifTrue:
  		[^0].
  	descriptor isBranch ifTrue:
  		["it's a branch; conditional?"
  		 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
  			[counter := (self
  							cCoerce: ((self
  											cCoerceSimple: cogMethodArg
  											to: #'CogMethod *') counters)
  							to: #'unsigned long *')
  								at: counterIndex.
  			 tuple := self picDataForCounter: counter at: bcpc + 1.
  			 tuple = 0 ifTrue: [^PrimErrNoMemory].
  			 objectMemory storePointer: picDataIndex ofObject: picData withValue: tuple.
  			 picDataIndex := picDataIndex + 1.
  			 counterIndex := counterIndex + 1].
  		 ^0].
  	((self isPureSendAnnotation: annotation)
  	 and: [entryPoint := backEnd callTargetFromReturnAddress: mcpc asUnsignedInteger.
  		 entryPoint > methodZoneBase]) ifFalse: "send is not linked, or is not a send"
  		[^0].
  	self targetMethodAndSendTableFor: entryPoint "It's a linked send; find which kind."
  		annotation: annotation
  		into: [:targetMethod :sendTable| | methodClassIfSuper association |
  			methodClassIfSuper := nil.
  			sendTable = superSendTrampolines ifTrue:
  				[methodClassIfSuper := coInterpreter methodClassOf: (self cCoerceSimple: cogMethodArg to: #'CogMethod *') methodObject].
  			sendTable = directedSuperSendTrampolines ifTrue:
  				[association := backEnd literalBeforeInlineCacheTagAt: mcpc asUnsignedInteger.
  				 methodClassIfSuper := objectRepresentation valueOfAssociation: association].
  			tuple := self picDataForSendTo: targetMethod
  						methodClassIfSuper: methodClassIfSuper
  						at: mcpc
  						bcpc: bcpc + 1].
  	tuple = 0 ifTrue: [^PrimErrNoMemory].
  	objectMemory storePointer: picDataIndex ofObject: picData withValue: tuple.
  	picDataIndex := picDataIndex + 1.
  	^0!



More information about the Vm-dev mailing list