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

commits at source.squeak.org commits at source.squeak.org
Thu May 21 04:58:14 UTC 2015


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

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

Name: VMMaker.oscog-eem.1317
Author: eem
Time: 20 May 2015, 9:56:04.05 pm
UUID: a7e082b5-1ad8-42ef-84cc-0079605c8440
Ancestors: VMMaker.oscog-eem.1316

Cogit:
Fix the performance regression on x86 in r3308
VMMaker.oscog-eem.1178 through the use of the XCHG
instruction in CogIA32Compiler>>genPushRegisterArgsForNumArgs:.
Since SendNumArgsReg is not live with small arity sends
it can be used instead of TempReg.

Replace uses of the magic constant 2 with
NumSendTrampolines - 2 (actually <= 2 =>
< (NumSendTrampolines - 1)) where appropriate. Hence
NumSendTrampolines moved to CogCompilationConstants.

Fix bug on ARM with pc-relative addressing. pc-relative
addressing can only be used within a method because of relocation.
The old code would use pc-relative addressing to access
trampolines for methods close to the trampolines and then
not for methods further away, causing changes in the code
generated by compileInterpreterPrimitive:.

To support this, rationalize the PIC compilation code, being sure
to initialize and concretize methodLabel at the start of each PIC.
Don't bother to pass PIC size as a parameter given we have
PIC-specific header-filling routines now.

Spur:
Firm up the checkTraversableSortedFreeList assert routine to
check that the list is traversable from lastFreeChunk, not just firstFreeChunk.

Slang:
Make promoteArithmeticTypes:and: obey C99's promotion rules
more closely in an effort to generate more stable sources.
Types were flipping between sqInt & usqInt for variables that
were assigned both types, so that one generation would produce
one type and a subsequent one another (Set/Dictionary hashing?).

Simulation/In-image Compilation:
Fix varBaseAddress calculations for in-image compilation so that
it jives with real compilation.

Allow setting of recordPrimTrace through initializationOptions.

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

Item was changed:
  ----- Method: CCodeGenerator>>promoteArithmeticTypes:and: (in category 'type inference') -----
  promoteArithmeticTypes: firstType and: secondType
