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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 14 01:32:24 UTC 2012


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

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

Name: VMMaker.oscog-eem.201
Author: eem
Time: 13 August 2012, 6:30:31.048 pm
UUID: 56cdd078-6771-401a-8bed-68402a0e283d
Ancestors: VMMaker.oscog-eem.200

Make sure youngReferrersList has room for every method since
become/cache implicit receiver can cause any method to gain a
young reference.  Do so by counting methods in the zone.

Refactor type name manipulation to move
extractTypeFor:fromDeclaration: from TMethod to CCodeGenerator.

Rename CogMethodZone>>zoneLimit to freeStart.

Fix assert in interpretMethodFromMachineCode.

Fix return type of jumpTargetAddress & longJumpTargetAddress.

Fix simulation of rewritePrimInvocationIn:.

Nuke unused methodBytesFreedSinceLastCompaction method.

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

Item was added:
+ ----- Method: CCodeGenerator>>extractTypeFor:fromDeclaration: (in category 'utilities') -----
+ extractTypeFor: aVariable fromDeclaration: aVariableDeclaration
+ 	"Eliminate inessentials from aVariableDeclaration to answer a C type without the variable,
+ 	 or initializations etc"
+ 	| decl fpIndex |
+ 	decl := aVariableDeclaration.
+ 	(decl beginsWith: 'static') ifTrue:
+ 		[decl := decl allButFirst: 6].
+ 	(decl indexOf: $= ifAbsent: []) ifNotNil:
+ 		[:index| decl := decl copyFrom: 1 to: index - 1].
+ 	decl := decl copyReplaceAll: aVariable with: '' tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]].
+ 	(fpIndex := decl indexOfSubCollection: '(*') > 0 ifTrue:
+ 		[decl := decl copyReplaceFrom: (decl indexOf: $( startingAt: fpIndex + 1)
+ 					to: (decl indexOf: $) startingAt: fpIndex + 1)
+ 					with: ''].
+ 	^decl withBlanksTrimmed!

Item was added:
+ ----- Method: CCodeGenerator>>testInliningFor:as: (in category 'utilities') -----
+ testInliningFor: selector as: inlineFlagOrSymbol
+ 	"Test inlining for the method with the given selector.
+ 	 Do all inlining first (cuz that's how the algorithm works.
+ 	 Then try and inline into a copy of the method.  This isn't
+ 	 exactly what happens in the real deal but is close enough."
+ 	| meth |
+ 	meth := (self methodNamed: selector) copy.
+ 	self doBasicInlining: inlineFlagOrSymbol.
+ 	self halt.
+ 	meth tryToInlineMethodsIn: self!

Item was changed:
  ----- Method: CCodeGenerator>>typeOfVariable: (in category 'C code generator') -----
  typeOfVariable: varName "<String>" 
  	scopeStack reverseDo:
  		[:dict|
  		(dict includesKey: varName) ifTrue:
+ 			[^self
+ 				extractTypeFor: varName
+ 				fromDeclaration: (dict at: varName)]].
+ 	^self
+ 		extractTypeFor: varName
+ 		fromDeclaration: (variableDeclarations at: varName ifAbsent: [^nil])!
- 			[^dict at: varName]].
- 	^variableDeclarations at: varName ifAbsent: nil!

Item was changed:
  ----- Method: CoInterpreter>>interpretMethodFromMachineCode (in category 'message sending') -----
  interpretMethodFromMachineCode
  	"Execute a method interpretively from machine code.  We assume (require) that newMethod
  	 messageSelector, primitiveFunctionPointer and argumentCount have been set in the caller.
  	 Once evaluated either continue in the interpreter via a jongjmp or in machine code via an
  	 enilopmart (a form of longjmp - a stinking rose by any other name)."
  	<inline: false>
  	cogit assertCStackWellAligned.
  	self assert: (self validInstructionPointer: instructionPointer inFrame: framePointer).
  	primitiveFunctionPointer ~= 0
  		ifTrue:
  			[primitiveFunctionPointer = #primitiveInvokeObjectAsMethod asSymbol
  				ifTrue: [self assert: (objectMemory isOopCompiledMethod: newMethod) not]
  				ifFalse: [self assert: ((objectMemory isOopCompiledMethod: newMethod)
  									  and: [(self primitiveIndexOf: newMethod) ~= 0])].
  			 "Invoke an interpreter primitive (because the method is to be interpreted or has not yet been
  			  compiled).  This is very similar to invoking an interpreter primitive from a compiled primitive
  			  (see e.g. SimpleStackBasedCogit>>compileInterpreterPrimitive:).  Cut back the stack pointer
  			  (done above) to skip the return address and invoke the function.  On return if it has succeeded
  			  simply continue otherwise restore the stackPointer, collect the pc and interpret.  Note that
  			  frame building primitives such as primitiveClosureValue, primitiveEvaluateMethod et al will not
  			  return but will instead jump into either machine code or longjmp back to the interpreter."
  			"Assign stackPage headFP so we can tell if the primitive built a frame.  We can't simply save
  			 the framePointer since e.g. assignment to contexts (via primitiveInstVarAt:put:) can change the
  			 framePointer.  But context assignments will change both the framePointer and stackPage headFP."
  			 stackPage headFP: framePointer.
  			 self isPrimitiveFunctionPointerAnIndex
  				ifTrue:
  					[self externalQuickPrimitiveResponse.
  					 primFailCode := 0]
  				ifFalse:
  					[self slowPrimitiveResponse].
  			self successful ifTrue:
  				[self return: self popStack toExecutive: false
  				 "NOTREACHED"]]
  		ifFalse:
+ 			[self assert: ((self isOopCompiledMethod: newMethod)
+ 						   and: [(self primitiveIndexOf: newMethod) = 0
+ 								or: [(self functionPointerFor: (self primitiveIndexOf: newMethod) inClass: objectMemory nilObject) = 0
+ 								or: [self isNullExternalPrimitiveCall: newMethod]]])].
- 			[self assert: ((self primitiveIndexOf: newMethod) = 0
- 						or: [(self functionPointerFor: (self primitiveIndexOf: newMethod) inClass: objectMemory nilObject) = 0])].
  	"if not primitive, or primitive failed, activate the method and reenter the interpreter"
  	self activateNewMethod.
  	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: CogAbstractInstruction>>jumpTargetAddress (in category 'generate machine code') -----
  jumpTargetAddress
+ 	<returnTypeC: #'AbstractInstruction *'>
  	<inline: true> "Since it's an extraction from other methods."
  	| jumpTarget |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	cogit assertSaneJumpTarget: jumpTarget.
  	(self isAnInstruction: jumpTarget) ifTrue:
  		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
  	self assert: jumpTarget ~= 0.
  	^jumpTarget!

Item was changed:
  ----- Method: CogAbstractInstruction>>longJumpTargetAddress (in category 'generate machine code') -----
  longJumpTargetAddress
+ 	<returnTypeC: #'AbstractInstruction *'>
  	<inline: true> "Since it's an extraction from other methods."
  	"This needs to be digfferent from jumpTargetAddress because long jumps can
  	be to absolute addresses and hence we can't assert that the jump target is sane."
  	| jumpTarget |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
  	(self isAnInstruction: jumpTarget) ifTrue:
  		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
  	self assert: jumpTarget ~= 0.
  	^jumpTarget!

Item was changed:
  CogClass subclass: #CogMethodZone
+ 	instanceVariableNames: 'youngReferrers methodCount openPICList mzFreeStart baseAddress limitAddress methodBytesFreedSinceLastCompaction coInterpreter objectRepresentation cogit objectMemory'
- 	instanceVariableNames: 'youngReferrers openPICList mzFreeStart baseAddress limitAddress methodBytesFreedSinceLastCompaction coInterpreter objectRepresentation cogit objectMemory'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
  !CogMethodZone commentStamp: '<historical>' prior: 0!
  I am a simple allocator/deallocator for the native code zone.  I also manage the youngReferers list, which contains methods that may refer to one or more young objects, and the openPICList which is a linked list of all open PICs in the zone.!

Item was changed:
  ----- Method: CogMethodZone>>allocate: (in category 'allocating') -----
  allocate: numBytes
  	| roundedBytes allocation |
  	roundedBytes := numBytes + 7 bitAnd: -8.
+ 	mzFreeStart + roundedBytes >= (limitAddress - (methodCount * BytesPerWord)) ifTrue:
- 	mzFreeStart + roundedBytes > (youngReferrers - BytesPerWord) ifTrue:
  		[^0].
  	allocation := mzFreeStart.
  	mzFreeStart := mzFreeStart + roundedBytes.
+ 	methodCount := methodCount + 1.
+ 	self assert: self roomOnYoungReferrersList.
  	self cCode: '' inSmalltalk:
  		[(cogit breakPC isInteger
  		   and: [cogit breakPC between: allocation and: mzFreeStart]) ifTrue:
  			[cogit singleStep: true]].
  	^allocation!