+ 	"Answer the return type for an arithmetic send.  This is so that the inliner can still inline
+ 	 simple expressions.  Deal with pointer arithmetic, floating point arithmetic and promotion."
+ 	| firstSize secondSize |
- 	"Answer the return type for an arithmetic sendThis is so that the inliner can still
- 	 inline simple expressions.  Deal with pointer arithmetic, floating point arithmetic
- 	 and promotion."
  	((#(#double float) includes: firstType)
  	 or: [#(#double float) includes: secondType]) ifTrue:
  		[^(firstType = #float and: [secondType = #float])
  			ifTrue: [#float]
  			ifFalse: [#double]].
  	"deal with unknowns, answering nil."
  	(firstType isNil or: [secondType isNil]) ifTrue:
  		[^nil].
+ 	"Deal with promotion; answer the longest type, defaulting to the recever if they're the same.
+ 	 See e.g. section 6.3.1.8 Usual arithmetic conversions, from the C99 standard:
+ 		Otherwise, the integer promotions are performed on both operands
+ 		Then the following rules are applied to the promoted operands:
+ 
+ 			If both operands have the same type, then no further conversion is needed.
+ 
+ 			Otherwise, if both operands have signed integer types or both have unsigned integer
+ 			types, the operand with the type of lesser integer conversion rank is converted to the
+ 			type of the operand with greater rank.
+ 
+ 			Otherwise, if the operand that has unsigned integer type has rank greater or equal to
+ 			the rank of the type of the other operand, then the operand with signed integer type
+ 			is converted to the type of the operand with unsigned integer type.
+ 
+ 			Otherwise, if the type of the operand with signed integer type can represent all of the
+ 			values of the type of the operand with unsigned integer type, then the operand with
+ 			unsigned integer type is converted to the type of the operand with signed integer type.
+ 
+ 			Otherwise, both operands are converted to the unsigned integer type corresponding to
+ 			the type of the operand with signed integer type.
+ 
+ 	It is important to choose deterministically to get stable source generation.  So if the types have
+ 	the same size but differ in signedness we choose the unsigned type, which is in partial agreement
+ 	with the above"
+ 	^(firstSize := self sizeOfIntegralCType: firstType) = (secondSize := self sizeOfIntegralCType: secondType)
+ 		ifTrue:
+ 			[(firstType first = $u)
+ 				ifTrue: [firstType]
+ 				ifFalse: [(secondType first = $u) ifTrue: [secondType] ifFalse: [firstType]]]
+ 		ifFalse:
+ 			[firstSize > secondSize ifTrue: [firstType] ifFalse: [secondType]]!
- 	"deal with promotion; answer the longest type, defaulting to the recever if they're the same"
- 	^(self sizeOfIntegralCType: firstType) >= (self sizeOfIntegralCType: secondType)
- 		ifTrue: [firstType]
- 		ifFalse: [secondType]!

Item was changed:
  ----- Method: CoInterpreter>>varBaseAddress (in category 'cog jit support') -----
  varBaseAddress
  	<api>
  	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: stackPointer) asUnsignedInteger - 16r42]
+ 		inSmalltalk: [cogit fakeVarBaseAddress]!
- 	^(self addressOf: stackPointer) asUnsignedInteger - 16r42!

Item was changed:
  ----- Method: CogARMCompiler>>loadCwInto: (in category 'generate machine code - support') -----
  loadCwInto: destReg
  	"Load the operand into the destination register, answering
  	 the size of the instructions generated to do so."
  	| operand distance |
  	operand := operands at: 0.
  	"First try and encode as a pc-relative reference..."
+ 	(cogit addressIsInCurrentCompilation: operand) ifTrue:
+ 		[distance := operand - (address + 8).
- 	(cogit addressIsInCodeZone: operand) ifTrue:
- 		[distance := operand  - (address + 8).
  		 self rotateable8bitImmediate: distance
  		 	ifTrue: [ :rot :immediate |
  		 		self machineCodeAt: 0 put: (self add: destReg rn: PC imm: immediate ror: rot).
  		 		^4]
  		 	ifFalse:
  		 		[self rotateable8bitImmediate: distance negated
  		 			ifTrue: [ :rot :immediate |
  		 				self machineCodeAt: 0 put: (self sub: destReg rn: PC imm: immediate ror: rot).
  		 				^4]
  					ifFalse: []]].
  	"If this fails, use the conventional and painfully long 4 instruction sequence."
  	^self at: 0 moveCw: operand intoR: destReg!

Item was changed:
  VMStructType subclass: #CogAbstractInstruction
  	instanceVariableNames: 'opcode machineCodeSize maxSize machineCode operands address dependent cogit objectMemory bcpc'
  	classVariableNames: 'NumOperands'
+ 	poolDictionaries: 'CogCompilationConstants CogRTLOpcodes'
- 	poolDictionaries: 'CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !CogAbstractInstruction commentStamp: 'eem 4/21/2015 09:12' prior: 0!
  I am an abstract instruction generated by the Cogit.  I am subsequently concretized to machine code for the current processor.  A sequence of concretized CogAbstractInstructions are concatenated to form the code for a CogMethod.  I am an abstract class.  My concrete subclasses concretize to the machine code of a specific processor.
  
  Instance Variables
  	address:			<Integer>
  	bcpc:				<Integer>
  	cogit:				<Cogit>
  	dependent:			<AbstractInstruction|nil>
  	machineCode:		<CArray on: (ByteArray|Array)>
  	machineCodeSize:	<Integer>
  	maxSize:			<Integer>
  	objectMemory:		<NewCoObjectMemory|SpurCoMemoryManager etc>
  	opcode:			<Integer>
  	operands:			<CArray on: Array>
  
  address
  	- the address at which the instruction will be generated
  
  bcpc
  	- the bytecode pc for which the instruction was generated; simulation only
  
  cogit
  	- the Cogit assembling the receiver; simulation only
  
  dependent
  	- a reference to another instruction which depends on the receiver, if any; in C this is a pointer
  
  machineCode
  	- the array of machine code the receiver generates when concretized
  
  machineCodeSize
  	- the size of machineCode in bytes
  
  maxSize
  	- the maximum size of machine code that the current instruction will generate, in bytes
  
  objectMemory
  	- the memory manager for the system; simulation only
  
  opcode
  	- the opcode for the receiver which defines which abstract opcode it represents; see CogRTLOpcodes class>>initialize and CogAbstractInstruction subclass initialize methods
  
  operands
  	- the array containing any operands the instruction may have; the opcode defines implicitly how many operands are consdered!

Item was changed:
  SharedPool subclass: #CogCompilationConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BadRegisterSet NumSendTrampolines SSBaseOffset SSConstant SSIllegal SSRegister SSSpill'
- 	classVariableNames: 'BadRegisterSet SSBaseOffset SSConstant SSIllegal SSRegister SSSpill'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!

Item was changed:
  ----- Method: CogIA32Compiler>>genPushRegisterArgsForNumArgs: (in category 'smalltalk calling convention') -----
  genPushRegisterArgsForNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs.  This
+ 	 won't be as clumsy on a RISC.  But putting the receiver and args above the return address
+ 	 means the CoInterpreter has a single machine-code frame format which saves us a lot of work.
+ 	 N.B. Take great care to /not/ smash TempReg, which is used in directed send marshalling.
+ 	 We could use XCHG to swap the ReceiverResultReg and top-of-stack return address, pushing the
+ 	 the ret pc (now in ReceiverResultReg) later, but XCHG is very slow.  We can use SendNumArgsReg
+ 	 because it is only live in sends of arity >= (NumSendTrampolines - 1)."
+ 	self assert: cogit numRegArgs < (NumSendTrampolines - 1).
- 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
- 	"This won't be as clumsy on a RISC.  But putting the receiver and
- 	 args above the return address means the CoInterpreter has a
- 	 single machine-code frame format which saves us a lot of work."
  	numArgs <= cogit numRegArgs ifTrue:
  		[self assert: cogit numRegArgs <= 2.
+ 		 false "these two variants show the same performance on Intel Core i7, but the second one may be shorter."
+ 			ifTrue:
+ 				[cogit MoveMw: 0 r: SPReg R: SendNumArgsReg. "Save return pc"
+ 				 numArgs > 0 ifTrue:
+ 					[cogit PushR: Arg0Reg.
+ 					 numArgs > 1 ifTrue:
+ 						[cogit PushR: Arg1Reg]].
+ 				 cogit PushR: SendNumArgsReg.
+ 				 cogit MoveR: ReceiverResultReg Mw: objectMemory wordSize * (1 + numArgs) r: SPReg]
+ 			ifFalse:
+ 				["a.k.a.
+ 					cogit gen: XCHGMwrR operand: 0 operand: SPReg operand: ReceiverResultReg.
+ 				  but XCHG is slow."
+ 				 cogit MoveMw: 0 r: SPReg R: SendNumArgsReg. "Save return pc"
+ 				 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
+ 				 numArgs > 0 ifTrue:
+ 					[cogit PushR: Arg0Reg.
+ 					 numArgs > 1 ifTrue:
+ 						[cogit PushR: Arg1Reg]].
+ 				 cogit PushR: SendNumArgsReg]] "Restore return address"!
- 		 "N.B. Take great care to /not/ smash TempReg, which is used in directed send marshalling."
- 		 "Swap the return address with ReceiverResultReg"
- 		 cogit gen: XCHGMwrR operand: 0 operand: SPReg operand: ReceiverResultReg. "Save return address; replace with receiver"
- 		 numArgs > 0 ifTrue:
- 			[cogit PushR: Arg0Reg.
- 			 numArgs > 1 ifTrue:
- 				[cogit PushR: Arg1Reg]].
- 		cogit PushR: ReceiverResultReg.
- 		"Reload ReceiverResultReg"
- 		cogit MoveMw: numArgs + 1 * objectMemory wordSize r: SPReg R: ReceiverResultReg]!

Item was changed:
  CogClass subclass: #Cogit
  	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs implicitReceiverSendTrampolines nsSendCacheSurrogateClass tempOop'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumTrampolines ProcessorClass'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSendTrampolines NumTrampolines ProcessorClass'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 4/6/2015 15:56' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

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

Item was changed:
  ----- Method: Cogit>>codeRangesFor: (in category 'disassembly') -----
  codeRangesFor: cogMethod
  	"Answer a sequence of ranges of code for the main method and all of the blocks in a CogMethod.
  	 N.B.  These are in order of block dispatch, _not_ necessarily address order in the method."
  	<doNotGenerate>
  	| pc end blockEntry starts |
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[end := (self addressOfEndOfCase: cogMethod cPICNumCases - 1 inCPIC: cogMethod) + cPICEndSize.
  		 ^{ CogCodeRange
  				from: cogMethod asInteger + (self sizeof: CogMethod)
  				to: end
  				cogMethod: cogMethod
  				startpc: nil }].
  	end := (self mapEndFor: cogMethod) - 1.
  	cogMethod blockEntryOffset = 0 ifTrue:
  		[^{ CogCodeRange
  				from: cogMethod asInteger + (self sizeof: CogMethod)
  				to: end
  				cogMethod: cogMethod
+ 				startpc: (cogMethod cmType ~= CMOpenPIC ifTrue:
+ 							[coInterpreter startPCOfMethodHeader: cogMethod methodHeader]) }].
- 				startpc: (coInterpreter startPCOfMethodHeader: cogMethod methodHeader) }].
  	pc := blockEntry := cogMethod blockEntryOffset + cogMethod asInteger.
  	starts := OrderedCollection with: cogMethod.
  	[pc < end] whileTrue:
  		[| targetpc |
  		 targetpc := blockEntry.
  		 (backEnd isJumpAt: pc) ifTrue:
  			[targetpc := backEnd jumpTargetPCAt: pc.
  			 targetpc < blockEntry ifTrue:
  				[starts add: (self cCoerceSimple: targetpc - (self sizeof: CogBlockMethod) to: #'CogBlockMethod *')]].
  		 pc := pc + (backEnd instructionSizeAt: pc)].
  	starts := starts asSortedCollection.
  	^(1 to: starts size + 1) collect:
  		[:i| | cogSubMethod nextpc |
  		i <= starts size
  			ifTrue:
  				[cogSubMethod := starts at: i.
  				 nextpc := i < starts size ifTrue: [(starts at: i + 1) address] ifFalse: [blockEntry].
  				 CogCodeRange
  					from: cogSubMethod address + (self sizeof: cogSubMethod)
  					to: nextpc - 1
  					cogMethod: cogSubMethod
  					startpc: (i = 1
  								ifTrue: [coInterpreter startPCOfMethodHeader: cogMethod methodHeader]
  								ifFalse: [cogSubMethod startpc])]
  			ifFalse:
  				[CogCodeRange
  					from: blockEntry
  					to: end]]!

Item was changed:
  ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
  cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
  	<api>
  	"Attempt to create a one-case PIC for an MNU.
  	 The tag for the case is at the send site and so doesn't need to be generated."
  	<returnTypeC: #'CogMethod *'>
+ 	| startAddress size end |
- 	| startAddress headerSize size end |
  	((objectMemory isYoung: selector)
  	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  		[^0].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: true.
  	self assert: endCPICCase0 notNil.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[coInterpreter callForCogCompiledCodeCompaction.
  		 ^0].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	self compileMNUCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs.
  	self computeMaximumSizes.
+ 	methodLabel concretizeAt: startAddress.
+ 	size := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
+ 	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
- 	headerSize := self sizeof: CogMethod.
- 	size := self generateInstructionsAt: startAddress + headerSize.
- 	end := self outputInstructionsAt: startAddress + headerSize.
  	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
  	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
  								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 		size: closedPICSize
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogOpenPICSelector:numArgs: (in category 'in-line cacheing') -----
  cogOpenPICSelector: selector numArgs: numArgs
  	"Create an Open PIC.  Temporarily create a direct call of ceSendFromOpenPIC:.
  	 Should become a probe of the first-level method lookup cache followed by a
  	 call of ceSendFromOpenPIC: if the probe fails."
  	<returnTypeC: #'CogMethod *'>
+ 	| startAddress codeSize mapSize end |
- 	| startAddress headerSize codeSize mapSize end |
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: false.
  	startAddress := methodZone allocate: openPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 100 bytecodes: 0.
  	self compileOpenPIC: selector numArgs: numArgs.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: startAddress.
+ 	codeSize := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
- 	headerSize := self sizeof: CogMethod.
- 	codeSize := self generateInstructionsAt: startAddress + headerSize.
  	mapSize := self generateMapAt: startAddress + openPICSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self assert: entry address - startAddress = cmEntryOffset.
+ 	self assert: (methodZone roundUpLength: (self sizeof: CogMethod) + codeSize) + (methodZone roundUpLength: mapSize) <= openPICSize.
+ 	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
- 	self assert: headerSize + codeSize + mapSize <= openPICSize.
- 	end := self outputInstructionsAt: startAddress + headerSize.
  	^self
  		fillInOPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 		size: openPICSize
  		numArgs: numArgs
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create 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; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
+ 	| startAddress size end |
- 	| startAddress headerSize size end |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: isMNUCase.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	self compileCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs.
  	self computeMaximumSizes.
+ 	methodLabel concretizeAt: startAddress.
+ 	size := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
+ 	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
- 	headerSize := self sizeof: CogMethod.
- 	size := self generateInstructionsAt: startAddress + headerSize.
- 	end := self outputInstructionsAt: startAddress + headerSize.
  	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
  	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
  								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: endCPICCase0 address = (startAddress + firstCPICCaseOffset).
  	self assert: endCPICCase1 address = (startAddress + firstCPICCaseOffset + cPICCaseSize).
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 		size: closedPICSize
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector !

Item was added:
+ ----- Method: Cogit>>fakeVarBaseAddress (in category 'accessing') -----
+ fakeVarBaseAddress
+ 	"We expect simulatedAddresses to have around 40 entries.  48 is hopefully a good maximum."
+ 	<doNotGenerate>
+ 	^self fakeAddressFor: nil index: 48!

Item was added:
+ ----- Method: Cogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
+ fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
+ 	<returnTypeC: #'CogMethod *'>
+ 	<var: #pic type: #'CogMethod *'>
+ 	<inline: true>
+ 	self assert: (objectMemory isYoung: selector) not.
+ 	pic cmType: CMClosedPIC.
+ 	pic objectHeader: 0.
+ 	pic blockSize: closedPICSize.
+ 	pic methodObject: 0.
+ 	pic methodHeader: 0.
+ 	pic selector: selector.
+ 	pic cmNumArgs: numArgs.
+ 	pic cmRefersToYoung: false.
+ 	pic cmUsageCount: self initialClosedPICUsageCount.
+ 	pic cpicHasMNUCase: hasMNUCase.
+ 	pic cPICNumCases: numCases.
+ 	pic blockEntryOffset: 0.
+ 	self assert: pic cmType = CMClosedPIC.
+ 	self assert: pic selector = selector.
+ 	self assert: pic cmNumArgs = numArgs.
+ 	self assert: pic cPICNumCases = numCases.
+ 	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
+ 	self assert: closedPICSize = (methodZone roundUpLength: closedPICSize).
+ 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
+ 	^pic!

Item was removed:
- ----- Method: Cogit>>fillInCPICHeader:size:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
- fillInCPICHeader: pic size: size numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
- 	<returnTypeC: #'CogMethod *'>
- 	<var: #pic type: #'CogMethod *'>
- 	self assert: (objectMemory isYoung: selector) not.
- 	pic cmType: CMClosedPIC.
- 	pic objectHeader: 0.
- 	pic blockSize: size.
- 	pic methodObject: 0.
- 	pic methodHeader: 0.
- 	pic selector: selector.
- 	pic cmNumArgs: numArgs.
- 	pic cmRefersToYoung: false.
- 	pic cmUsageCount: self initialClosedPICUsageCount.
- 	pic cpicHasMNUCase: hasMNUCase.
- 	pic cPICNumCases: numCases.
- 	pic blockEntryOffset: 0.
- 	self assert: pic cmType = CMClosedPIC.
- 	self assert: pic selector = selector.
- 	self assert: pic cmNumArgs = numArgs.
- 	self assert: pic cPICNumCases = numCases.
- 	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
- 	self assert: size = (methodZone roundUpLength: size).
- 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + size.
- 	^pic!

Item was added:
+ ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
+ fillInOPICHeader: pic numArgs: numArgs selector: selector
+ 	<returnTypeC: #'CogMethod *'>
+ 	<var: #pic type: #'CogMethod *'>
+ 	<inline: true>
+ 	pic cmType: CMOpenPIC.
+ 	pic objectHeader: 0.
+ 	pic blockSize: openPICSize.
+ 	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
+ 	methodZone addToOpenPICList: pic.
+ 	pic methodHeader: 0.
+ 	pic selector: selector.
+ 	pic cmNumArgs: numArgs.
+ 	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
+ 		[methodZone addToYoungReferrers: pic].
+ 	pic cmUsageCount: self initialOpenPICUsageCount.
+ 	pic cpicHasMNUCase: false.
+ 	pic cPICNumCases: 0.
+ 	pic blockEntryOffset: 0.
+ 	self assert: pic cmType = CMOpenPIC.
+ 	self assert: pic selector = selector.
+ 	self assert: pic cmNumArgs = numArgs.
+ 	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
+ 	self assert: openPICSize = (methodZone roundUpLength: openPICSize).
+ 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + openPICSize.
+ 	^pic!

Item was removed:
- ----- Method: Cogit>>fillInOPICHeader:size:numArgs:selector: (in category 'generate machine code') -----
- fillInOPICHeader: pic size: size numArgs: numArgs selector: selector
- 	<returnTypeC: #'CogMethod *'>
- 	<var: #pic type: #'CogMethod *'>
- 	pic cmType: CMOpenPIC.
- 	pic objectHeader: 0.
- 	pic blockSize: size.
- 	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
- 	methodZone addToOpenPICList: pic.
- 	pic methodHeader: 0.
- 	pic selector: selector.
- 	pic cmNumArgs: numArgs.
- 	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
- 		[methodZone addToYoungReferrers: pic].
- 	pic cmUsageCount: self initialOpenPICUsageCount.
- 	pic cpicHasMNUCase: false.
- 	pic cPICNumCases: 0.
- 	pic blockEntryOffset: 0.
- 	self assert: pic cmType = CMOpenPIC.
- 	self assert: pic selector = selector.
- 	self assert: pic cmNumArgs = numArgs.
- 	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
- 	self assert: size = (methodZone roundUpLength: size).
- 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + size.
- 	^pic!

Item was changed:
  ----- Method: Cogit>>generateClosedPICPrototype (in category 'initialization') -----
  generateClosedPICPrototype
  	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
- 	| headerSize |
  	numPICCases := 6.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	self compileClosedPICPrototype.
  	self computeMaximumSizes.
+ 	methodLabel concretizeAt: methodZoneBase.
+ 	closedPICSize := (self sizeof: CogMethod) + (self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod)).
- 	headerSize := self sizeof: CogMethod.
- 	closedPICSize := headerSize + (self generateInstructionsAt: methodZoneBase + headerSize).
  	firstCPICCaseOffset := endCPICCase0 address - methodZoneBase.
  	cPICCaseSize := endCPICCase1 address - endCPICCase0 address.
  	cPICEndSize := closedPICSize - (numPICCases - 1 * cPICCaseSize + firstCPICCaseOffset).
  	closedPICSize := methodZone roundUpLength: closedPICSize
  	"self cCode: ''
  		inSmalltalk:
  			[| end |
  			 end := self outputInstructionsAt: methodZoneBase + headerSize.
  			 self disassembleFrom: methodZoneBase + headerSize to: end - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>generateOpenPICPrototype (in category 'initialization') -----
  generateOpenPICPrototype
  	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
+ 	| codeSize mapSize |
- 	| headerSize codeSize mapSize |
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 100 bytecodes: 0.
+ 	methodLabel
+ 		address: methodZoneBase;
+ 		dependent: nil.
+ 	"Need a real selector here so that the map accomodates the annotations for the selector.
+ 	 Use self numRegArgs to generate the longest possible code sequence due to
+ 	 genPushRegisterArgsForNumArgs:"
- 	"Ned a real selector here so that the map accomodates the annotations for the selector."
  	self compileOpenPIC: (coInterpreter specialSelector: 0) numArgs: self numRegArgs.
  	self computeMaximumSizes.
- 	headerSize := self sizeof: CogMethod.
  	methodLabel concretizeAt: methodZoneBase.
+ 	codeSize := self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
- 	codeSize := self generateInstructionsAt: methodZoneBase + headerSize.
  	mapSize := self generateMapAt: nil start: methodZoneBase + cmNoCheckEntryOffset.
+ 	openPICSize := (methodZone roundUpLength: (self sizeof: CogMethod) + codeSize) + (methodZone roundUpLength: mapSize).
- 	openPICSize := (methodZone roundUpLength: headerSize + codeSize) + (methodZone roundUpLength: mapSize).
  	"self cCode: ''
  		inSmalltalk:
  			[| end |
  			 end := self outputInstructionsAt: methodZoneBase + headerSize.
+ 			 self disassembleFrom: methodZoneBase + (self sizeof: CogMethod) to: end - 1.
- 			 self disassembleFrom: methodZoneBase + headerSize to: end - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>generateTrampolines (in category 'initialization') -----
  generateTrampolines
  	"Generate the run-time entries and exits at the base of the native code zone and update the base.
  	 Read the class-side method trampolines for documentation on the various trampolines"
  	| methodZoneStart |
  	methodZoneStart := methodZoneBase.
+ 	methodLabel address: methodZoneStart.
  	self allocateOpcodes: 80 bytecodes: 0.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	hasYoungReferent := false.
  	self generateSendTrampolines.
  	self generateMissAbortTrampolines.
  	objectRepresentation generateObjectRepresentationTrampolines.
  	self generateRunTimeTrampolines.
  	self cppIf: NewspeakVM ifTrue: 	[self generateNewspeakRuntime].
  	self cppIf: SistaVM ifTrue: [self generateSistaRuntime].
  	self generateEnilopmarts.
  	self generateTracingTrampolines.
  
  	"finish up"
  	self recordGeneratedRunTime: 'methodZoneBase' address: methodZoneBase.
  	processor flushICacheFrom: methodZoneStart to: methodZoneBase!

Item was added:
+ ----- Method: Cogit>>methodLabel (in category 'accessing') -----
+ methodLabel
+ 	<cmacro: '() methodLabel'>
+ 	^methodLabel!

Item was changed:
  ----- Method: Cogit>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	coInterpreter := aCoInterpreter.
  	objectMemory := aCoInterpreter objectMemory.
  	threadManager := aCoInterpreter threadManager. "N.B. may be nil"
  	methodZone := CogMethodZone new.
  	objectRepresentation := objectMemory objectRepresentationClass
  								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
  	primitiveGeneratorTable := self class primitiveTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
+ 	traceFlags := (self class initializationOptions at: #recordPrimTrace ifAbsent: [true])
+ 					ifTrue: [8] "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
+ 					ifFalse: [0].
- 	traceFlags := 8. "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
  	breakBlock ifNil: [self breakPC: breakPC].
  	(backEnd := processor abstractInstructionCompilerClass new) cogit: self.
  	(methodLabel := processor abstractInstructionCompilerClass new) cogit: self.
  	ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[directedSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	NewspeakVM ifTrue:
  		[selfSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		implicitReceiverSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		outerSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	"debug metadata"
  	objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).
  	runtimeObjectRefIndex := 0.
  	"debug metadata"
  	trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).
  	trampolineTableIndex := 0.
  
  	compilationTrace ifNil: [compilationTrace := self class initializationOptions at: #compilationTrace ifAbsent: [0]].
  	extA := extB := 0!

Item was changed:
  ----- Method: Cogit>>varBaseAddress (in category 'accessing') -----
  varBaseAddress
  	"We expect simulatedAddresses to have around 40 entries.  48 is hopefully a good maximum."
  	<doNotGenerate>
+ 	^coInterpreter varBaseAddress!
- 	^self cCode: [coInterpreter varBaseAddress]
- 		inSmalltalk: [self fakeAddressFor: nil index: 48]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>addressForLabel: (in category 'labels') -----
  addressForLabel: l
+ 	^variables at: l ifAbsentPut: [variables size * 4 + self variablesBase]!
- 	^variables
- 		at: l
- 		ifAbsentPut:
- 			[(self isLabelRelativeToCogitVarBaseReg: l)
- 				ifTrue: [cogit fakeAddressFor: l index: variables size + 48]
- 				ifFalse: [variables size * 4 + self variablesBase]]!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>varBaseAddress (in category 'accessing') -----
+ varBaseAddress
+ 	"This value is chosen for ARM, which has the ability to do 12-bit relative addresses from the var base register."
+ 	^(variables at: 'stackLimit') - (1 << 11)!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  genSend: selector numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	self assert: (numArgs between: 0 and: 255). "say"
  	self assert: (objectMemory addressCouldBeOop: selector).
  	self MoveMw: numArgs * objectMemory wordSize r: SPReg R: ReceiverResultReg.
  	"Deal with stale super sends; see SpurMemoryManager's class comment."
  	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
+ 	"0 through (NumSendTrampolines - 2) numArgs sends have the arg count implciti in the trampoline.
+ 	 The last send trampoline (NumSendTrampolines - 1) passes numArgs in SendNumArgsReg."
+ 	numArgs >= (NumSendTrampolines - 1) ifTrue:
- 	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
  	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self genMoveConstant: tempOop R: TempReg].
  	self MoveCw: selector R: ClassReg.
  	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
  		with: annotation.
  	self PushR: ReceiverResultReg.
  	^0!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
+ fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
+ 	pic counters: 0.
+ 	^super fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>fillInCPICHeader:size:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
- fillInCPICHeader: pic size: size numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
- 	pic counters: 0.
- 	^super fillInCPICHeader: pic size: size numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
+ fillInOPICHeader: pic numArgs: numArgs selector: selector
+ 	pic counters: 0.
+ 	^super fillInOPICHeader: pic numArgs: numArgs selector: selector!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>fillInOPICHeader:size:numArgs:selector: (in category 'generate machine code') -----
- fillInOPICHeader: pic size: size numArgs: numArgs selector: selector
- 	pic counters: 0.
- 	^super fillInOPICHeader: pic size: size numArgs: numArgs selector: selector!

Item was changed:
  ----- Method: SpurMemoryManager>>checkTraversableSortedFreeList (in category 'simulation only') -----
  checkTraversableSortedFreeList
+ 	| prevFree prevPrevFree freeChunk |
- 	| prevFree freeChunk |
  	<api>
  	<inline: false>
+ 	prevFree := prevPrevFree := 0.
- 	prevFree := 0.
  	freeChunk := firstFreeChunk.
  	self allOldSpaceEntitiesDo:
  		[:o| | objOop next limit |
  		(self isFreeObject: o) ifTrue:
  			[self assert: o = freeChunk.
  			 next := self nextInSortedFreeListLink: freeChunk given: prevFree.
  			 limit := next = 0 ifTrue: [endOfMemory] ifFalse: [next].
  			 "coInterpreter transcript cr; print: freeChunk; tab; print: o; tab; print: prevFree; nextPutAll: '<->'; print: next; flush."
  			 objOop := freeChunk.
  			 [self oop: (objOop := self objectAfter: objOop) isLessThan: limit] whileTrue:
  				[self assert: (self isFreeObject: objOop) not].
+ 			 prevPrevFree := prevFree.
  			 prevFree := freeChunk.
  			 freeChunk := next]].
  	self assert: prevFree = lastFreeChunk.
+ 	self assert: (self nextInSortedFreeListLink: lastFreeChunk given: 0) = prevPrevFree.
  	self assert: freeChunk = 0.
  	^true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMarshalledSend:numArgs:sendTable: (in category 'bytecode generator support') -----
  genMarshalledSend: selector numArgs: numArgs sendTable: sendTable
  	<inline: false>
  	<var: #sendTable type: #'sqInt *'>
  	| annotation |
  	(objectMemory isYoung: selector) ifTrue:
  		[hasYoungReferent := true].
  	self assert: needsFrame.
  	annotation := self annotationForSendTable: sendTable.
  	"Deal with stale super sends; see SpurMemoryManager's class comment."
  	(self annotationIsForUncheckedEntryPoint: annotation) ifTrue:
  		[objectRepresentation genEnsureOopInRegNotForwarded: ReceiverResultReg scratchReg: TempReg].
+ 	"0 through (NumSendTrampolines - 2) numArgs sends have the arg count implciti in the trampoline.
+ 	 The last send trampoline (NumSendTrampolines - 1) passes numArgs in SendNumArgsReg."
+ 	numArgs >= (NumSendTrampolines - 1) ifTrue:
- 	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
  	(BytecodeSetHasDirectedSuperSend
  	 and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[self genMoveConstant: tempOop R: TempReg].
  	self MoveCw: selector R: ClassReg.
  	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
  		with: annotation.
  	optStatus isReceiverResultRegLive: false.
  	^self ssPushRegister: ReceiverResultReg!



More information about the Vm-dev mailing list