Item was changed:
  ----- Method: CogMethodZone>>clearCogCompiledCode (in category 'jit - api') -----
  clearCogCompiledCode
  	"Free all methods"
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	 cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	 [cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
  		[cogMethod cmType = CMMethod ifTrue:
  			[self freeMethod: cogMethod].
  		 cogMethod := self methodAfter: cogMethod].
+ 	self manageFrom: baseAddress to: limitAddress!
- 	mzFreeStart := baseAddress.
- 	youngReferrers := limitAddress.
- 	openPICList := nil.
- 	methodBytesFreedSinceLastCompaction := 0!

Item was added:
+ ----- Method: CogMethodZone>>cogit (in category 'simulation only') -----
+ cogit
+ 	"This is for the sizeof: CogMethod hook that allows different cogit classes to use differet CogMethod variants."
+ 	<doNotGenerate>
+ 	^cogit!

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode: (in category 'compaction') -----
  compactCompiledCode: objectHeaderValue
  	| source dest bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	openPICList := nil.
+ 	methodCount := 0.
  	[source < self limitZony
  	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
  		 source objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
  			[source cmUsageCount: source cmUsageCount // 2].
  		 source cmType = CMOpenPIC ifTrue:
  			[source nextOpenPIC: openPICList asUnsignedInteger.
  			 openPICList := source].
+ 		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
  		 source cmType ~= CMFree ifTrue:
+ 			[methodCount := methodCount + 1.
+ 			 self mem: dest mo: source ve: bytes.
- 			[self mem: dest mo: source ve: bytes.
  			 dest objectHeader: objectHeaderValue.
  			 dest cmType = CMMethod
  				ifTrue:
  					["For non-Newspeak there should ne a one-to-one mapping metween bytecoded and
  					  cog methods. For Newspeak not necessarily, but only for anonymous accessors."
  					 self assert: ((coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  								or: [(cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject]).
  					"Only update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger ifTrue:
  						[coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]]
  				ifFalse:
  					[dest cmType = CMOpenPIC ifTrue:
  						[dest nextOpenPIC: openPICList asUnsignedInteger.
  						 openPICList := dest]].
  			 dest cmUsageCount > 0 ifTrue:
  				[dest cmUsageCount: dest cmUsageCount // 2].
  			 dest := coInterpreter
  								cCoerceSimple: dest asInteger + bytes
  								to: #'CogMethod *'].
  		 source := coInterpreter
  							cCoerceSimple: source asInteger + bytes
  							to: #'CogMethod *'].
  	mzFreeStart := dest asInteger.
  	methodBytesFreedSinceLastCompaction := 0!

Item was added:
+ ----- Method: CogMethodZone>>freeStart (in category 'accessing') -----
+ freeStart
+ 	<inline: true>
+ 	<returnTypeC: #usqInt>
+ 	^mzFreeStart!

Item was added:
+ ----- Method: CogMethodZone>>freeStart: (in category 'accessing') -----
+ freeStart: zoneLimit
+ 	<doNotGenerate>
+ 	^mzFreeStart := zoneLimit!

Item was changed:
  ----- Method: CogMethodZone>>manageFrom:to: (in category 'initialization') -----
  manageFrom: theStartAddress to: theLimitAddress
  	<returnTypeC: #void>
  	mzFreeStart := baseAddress := theStartAddress.
  	youngReferrers := limitAddress := theLimitAddress.
  	openPICList := nil.
+ 	methodBytesFreedSinceLastCompaction := 0.
+ 	methodCount := 0!
- 	methodBytesFreedSinceLastCompaction := 0!

Item was removed:
- ----- Method: CogMethodZone>>methodBytesFreedSinceLastCompaction (in category 'accessing') -----
- methodBytesFreedSinceLastCompaction
- 	<cmacro: '() methodBytesFreedSinceLastCompaction'> "we all get a tad fatigued now and again..."
- 	^methodBytesFreedSinceLastCompaction!

Item was added:
+ ----- Method: CogMethodZone>>numMethods (in category 'accessing') -----
+ numMethods
+ 	^methodCount!

Item was changed:
  ----- Method: CogMethodZone>>roomOnYoungReferrersList (in category 'young referers') -----
  roomOnYoungReferrersList
+ 	"The youngReferrers list holds methods that may contain a reference to a young
+ 	 object and hence need to be visited during young-space garbage collection.  The
+ 	 list saves walking through all of code space to do so, as in typical circumstances
+ 	 there are no methods that refer to young objects.However, events like become:
+ 	 can potentially cause every method to refer to a new object (becomming true for
+ 	 example).  So there needs to be room on the list for as many methods as exist."
+ 	self assert: (youngReferrers <= limitAddress
+ 				and: [youngReferrers >= (limitAddress - (methodCount * BytesPerWord))]).
+ 	^limitAddress - (methodCount * BytesPerWord) >= mzFreeStart!
- 	^youngReferrers - BytesPerWord >= mzFreeStart!

Item was changed:
  ----- Method: CogMethodZone>>zoneEnd (in category 'accessing') -----
  zoneEnd
+ 	<inline: true>
  	^limitAddress!

Item was removed:
- ----- Method: CogMethodZone>>zoneLimit (in category 'accessing') -----
- zoneLimit
- 	<returnTypeC: #usqInt>
- 	^mzFreeStart!

Item was removed:
- ----- Method: CogMethodZone>>zoneLimit: (in category 'accessing') -----
- zoneLimit: zoneLimit
- 	<doNotGenerate>
- 	^mzFreeStart := zoneLimit!

Item was added:
+ ----- Method: CogVMSimulator>>commenceCogCompiledCodeCompaction (in category 'process primitive support') -----
+ commenceCogCompiledCodeCompaction
+ 	self halt.
+ 	^super commenceCogCompiledCodeCompaction!

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.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	outerReturn := coInterpreter stackTop.
+ 	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
- 	self assert: (outerReturn between: methodZoneBase and: methodZone zoneLimit).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[self assert: (targetMethod asInteger + cmEntryOffset = entryPoint
  					or: [targetMethod asInteger + cmDynSuperEntryOffset = entryPoint]).
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
  		 targetMethod asInteger + cmDynSuperEntryOffset = entryPoint ifTrue:
  			[^coInterpreter
  				ceDynamicSuperSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs]].
  	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: [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 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.
  		 (errorSelectorOrNil notNil
  		  or: [pic asInteger between: MaxNegativeErrorCode and: -1]) ifTrue:
  			["If for some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send.  If this is an error case continue as if this is an
  			  unlinked send to invoke the appropriate error behavior (MNU, cannot interpret et al)."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod]].
  	extent := backEnd
  				rewriteCallAt: outerReturn
  				target: pic asInteger + cmEntryOffset.
  	processor
  		flushICacheFrom: outerReturn - 1 - extent to: outerReturn - 1;
  		flushICacheFrom: pic asInteger to: pic asInteger + closedPICSize.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogMethodFromLinkedSend: pic
  		withReceiver: 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 isNil ifTrue:
  		[^constituents].
  	coInterpreter pushRemappableOop: constituents.
  	((label := coInterpreter stringForCString: 'CogCode') isNil
  	 or: [(value := coInterpreter cePositive32BitIntegerFor: 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 := coInterpreter stringForCString: (trampolineAddresses at: i)) isNil
  		 or: [(value := coInterpreter cePositive32BitIntegerFor: (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 := coInterpreter cePositive32BitIntegerFor: cogMethod asUnsignedInteger) isNil ifTrue:
  				[coInterpreter popRemappableOop.
  				 ^nil].
  			 coInterpreter
  				storePointerUnchecked: count + 1
  				ofObject: coInterpreter topRemappableOop
  				withValue: value.
  			 count := count + 2].
  		cogMethod := methodZone methodAfter: cogMethod].
  	((label := coInterpreter stringForCString: 'CCFree') isNil
+ 	 or: [(value := coInterpreter cePositive32BitIntegerFor: methodZone freeStart) isNil]) ifTrue:
- 	 or: [(value := coInterpreter cePositive32BitIntegerFor: methodZone zoneLimit) isNil]) ifTrue:
  		[coInterpreter popRemappableOop.
  		 ^nil].
  	coInterpreter
  		storePointerUnchecked: count ofObject: coInterpreter topRemappableOop withValue: label;
  		storePointerUnchecked: count + 1 ofObject: coInterpreter topRemappableOop withValue: value.
  	((label := coInterpreter stringForCString: 'CCEnd') isNil
  	 or: [(value := coInterpreter cePositive32BitIntegerFor: 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>>cogMethodDoesntLookKosher: (in category 'debugging') -----
  cogMethodDoesntLookKosher: cogMethod
  	"Check that the header fields onf a non-free method are consistent with
  	 the type. Answer 0 if it is ok, otherwise answer a code for the error."
  	<api>
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	((cogMethod blockSize bitAnd: BytesPerWord - 1) ~= 0
  	 or: [cogMethod blockSize < (self sizeof: CogMethod)
  	 or: [cogMethod blockSize >= 32768]]) ifTrue:
  		[^1].
  
  	cogMethod cmType = CMFree ifTrue: [^2].
  
  	cogMethod cmType = CMMethod ifTrue:
  		[(objectMemory isIntegerObject: cogMethod methodHeader) ifFalse:
  			[^11].
  		 (objectRepresentation couldBeObject: cogMethod methodObject) ifFalse:
  			[^12].
  		 (cogMethod stackCheckOffset > 0
  		 and: [cogMethod stackCheckOffset < cmNoCheckEntryOffset]) ifTrue:
  			[^13].
  		 ^0].
  
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[cogMethod blockSize ~= openPICSize ifTrue:
  			[^21].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^22].
  		
  		 "Check the nextOpenPIC link unless we're compacting"
  		 cogMethod objectHeader signedIntFromLong >= 0 ifTrue:
  			[(cogMethod methodObject ~= 0
  			 and: [cogMethod methodObject < methodZoneBase
+ 				   or: [cogMethod methodObject > (methodZone freeStart - openPICSize)
- 				   or: [cogMethod methodObject > (methodZone zoneLimit - openPICSize)
  				   or: [(cogMethod methodObject bitAnd: BytesPerWord - 1) ~= 0
  				   or: [(self cCoerceSimple: cogMethod methodObject
  							to: #'CogMethod *') cmType ~= CMOpenPIC]]]]) ifTrue:
  				[^23]].
  		 cogMethod stackCheckOffset ~= 0 ifTrue:
  			[^24].
  		 ^0].
  
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[cogMethod blockSize ~= closedPICSize ifTrue:
  			[^31].
  		 (cogMethod cPICNumCases between: 1 and: numPICCases) ifFalse:
  			[^32].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^33].
  		 cogMethod methodObject ~= 0 ifTrue:
  			[^34].
  		 ^0].
  
  	^9!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assert: self noCogMethodsMaximallyMarked.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
  	self freePICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  	self relocateMethodsPreCompaction.
  	methodZone compactCompiledCode: objectMemory nullHeaderForMachineCodeMethod.
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
+ 	processor flushICacheFrom: methodZoneBase to: methodZone freeStart!
- 	processor flushICacheFrom: methodZoneBase to: methodZone zoneLimit!

Item was changed:
  ----- Method: Cogit>>freePICsWithFreedTargets (in category 'compaction') -----
  freePICsWithFreedTargets
+ 	| cogMethod count |
- 	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
+ 	count := 0.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType = CMClosedPIC
  		 and: [self cPICHasFreedTargets: cogMethod]) ifTrue:
  			[cogMethod cmType: CMFree].
+ 		 cogMethod := methodZone methodAfter: cogMethod.
+ 		 count := count + 1].
+ 	self assert: count = methodZone numMethods!
- 		 cogMethod := methodZone methodAfter: cogMethod]!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #headerReference type: #'AbstractInstruction *'>
  	<returnTypeC: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: headerSize negated.
  	self computeMaximumSizes.
+ 	methodLabel concretizeAt: methodZone freeStart.
- 	methodLabel concretizeAt: (methodZone allocate: 0).
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: 0 start: methodLabel address + cmNoCheckEntryOffset.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithNopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: selector.
  	postCompileHook notNil ifTrue:
  		[self perform: postCompileHook with: method with: primInvokeLabel.
  		 postCompileHook := nil].
  	processor flushICacheFrom: startAddress to: startAddress + headerSize + codeSize.
  	^method!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function result savedFramePointer savedStackPointer savedArgumentCount rpc |
  	evaluable := simulatedTrampolines at: aProcessorSimulationTrap address.
  	function := evaluable
  					isBlock ifTrue: ['aBlock; probably some plugin primitive']
  					ifFalse: [evaluable selector].
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[coInterpreter assertValidExternalStackPointers].
  	(function beginsWith: 'ceShort') ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
  	aProcessorSimulationTrap type = #call
  		ifTrue:
  			[processor
  				simulateCallOf: aProcessorSimulationTrap address
  				nextpc: aProcessorSimulationTrap nextpc
  				memory: coInterpreter memory.
  			self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  		ifFalse:
  			[processor
  				simulateJumpCallOf: aProcessorSimulationTrap address
  				memory: coInterpreter memory.
  			 self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: coInterpreter memory)]
  				on: ReenterMachineCode
  				do: [:ex| ex return: ex returnValue].
  			
  	coInterpreter assertValidExternalStackPointers.
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter primFailCode = 0
  			ifTrue: [(#(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
  						primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  						primitiveExecuteMethodArgsArray primitiveExecuteMethod
  						primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  						primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
  							includes: function) ifFalse:
  						[self assert: savedFramePointer = coInterpreter framePointer.
  						 self assert: savedStackPointer + (savedArgumentCount * BytesPerWord)
  								= coInterpreter stackPointer]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
  		 rpc := processor retpcIn: coInterpreter memory.
+ 		 self assert: (rpc >= codeBase and: [rpc < methodZone freeStart]).
- 		 self assert: (rpc >= codeBase and: [rpc < methodZone zoneLimit]).
  		 processor
  			smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: BytesPerWord;
  			simulateReturnIn: coInterpreter memory].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
  			or: [#(nil continue continueNoReturn) includes: result]]]).
  	processor cResultRegister: (result
  							ifNil: [0]
  							ifNotNil: [result isInteger
  										ifTrue: [result]
  										ifFalse: [16rF00BA222]])
  
  	"coInterpreter cr.
  	 processor sp + 32 to: processor sp - 32 by: -4 do:
  		[:sp|
  		 sp = processor sp
  			ifTrue: [coInterpreter print: 'sp->'; tab]
  			ifFalse: [coInterpreter printHex: sp].
  		 coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was changed:
  ----- Method: Cogit>>isPCWithinMethodZone: (in category 'disassembly') -----
  isPCWithinMethodZone: address
  	<api>
  	<var: #address type: #'char *'>
  	^address asUnsignedInteger
  		between: methodZoneBase
+ 		and: methodZone freeStart!
- 		and: methodZone zoneLimit!

Item was changed:
  ----- Method: Cogit>>isSendReturnPC: (in category 'jit - api') -----
  isSendReturnPC: retpc
  	<api>
  	"Answer if the instruction preceeding retpc is a call instruction."
  	| target |
  	(backEnd isCallPreceedingReturnPC: retpc) ifFalse:
  		[^false].
  	target := backEnd callTargetFromReturnAddress: retpc.
  	^(target between: firstSend and: lastSend)
+ 	   or: [target between: methodZoneBase and: methodZone freeStart]!
- 	   or: [target between: methodZoneBase and: methodZone zoneLimit]!

Item was changed:
  ----- Method: Cogit>>linkSendAt:in:to:offset:receiver: (in category 'in-line cacheing') -----
  linkSendAt: callSiteReturnAddress in: sendingMethod to: targetMethod offset: theEntryOffset receiver: receiver
  	<api>
  	<var: #sendingMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| inlineCacheTag address extent |
  	self cppIf: NewspeakVM
  		ifTrue: [self assert: (theEntryOffset = cmEntryOffset
  							or: [theEntryOffset = cmNoCheckEntryOffset
  							or: [theEntryOffset = cmDynSuperEntryOffset]])]
  		ifFalse: [self assert: (theEntryOffset = cmEntryOffset
  							or: [theEntryOffset = cmNoCheckEntryOffset])].
+ 	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone freeStart).
- 	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone zoneLimit).
  	inlineCacheTag := theEntryOffset = cmNoCheckEntryOffset
  						ifTrue: [targetMethod selector "i.e. no change"]
  						ifFalse: [objectRepresentation inlineCacheTagForInstance: receiver].
  	(sendingMethod cmRefersToYoung not
  	 and: [(objectRepresentation inlineCacheTagIsYoung: inlineCacheTag)]) ifTrue:
  		[self assert: (methodZone occurrencesInYoungReferrers: sendingMethod) = 0.
  		 sendingMethod cmRefersToYoung: true.
  		 methodZone addToYoungReferrers: sendingMethod].
  	address := targetMethod asInteger + theEntryOffset.
  	extent := backEnd
  				rewriteInlineCacheAt: callSiteReturnAddress
  				tag: inlineCacheTag
  				target: address.
  	processor
  		flushICacheFrom: callSiteReturnAddress - 1 - extent
  		to: callSiteReturnAddress - 1!

Item was changed:
  ----- Method: Cogit>>lookupAddress: (in category 'disassembly') -----
  lookupAddress: address
  	<doNotGenerate>
  	| cogMethod |
+ 	address < methodZone freeStart ifTrue:
- 	address < methodZone zoneLimit ifTrue:
  		[address >= methodZoneBase
  			ifTrue:
  				[(cogMethod := methodZone methodFor: address) ~= 0 ifTrue:
  					[cogMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'.
  					 ^((cogMethod selector ~= objectMemory nilObject
  					    and: [objectRepresentation couldBeObject: cogMethod selector])
  						ifTrue: [coInterpreter stringOf: cogMethod selector]
  						ifFalse: [cogMethod asInteger hex]),
  					   '@', ((address - cogMethod asInteger) hex allButFirst: 3)]]
  			ifFalse:
  				[^address = (self codeEntryFor: address) ifTrue:
  					[self codeEntryNameFor: address]].
  		 ^nil].
  	(simulatedTrampolines includesKey: address) ifTrue:
  		[^self labelForSimulationAccessor: (simulatedTrampolines at: address)].
  	(simulatedVariableGetters includesKey: address) ifTrue:
  		[^self labelForSimulationAccessor: (simulatedVariableGetters at: address)].
  	^coInterpreter lookupAddress: address!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCode: (in category 'jit - api') -----
  mapObjectReferencesInMachineCode: gcMode
  	<api>
  	"Update all references to objects in machine code."
  	gcMode caseOf: {
  		[GCModeIncr]		-> [self mapObjectReferencesInMachineCodeForIncrementalGC].
  		[GCModeFull]		-> [self mapObjectReferencesInMachineCodeForFullGC].
+ 		[GCModeBecome]	-> [self mapObjectReferencesInMachineCodeForBecome] }.
+ 
+ 	(self asserta: methodZone freeStart <= methodZone youngReferrers) ifFalse:
+ 		[self error: 'youngReferrers list overflowed']!
- 		[GCModeBecome]	-> [self mapObjectReferencesInMachineCodeForBecome] }!

Item was changed:
  ----- Method: Cogit>>outputInstructionsForGeneratedRuntimeAt: (in category 'initialization') -----
  outputInstructionsForGeneratedRuntimeAt: startAddress
  	"Output instructions generated for one of the generated run-time routines, a trampoline, etc"
  	| size endAddress |
  	<inline: false>
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: startAddress.
  	endAddress := self outputInstructionsAt: startAddress.
  	self assert: startAddress + size = endAddress.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
+ 	self cCode: '' inSmalltalk: [methodZone freeStart: methodZoneBase].
- 	self cCode: '' inSmalltalk: [methodZone zoneLimit: methodZoneBase].
  	^startAddress!

Item was changed:
  ----- Method: Cogit>>simulateEnilopmart:numArgs: (in category 'simulation only') -----
  simulateEnilopmart: enilopmartAddress numArgs: n
  	<doNotGenerate>
  	"Enter Cog code, popping the class reg and receiver from the stack
  	 and then returning to the address beneath them.
  	 In the actual VM the enilopmart is a function pointer and so senders
  	 of this method end up calling the enilopmart to enter machine code.
  	 In simulation we either need to start simulating execution (if we're in
  	 the interpreter) or return to the simulation (if we're in the run-time
  	 called from machine code. We should also smash the register state
  	 since, being an abnormal entry, no saved registers will be restored."
  	self assert: (coInterpreter isOnRumpCStack: processor sp).
+ 	self assert: ((coInterpreter stackValue: n) between: guardPageSize and: methodZone freeStart - 1).
- 	self assert: ((coInterpreter stackValue: n) between: guardPageSize and: methodZone zoneLimit - 1).
  	(printInstructions or: [printRegisters]) ifTrue:
  		[coInterpreter printExternalHeadFrame].
  	processor
  		smashRegistersWithValuesFrom: 16r80000000 by: BytesPerWord;
  		simulateLeafCallOf: enilopmartAddress
  		nextpc: 16rBADF00D
  		memory: coInterpreter memory.
  	"If we're already simulating in the context of machine code then
  	 this will take us back to handleCallSimulationTrap:.  Otherwise
  	 start executing machine code in the simulator."
  	(ReenterMachineCode new returnValue: #continueNoReturn) signal.
  	self simulateCogCodeAt: enilopmartAddress.
  	"We should either longjmp back to the interpreter or
  	 stay in machine code so control should not reach here."
  	self assert: false!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>rewritePrimInvocationIn:to: (in category 'external primitive support') -----
  rewritePrimInvocationIn: cogMethod to: primFunctionPointer
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #primFunctionPointer declareC: #'void (*primFunctionPointer)(void)'>
  	| primIndex flags address extent |
  	self assert: cogMethod cmType = CMMethod.
  	primIndex := coInterpreter primitiveIndexOfMethodHeader: cogMethod methodHeader.
  	flags := coInterpreter primitivePropertyFlags: primIndex.
  	"See compileInterpreterPrimitive:"
  	(flags bitAnd: PrimCallMayCallBack) ~= 0
  		ifTrue:
  			[address := cogMethod asUnsignedInteger
+ 						+ (externalPrimJumpOffsets at: cogMethod cmNumArgs).
+ 			extent := backEnd
+ 						rewriteJumpLongAt: address
+ 						target: (self cCode: [primFunctionPointer asUnsignedInteger]
+ 									inSmalltalk: [self simulatedTrampolineFor: primFunctionPointer])]
- 					+ (externalPrimJumpOffsets at: cogMethod cmNumArgs).
- 			extent := backEnd rewriteJumpLongAt: address target: primFunctionPointer asInteger]
  		ifFalse:
  			[address := cogMethod asUnsignedInteger
+ 						+ (externalPrimCallOffsets at: cogMethod cmNumArgs).
+ 			extent := backEnd
+ 						rewriteCallAt: address
+ 						target: (self cCode: [primFunctionPointer asUnsignedInteger]
+ 									inSmalltalk: [self simulatedTrampolineFor: primFunctionPointer])].
- 				+ (externalPrimCallOffsets at: cogMethod cmNumArgs).
- 			extent := backEnd rewriteCallAt: address target: primFunctionPointer asInteger].
  	processor flushICacheFrom: address to: address + extent!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>handleWriteSimulationTrap: (in category 'simulation only') -----
  handleWriteSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| address end |
  	address := aProcessorSimulationTrap address.
+ 	(address >= methodZone freeStart
- 	(address >= methodZone zoneLimit
  	or: [address <= methodZoneBase]) ifTrue:
  		[^super handleWriteSimulationTrap: aProcessorSimulationTrap].
  
  	(counterMethodCache isNil
  	 or: [address < counterMethodCache
  	 or: [counterMethodCache address + counterMethodCache blockSize < address]]) ifTrue:
  		[counterMethodCache := methodZone methodFor: address].
  	end := counterMethodCache address + counterMethodCache blockSize.
  	self assert: (address
  					between: end - (CounterBytes * counterMethodCache numCounters)
  					and: end).
  	objectMemory longAt: address put: (processor perform: aProcessorSimulationTrap registerAccessor).
  	processor pc: aProcessorSimulationTrap nextpc!

Item was added:
+ ----- Method: StackInterpreter>>isNullExternalPrimitiveCall: (in category 'compiled methods') -----
+ isNullExternalPrimitiveCall: aMethodObj
+ 	"Answer if the method is an external primtiive call (prim 117) with a null external primtiive.
+ 	 This is just for an assert in the CoInterpreter."
+ 	| lit |
+ 	((self primitiveIndexOf: aMethodObj) = 117
+ 	and: [(self literalCountOf: aMethodObj) > 0]) ifFalse:
+ 		[^false].
+ 
+ 	lit := self literal: 0 ofMethod: aMethodObj.
+ 	^(objectMemory isArray: lit)
+ 	  and: [(objectMemory lengthOf: lit) = 4
+ 	  and: [(objectMemory fetchPointer: 3 ofObject: lit) = ConstZero]]!

Item was removed:
- ----- Method: TMethod>>extractTypeFor:fromDeclaration: (in category 'utilities') -----
- extractTypeFor: aVariable fromDeclaration: aVariableDeclaration
- 	"Eliminate inessentials from aVariableDeclaration to answer a C type without the variable,
- 	 or initializations etc"
- 	| decl fpIndex |
- 	decl := aVariableDeclaration.
- 	(decl beginsWith: 'static') ifTrue:
- 		[decl := decl allButFirst: 6].
- 	(decl indexOf: $= ifAbsent: []) ifNotNil:
- 		[:index| decl := decl copyFrom: 1 to: index - 1].
- 	decl := decl copyReplaceAll: aVariable with: '' tokenish: [:ch| ch = $_ or: [ch isAlphaNumeric]].
- 	(fpIndex := decl indexOfSubCollection: '(*') > 0 ifTrue:
- 		[decl := decl copyReplaceFrom: (decl indexOf: $( startingAt: fpIndex + 1)
- 					to: (decl indexOf: $) startingAt: fpIndex + 1)
- 					with: ''].
- 	^decl withBlanksTrimmed!

Item was changed:
  ----- Method: TMethod>>inlineSend:directReturn:exitVar:in: (in category 'inlining') -----
  inlineSend: aSendNode directReturn: directReturn exitVar: exitVar in: aCodeGen
  	"Answer a collection of statements to replace the given send.  directReturn indicates
  	 that the send is the expression in a return statement, so returns can be left in the
  	 body of the inlined method. If exitVar is nil, the value returned by the send is not
  	 used; thus, returns need not assign to the output variable.
  
  	 Types are propagated to as-yet-untyped variables when inlining a send that is assigned,
  	 otherwise the assignee variable type must match the return type of the inlinee.  Return
  	 types are not propagated."
  
  	| sel meth exitLabel inlineStmts label exitType |
  	sel := aSendNode selector.
  	meth := aCodeGen methodNamed: sel.
  	meth args size = aSendNode args size ifFalse:
  		[^nil].
  	meth args with: aSendNode args do:
  		[:formal :actual|
  		(actual isVariable
  		and: [(aCodeGen
+ 				variableOfType: (self typeFor: formal using: aCodeGen)
- 				variableOfType: (self typeFor: formal)
  				acceptsValueOfType: (self typeFor: actual name in: aCodeGen)) not]) ifTrue:
  			[aCodeGen logger
  				nextPutAll:
  					'type mismatch for formal ', formal, ' and actual ', actual name,
  					' when inlining ', sel, ' in ', selector, '. Use a cast.';
  				cr; flush]]. 
  	meth := meth copy.
  
  	"Propagate the return type of an inlined method"
  	(directReturn or:[exitVar notNil]) ifTrue:[
  		exitType := directReturn 
  			ifTrue:[returnType] 
  			ifFalse:[(self typeFor: exitVar in: aCodeGen) ifNil:[#sqInt]].
  		(exitType = #void or:[exitType = meth returnType]) 
  			ifFalse:[meth propagateReturnIn: aCodeGen]].
  
  	meth renameVarsForInliningInto: self except: #() in: aCodeGen.
  	meth renameLabelsForInliningInto: self.
  	self addVarsDeclarationsAndLabelsOf: meth except: #().
  	meth hasReturn ifTrue:[
  		directReturn ifFalse:[
  			exitLabel := self unusedLabelForInliningInto: self.
  			(meth exitVar: exitVar label: exitLabel) "is label used?"
  				ifTrue: [ labels add: exitLabel ]
  				ifFalse: [ exitLabel := nil ]]].
  	(inlineStmts := OrderedCollection new: 100)
  		add: (label := TLabeledCommentNode new setComment: 'begin ', sel);
  		addAll: (self argAssignmentsFor: meth args: aSendNode args in: aCodeGen);
  		addAll: meth statements.  "method body"
  	"Vile hacks to prevent too many labels.  If the C compiler inlines functions it can duplicate
  	 labels and cause compilation to fail.  The second statement prevents us creating labels in
  	 anything other than the interpreter.  If we add labels to small functions that may be inlined
  	 by the C compiler then the label can be duplicated by the C compiler and cause the assembler
  	 to fail.  eem 9/20/2008 12:29"
  	(aCodeGen wantsLabels
  	 and: [meth asmLabel
  	 and: [meth mustAsmLabel or: [meth hasMoreSendsThan: 20]]]) ifTrue:
  		[label asmLabel: sel].
  	(directReturn
  	 and: [meth endsWithReturn not]) ifTrue:
  		[inlineStmts add:
  			(TReturnNode new setExpression: (TVariableNode new setName: 'nil'))].
  	exitLabel ~= nil ifTrue:
  		[inlineStmts add:
  			(TLabeledCommentNode new setLabel:
  				exitLabel comment: 'end ', meth selector)].
  	^inlineStmts!

Item was changed:
  ----- Method: TMethod>>propagateReturnIn: (in category 'inlining support') -----
  propagateReturnIn: aCodeGen
  	"Propagate the return type to all return nodes"
  	| map |
  	map := IdentityDictionary new.
  	parseTree nodesDo:[:node|
  		node isReturn ifTrue:[
  			map at: node expression put: (TSendNode new
  				setSelector: #cCoerce:to:
  				receiver: (TVariableNode new setName: 'self')
  				arguments: {node expression.
  							TConstantNode new "The following is necessary for functions returning functions, which have problematic syntax"
+ 								setValue: (aCodeGen
+ 											extractTypeFor: (aCodeGen cFunctionNameFor: self selector)
- 								setValue: (self extractTypeFor: (aCodeGen cFunctionNameFor: self selector)
  											fromDeclaration: returnType) })]].
+ 	self replaceNodesIn: map!
- 	self replaceNodesIn: map.!

Item was removed:
- ----- Method: TMethod>>typeFor: (in category 'utilities') -----
- typeFor: aVariable
- 	"Answer the type for aVariable.  Answer nil for variables without types.  nil for
- 	 typelessness is required by the type propagation logic in inlineSend:directReturn:exitVar:in:."
- 	^self extractTypeFor: aVariable fromDeclaration: (declarations at: aVariable asString ifAbsent: [^nil])!

Item was changed:
  ----- Method: TMethod>>typeFor:in: (in category 'utilities') -----
  typeFor: aVariable in: aCodeGen
  	"Answer the type for aVariable, deferring to aCodeGen (which defers to the vmClass)
  	 if no type is found and the variable is global (not an arg or a local).  Expect the
  	 cCodeGen to answer nil for variables without types. nil for typelessness is required
  	 by the type propagation logic in inlineSend:directReturn:exitVar:in:."
  	^(declarations
  			at: aVariable asString
  			ifAbsent: [((locals includes: aVariable) or: [args includes: aVariable]) ifFalse:
  						[aCodeGen typeOfVariable: aVariable]]) ifNotNil:
  		[:decl|
+ 		aCodeGen extractTypeFor: aVariable fromDeclaration: decl]!
- 		self extractTypeFor: aVariable fromDeclaration: decl]!

Item was added:
+ ----- Method: TMethod>>typeFor:using: (in category 'utilities') -----
+ typeFor: aVariable using: aCCodeGen
+ 	"Answer the type for aVariable.  Answer nil for variables without types.  nil for
+ 	 typelessness is required by the type propagation logic in inlineSend:directReturn:exitVar:in:."
+ 	^aCCodeGen extractTypeFor: aVariable fromDeclaration: (declarations at: aVariable asString ifAbsent: [^nil])!

Item was added:
+ ----- Method: TParseNode>>detect: (in category 'enumerating') -----
+ detect: aBlock
+ 	^self detect: aBlock ifNone: [self error: 'Node is not in the tree']!

Item was added:
+ ----- Method: TParseNode>>detect:ifNone: (in category 'enumerating') -----
+ detect: aBlock ifNone: defaultBlock
+ 	self nodesDo: [:n| (aBlock value: n) ifTrue: [^n]].
+ 	^defaultBlock value!

Item was changed:
  ----- Method: VMStructType class>>structTargetKindForDeclaration: (in category 'translation') -----
  structTargetKindForDeclaration: decl
  	StructTypeNameCache ifNil:
  		[StructTypeNameCache := Set new.
  		 self allSubclassesDo:
  			[:sc| StructTypeNameCache add: sc name; add: sc structTypeName ]].
  	^(decl notNil
+ 	   and: [(StructTypeNameCache includes: decl)
+ 			or: [StructTypeNameCache anySatisfy:
+ 					[:structType|
+ 					(decl beginsWith: structType)
+ 					and: [(decl indexOf: $* ifAbsent: [decl indexOf: Character space]) > structType size]]]]) ifTrue:
- 	   and: [StructTypeNameCache anySatisfy:
- 			[:structType|
- 			(decl beginsWith: structType)
- 			and: [(decl indexOf: $* ifAbsent: [decl indexOf: Character space]) > structType size]]]) ifTrue:
  		[(decl indexOf: $*) > 0
  			ifTrue: [#pointer]
  			ifFalse: [#struct]]!



More information about the Vm-dev mailing list