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

commits at source.squeak.org commits at source.squeak.org
Mon Apr 6 23:09:28 UTC 2015


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

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

Name: VMMaker.oscog-eem.1164
Author: eem
Time: 6 April 2015, 4:07:16.571 pm
UUID: 69e65453-aec5-4f00-9b29-14fa7f384209
Ancestors: VMMaker.oscog-eem.1163

WARNING!! Because of the rename of 
VMSqueakV3BytecodeConstants to VMBytecodeConstants
you will probably have to do a recompile package after
loading this iunless loading it for the first time.

Add support for a directed super send bytecode
that starts the lookup above the class that is the
value of an association pushed on the stack immediately
before the send.  This bytecode is used in SistaV1
to allow inlining of code that contains super sends.

Add mapFor:bcpc:withAnnotationPerformUntil:arg: and
use it to gather send and branch data in the Sista
Cogit.

Rename VMSqueakV3BytecodeConstants to
VMBytecodeConstants and add the
BytecodeSetHasDirectedSuperSend flag.  Rewrite
initialization of NumTrampolines to take into account
the directedSuperSend trampolines.

Use PushCq to pass small integer constants in the
trampolines instead of smashing TempReg, which is
now used to hold the directed supersend argument.
Add support for PushCq.  Could use PushCw but on
x86 PushCq is a lot shorter.

Change a few byteAt: sends to send to the right class.
Fix a slip in isDirectedSuper:extA:extB:.  Fix slip in
annotationForSendTable:.
Fix a bug in nextDescriptorAndExtensionsInto: so that it
answers info for the next, not the current, bytecode.
Fix printing in CurrentImageCoInterpreterFacade so that
printTrampolineTable works with a facade.

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

Item was added:
+ ----- Method: CoInterpreter>>ceSend:above:to:numArgs: (in category 'trampolines') -----
+ ceSend: selector above: startAssociationArg to: rcvr numArgs: numArgs
+ 	"Entry-point for an unlinked directed super send in a CogMethod.  Smalltalk stack looks like
+ 					receiver
+ 					args
+ 		head sp ->	sender return pc
+ 	startAssociation is an association whose value is the class above which to start the lookup.
+ 
+ 	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
+ 	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
+ 	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
+ 	because we're out of code memory.
+ 
+ 	Continue execution via either executeMethod or interpretMethodFromMachineCode:
+ 	depending on whether the target method is cogged or not."
+ 	<api>
+ 	<option: #BytecodeSetHasDirectedSuperSend>
+ 	| startAssociation classTag errSelIdx cogMethod |
+ 	<inline: false>
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<var: #newCogMethod type: #'CogMethod *'>
+ 	"self printExternalHeadFrame"
+ 	"self printStringOf: selector"
+ 	cogit assertCStackWellAligned.
+ 	self assert: (objectMemory addressCouldBeOop: rcvr).
+ 	self sendBreakpoint: selector receiver: rcvr.
+ 	startAssociation := objectMemory followMaybeForwarded: startAssociationArg.
+ 	classTag := objectMemory classTagForClass: (self superclassOf: (objectMemory fetchPointer: ValueIndex ofObject: startAssociation)).
+ 	argumentCount := numArgs.
+ 	(self lookupInMethodCacheSel: selector classTag: classTag)
+ 		ifTrue:"check for coggability because method is in the cache"
+ 			[self
+ 				ifAppropriateCompileToNativeCode: newMethod
+ 				selector: selector]
+ 		ifFalse:
+ 			[self deny: (objectMemory isForwardedClassTag: classTag).
+ 			 (objectMemory isOopForwarded: selector) ifTrue:
+ 				[^self
+ 					ceSend: (self handleForwardedSelectorFaultFor: selector)
+ 					above: startAssociation
+ 					to: rcvr
+ 					numArgs: numArgs].
+ 			 messageSelector := selector.
+ 			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
+ 				[(errSelIdx = SelectorDoesNotUnderstand
+ 				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
+ 											receiver: rcvr
+ 											methodOperand: (self mnuMethodOrNilFor: rcvr)
+ 											numArgs: argumentCount) asUnsignedInteger
+ 						> cogit minCogMethodAddress]) ifTrue:
+ 						[cogit
+ 							linkSendAt: (stackPages longAt: stackPointer)
+ 							in: (self mframeHomeMethod: framePointer)
+ 							to: cogMethod
+ 							offset: cogit noCheckEntryOffset
+ 							receiver: rcvr].
+ 				self handleMNU: errSelIdx
+ 					InMachineCodeTo: rcvr
+ 					classForMessage: (objectMemory classForClassTag: classTag).
+ 				self assert: false "NOTREACHED"]].
+ 	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
+ 	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
+ 	(self maybeMethodHasCogMethod: newMethod) ifTrue:
+ 		[cogMethod := self cogMethodOf: newMethod.
+ 		 cogMethod selector = objectMemory nilObject
+ 			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
+ 			ifFalse:
+ 				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
+ 				  correct selector.  If not, try and compile a new method with the correct selector."
+ 				 cogMethod selector ~= selector ifTrue:
+ 					[(cogit cog: newMethod selector: selector) ifNotNil:
+ 						[:newCogMethod| cogMethod := newCogMethod]]].
+ 		 cogMethod selector = selector
+ 			ifTrue:
+ 				[cogit
+ 					linkSendAt: (stackPages longAt: stackPointer)
+ 					in: (self mframeHomeMethod: framePointer)
+ 					to: cogMethod
+ 					offset: cogit noCheckEntryOffset
+ 					receiver: rcvr]
+ 			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
+ 				[cogit
+ 					patchToOpenPICFor: selector
+ 					numArgs: numArgs
+ 					receiver: rcvr].
+ 		 instructionPointer := self popStack.
+ 		 self executeNewMethod.
+ 		 self assert: false "NOTREACHED"].
+ 	instructionPointer := self popStack.
+ 	^self interpretMethodFromMachineCode
+ 	"NOTREACHED"!

Item was changed:
  ----- Method: CogIA32Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^maxSize := N forms are to get around the compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^maxSize := 0].
  		[AlignmentNops]		-> [^maxSize := (operands at: 0) - 1].
  		[Fill16]					-> [^maxSize := 2].
  		[Fill32]					-> [^maxSize := 4].
  		[FillFromWord]			-> [^maxSize := 4].
  		[Nop]					-> [^maxSize := 1].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^maxSize := 1].
  		[IDIVR]					-> [^maxSize := 2].
  		[IMULRR]				-> [^maxSize := 3].
  		[CPUID]					-> [^maxSize := 2].
  		[CMPXCHGAwR]			-> [^maxSize := 7].
  		[CMPXCHGMwrR]		-> [^maxSize := 8].
  		[LFENCE]				-> [^maxSize := 3].
  		[MFENCE]				-> [^maxSize := 3].
  		[SFENCE]				-> [^maxSize := 3].
  		[LOCK]					-> [^maxSize := 1].
  		[XCHGAwR]				-> [^maxSize := 6].
  		[XCHGMwrR]			-> [^maxSize := 7].
  		[XCHGRR]				-> [^maxSize := 2].
  		"Control"
  		[Call]					-> [^maxSize := 5].
  		[JumpR]					-> [^maxSize := 2].
  		[Jump]					-> [self resolveJumpTarget. ^maxSize := 5].
  		[JumpLong]				-> [self resolveJumpTarget. ^maxSize := 5].
  		[JumpZero]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNonZero]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNegative]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNonNegative]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpOverflow]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNoOverflow]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpNoCarry]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLess]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpGreaterOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpGreater]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLessOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpAbove]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPEqual]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPNotEqual]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPLess]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPLessOrEqual]	-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPOrdered]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[JumpFPUnordered]		-> [self resolveJumpTarget. ^maxSize := 6].
  		[RetN]					-> [^maxSize := (operands at: 0) = 0
  													ifTrue: [1]
  													ifFalse: [3]].
  		[Stop]					-> [^maxSize := 1].
  
  		"Arithmetic"
  		[AddCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AndCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[CmpCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[OrCqR]			-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[SubCqR]		-> [^maxSize := (self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AddCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[AndCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[CmpCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[OrCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[SubCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[XorCwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]].
  		[AddRR]			-> [^maxSize := 2].
  		[AndRR]			-> [^maxSize := 2].
  		[CmpRR]		-> [^maxSize := 2].
  		[OrRR]			-> [^maxSize := 2].
  		[XorRR]			-> [^maxSize := 2].
  		[SubRR]			-> [^maxSize := 2].
  		[NegateR]		-> [^maxSize := 2].
  		[LoadEffectiveAddressMwrR]
  						-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[LogicalShiftLeftCqR]		-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[LogicalShiftRightCqR]	-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[ArithmeticShiftRightCqR]	-> [^maxSize := (operands at: 0) = 1
  														ifTrue: [2]
  														ifFalse: [3]].
  		[LogicalShiftLeftRR]		-> [self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [self computeShiftRRSize].
  		[ArithmeticShiftRightRR]	-> [self computeShiftRRSize].
  		[AddRdRd]				-> [^maxSize := 4].
  		[CmpRdRd]				-> [^maxSize := 4].
  		[SubRdRd]				-> [^maxSize := 4].
  		[MulRdRd]				-> [^maxSize := 4].
  		[DivRdRd]				-> [^maxSize := 4].
  		[SqrtRd]					-> [^maxSize := 4].
  		"Data Movement"
  		[MoveCqR]		-> [^maxSize := (operands at: 0) = 0 ifTrue: [2] ifFalse: [5]].
  		[MoveCwR]		-> [^maxSize := 5].
  		[MoveRR]		-> [^maxSize := 2].
  		[MoveRdRd]		-> [^maxSize := 4].
  		[MoveAwR]		-> [^maxSize := (self concreteRegister: (operands at: 1)) = EAX
  											ifTrue: [5]
  											ifFalse: [6]].
  		[MoveRAw]		-> [^maxSize := (self concreteRegister: (operands at: 0)) = EAX
  											ifTrue: [5]
  											ifFalse: [6]].
  		[MoveRMwr]		-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRdM64r]	-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMbrR]		-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRMbr]		-> [^maxSize := ((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM16rR]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM64rRd]	-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMwrR]		-> [^maxSize := ((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveXwrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^maxSize := (self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[PopR]			-> [^maxSize := 1].
  		[PushR]			-> [^maxSize := 1].
+ 		[PushCq]		-> [^maxSize := (self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^maxSize := 5].
  		[PrefetchAw]	-> [^maxSize := self hasSSEInstructions ifTrue: [7] ifFalse: [0]].
  		"Conversion"
  		[ConvertRRd]	-> [^maxSize := 4] }.
  	^0 "to keep C compiler quiet"!

Item was added:
+ ----- Method: CogIA32Compiler>>concretizePushCq (in category 'generate machine code') -----
+ concretizePushCq
+ 	<inline: true>
+ 	| value |
+ 	value := operands at: 0.
+ 	(self isQuick: value) ifTrue:
+ 		[machineCode
+ 			at: 0 put: 16r6A;
+ 			at: 1 put: (value bitAnd: 16rFF).
+ 		^machineCodeSize := 2].
+ 	machineCode
+ 		at: 0 put: 16r68;
+ 		at: 1 put: (value bitAnd: 16rFF);
+ 		at: 2 put: (value >> 8 bitAnd: 16rFF);
+ 		at: 3 put: (value >> 16 bitAnd: 16rFF);
+ 		at: 4 put: (value >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := 5!

Item was changed:
  ----- Method: CogIA32Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	<returnTypeC: #void>
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill16]				-> [^self concretizeFill16].
  		[Fill32]				-> [^self concretizeFill32].
  		[FillFromWord]		-> [^self concretizeFillFromWord].
  		[Nop]				-> [^self concretizeNop].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
  		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
  		[LFENCE]				-> [^self concretizeFENCE: 5].
  		[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7].
  		[LOCK]					-> [^self concretizeLOCK].
  		[XCHGAwR]				-> [^self concretizeXCHGAwR].
  		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpLong]				-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJumpLong: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJumpLong: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeAddCwR].
  		[AddRR]						-> [^self concretizeAddRR].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[AndRR]						-> [^self concretizeAndRR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[CmpRR]					-> [^self concretizeCmpRR].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[OrCqR]						-> [^self concretizeOrCqR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[OrRR]						-> [^self concretizeOrRR].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[SubRR]						-> [^self concretizeSubRR].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[XorCwR]						-> [^self concretizeXorCwR].
  		[XorRR]							-> [^self concretizeXorRR].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
+ 		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd] }!

Item was changed:
  ----- Method: CogIA32Compiler>>genPassConst:asArgument: (in category 'abi') -----
  genPassConst: constant asArgument: zeroRelativeArgIndex
+ 	cogit PushCq: constant.
- 	cogit
- 		MoveCq: constant R: TempReg;
- 		PushR: TempReg.
  	^0!

Item was added:
+ ----- Method: CogIA32Compiler>>literalBeforeInlineCacheTagAt: (in category 'inline cacheing') -----
+ literalBeforeInlineCacheTagAt: callSiteReturnAddress
+ 	"Answer a literal loaded before the inline cache tag load for the return address of a send."
+ 	^self literalBeforeFollowingAddress: callSiteReturnAddress - 10!

Item was added:
+ ----- Method: CogObjectRepresentation>>valueOfAssociation: (in category 'sista support') -----
+ valueOfAssociation: association
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveMirrorNewWithArg: (in category 'primitive generators') -----
  genInnerPrimitiveMirrorNewWithArg: retNoffset
  	"Implement instantiateVariableClass:withSize: for convenient cases:
  	- the class argument has a hash
  	- the class argument is variable and not compiled method
  	- single word header/num slots < numSlotsMask
  	- the result fits in eden
  	See superclass method for dynamic frequencies of formats.
  	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
  
  	<option: #NewspeakVM>
  	| halfHeaderReg fillReg instSpecReg byteSizeReg maxSlots
  	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
  	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
  	  jumpUnhashed jumpTooSmall jumpImmediate jumpNotFixedPointers
  	  jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |
  	<var: 'skip' type: #'AbstractInstruction *'>
  	<var: 'fillLoop' type: #'AbstractInstruction *'>	
  	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
  	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
  	<var: 'jumpTooSmall' type: #'AbstractInstruction *'>
  	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
  	<var: 'jumpImmediate' type: #'AbstractInstruction *'>
  	<var: 'jumpByteFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
  	<var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
  	<var: 'jumpNotFixedPointers' type: #'AbstractInstruction *'>
  
  	"half header will contain 1st half of header (classIndex/class's hash & format),
  	 then 2nd half of header (numSlots) and finally fill value (nilObject)."
  	halfHeaderReg := fillReg := SendNumArgsReg.
  	"inst spec will hold class's instance specification and then byte size and finally numSlots half of header"
  	instSpecReg := byteSizeReg := ClassReg.
  	"The max slots we'll allocate here are those for a single header"
  	maxSlots := objectMemory numSlotsMask - 1.
  
  	"check size and fail if not a +ve integer"
  	cogit MoveR: Arg1Reg R: TempReg.
  	jumpNElementsNonInt := self genJumpNotSmallIntegerInScratchReg: TempReg.
  
  	"Is the class arg pointers with at least 3 fields?"
  	cogit MoveR: Arg0Reg R: TempReg.
  	jumpImmediate := self genJumpImmediateInScratchReg: TempReg.
  
  	self genGetFormatOf: Arg0Reg
  		into: TempReg
  		leastSignificantHalfOfBaseHeaderIntoScratch: nil.
  	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
  	jumpNotFixedPointers := cogit JumpNonZero: 0.
  	
  	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
  	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
  	jumpTooSmall := cogit JumpLess: 0.
  
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: Arg0Reg into: halfHeaderReg.
  	jumpUnhashed := cogit JumpZero: 0.
  
  	"The basicNew: code (genInnerPrimitiveNewWithArg:) expects class in ReceiverResultReg
  	 and size in Arg0Reg.  Shuffle args to match, undoing on failure."
  	cogit
  		PushR: ReceiverResultReg;
  		MoveR: Arg0Reg R: ReceiverResultReg;
  		MoveR: Arg1Reg R: Arg0Reg.
  
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: ReceiverResultReg into: halfHeaderReg.
  	jumpUnhashed := cogit JumpZero: 0.
  	"get class's format inst var for inst spec (format field)"
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
  	cogit AndCq: objectMemory formatMask R: instSpecReg.
  	"Add format to classIndex/format half header now"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: halfHeaderReg.
  	"get integer value of num fields in TempReg now"
  	cogit MoveR: Arg0Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	"dispatch on format, failing if not variable or if compiled method"
  	cogit CmpCq: objectMemory arrayFormat R: instSpecReg.
  	jumpArrayFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
  	jumpByteFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
  	jumpFailCuzFixed := cogit JumpNonZero: 0.
  
  	cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg.
  	jumpLongTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"push fill value"
+ 	cogit PushCq: 0.
- 	cogit MoveCq: 0 R: TempReg.
- 	cogit PushR: TempReg.
  	jumpLongPrepDone := cogit Jump: 0. "go allocate"
  
  	jumpByteFormat jmpTarget:
  	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
  	jumpByteTooBig := cogit JumpAbove: 0.
  	"save num elements to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"compute odd bits and add into halfHeaderReg; oddBits := 4 - nElements bitAnd: 3"
  	cogit MoveCq: objectMemory wordSize R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: halfHeaderReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
  	"push fill value"
+ 	cogit PushCq: 0.
- 	cogit MoveCq: 0 R: TempReg.
- 	cogit PushR: TempReg.
  	jumpBytePrepDone := cogit Jump: 0. "go allocate"
  
  	jumpArrayFormat jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
  	jumpArrayTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"push fill value"
+ 	cogit PushCw: objectMemory nilObject.
- 	cogit MoveCw: objectMemory nilObject R: TempReg.
- 	cogit PushR: TempReg.
  	"fall through to allocate"
  
  	jumpBytePrepDone jmpTarget:
  	(jumpLongPrepDone jmpTarget: cogit Label).
  
  	"write half header now; it frees halfHeaderReg"
  	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
  	"save numSlots to halfHeaderReg"
  	cogit MoveR: instSpecReg R: halfHeaderReg.
  	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
  	 rounded up to 8 bytes."
  	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
  	jumpHasSlots := cogit JumpNonZero: 0.
  	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
  	skip := cogit Jump: 0.
  	"round up to allocationUnit"
  	jumpHasSlots jmpTarget:
  	(cogit MoveR: byteSizeReg R: TempReg).
  	cogit AndCq: 1 R: TempReg.
  	cogit AddR: TempReg R: byteSizeReg.
  	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
  	skip jmpTarget:
  	"shift halfHeaderReg to put numSlots in correct place"
  	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
  	"check if allocation fits"
  	cogit AddR: Arg1Reg R: byteSizeReg.
  	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
  	"write other half of header (numSlots/0 identityHash)"
  	cogit MoveR: halfHeaderReg Mw: 4 r: ReceiverResultReg.
  	"now fill"
  	cogit PopR: fillReg.
  	cogit PopR: TempReg. "discard pushed receiver"
  	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
  	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
  	fillLoop := 
  	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
  	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
  	cogit AddCq: 8 R: Arg1Reg.
  	cogit CmpR: Arg1Reg R: byteSizeReg.
  	cogit JumpAbove: fillLoop.
  	cogit RetN: retNoffset.
  
  	"pop discarded fill value & fall through to failure"
  	jumpNoSpace jmpTarget: (cogit PopR: TempReg).
  
  	jumpFailCuzFixed jmpTarget:
  	(jumpArrayTooBig jmpTarget:
  	(jumpByteTooBig jmpTarget:
  	(jumpLongTooBig jmpTarget: cogit Label))).
  
  	"unshuffle arguments"
  	cogit
  		MoveR: Arg0Reg R: Arg1Reg;
  		MoveR: ReceiverResultReg R: Arg0Reg;
  		PopR: ReceiverResultReg.
  
  	jumpUnhashed jmpTarget:
  	(jumpImmediate jmpTarget:
  	(jumpNotFixedPointers jmpTarget:
  	(jumpTooSmall jmpTarget:
  	(jumpNElementsNonInt jmpTarget: cogit Label)))).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
  genInnerPrimitiveNewWithArg: retNoffset
  	"Implement primitiveNewWithArg for convenient cases:
  	- the receiver has a hash
  	- the receiver is variable and not compiled method
  	- single word header/num slots < numSlotsMask
  	- the result fits in eden
  	See superclass method for dynamic frequencies of formats.
  	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
  
  	| halfHeaderReg fillReg instSpecReg byteSizeReg maxSlots
  	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
  	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
  	  jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |
  	<var: 'skip' type: #'AbstractInstruction *'>
  	<var: 'fillLoop' type: #'AbstractInstruction *'>	
  	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
  	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
  	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
  	<var: 'jumpByteFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
  	<var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
  
  	"half header will contain 1st half of header (classIndex/class's hash & format),
  	 then 2nd half of header (numSlots) and finally fill value (nilObject)."
  	halfHeaderReg := fillReg := SendNumArgsReg.
  	"inst spec will hold class's instance specification and then byte size and finally numSlots half of header"
  	instSpecReg := byteSizeReg := ClassReg.
  	"The max slots we'll allocate here are those for a single header"
  	maxSlots := objectMemory numSlotsMask - 1.
  
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: ReceiverResultReg into: halfHeaderReg.
  	jumpUnhashed := cogit JumpZero: 0.
  	"get index and fail if not a +ve integer"
  	cogit MoveR: Arg0Reg R: TempReg.
  	jumpNElementsNonInt := self genJumpNotSmallIntegerInScratchReg: TempReg.
  	"get class's format inst var for inst spec (format field)"
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
  	cogit AndCq: objectMemory formatMask R: instSpecReg.
  	"Add format to classIndex/format half header now"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: halfHeaderReg.
  	"get integer value of num fields in TempReg now"
  	cogit MoveR: Arg0Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	"dispatch on format, failing if not variable or if compiled method"
  	cogit CmpCq: objectMemory arrayFormat R: instSpecReg.
  	jumpArrayFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
  	jumpByteFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
  	jumpFailCuzFixed := cogit JumpNonZero: 0.
  
  	cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg.
  	jumpLongTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"push fill value"
+ 	cogit PushCq: 0.
- 	cogit MoveCq: 0 R: TempReg.
- 	cogit PushR: TempReg.
  	jumpLongPrepDone := cogit Jump: 0. "go allocate"
  
  	jumpByteFormat jmpTarget:
  	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
  	jumpByteTooBig := cogit JumpAbove: 0.
  	"save num elements to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"compute odd bits and add into halfHeaderReg; oddBits := 4 - nElements bitAnd: 3"
  	cogit MoveCq: objectMemory wordSize R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: halfHeaderReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
  	"push fill value"
+ 	cogit PushCq: 0.
- 	cogit MoveCq: 0 R: TempReg.
- 	cogit PushR: TempReg.
  	jumpBytePrepDone := cogit Jump: 0. "go allocate"
  
  	jumpArrayFormat jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
  	jumpArrayTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"push fill value"
+ 	cogit PushCw: objectMemory nilObject.
- 	cogit MoveCw: objectMemory nilObject R: TempReg.
- 	cogit PushR: TempReg.
  	"fall through to allocate"
  
  	jumpBytePrepDone jmpTarget:
  	(jumpLongPrepDone jmpTarget: cogit Label).
  
  	"write half header now; it frees halfHeaderReg"
  	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
  	"save numSlots to halfHeaderReg"
  	cogit MoveR: instSpecReg R: halfHeaderReg.
  	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
  	 rounded up to 8 bytes."
  	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
  	jumpHasSlots := cogit JumpNonZero: 0.
  	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
  	skip := cogit Jump: 0.
  	"round up to allocationUnit"
  	jumpHasSlots jmpTarget:
  	(cogit MoveR: byteSizeReg R: TempReg).
  	cogit AndCq: 1 R: TempReg.
  	cogit AddR: TempReg R: byteSizeReg.
  	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
  	skip jmpTarget:
  	"shift halfHeaderReg to put numSlots in correct place"
  	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
  	"check if allocation fits"
  	cogit AddR: Arg1Reg R: byteSizeReg.
  	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
  	"write other half of header (numSlots/0 identityHash)"
  	cogit MoveR: halfHeaderReg Mw: 4 r: ReceiverResultReg.
  	"now fill"
  	cogit PopR: fillReg.
  	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
  	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
  	fillLoop := 
  	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
  	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
  	cogit AddCq: 8 R: Arg1Reg.
  	cogit CmpR: Arg1Reg R: byteSizeReg.
  	cogit JumpAbove: fillLoop.
  	cogit RetN: retNoffset.
  
  	"pop discarded fill value & fall through to failure"
  	jumpNoSpace jmpTarget: (cogit PopR: TempReg).
  
  	jumpUnhashed jmpTarget:
  	(jumpFailCuzFixed jmpTarget:
  	(jumpArrayTooBig jmpTarget:
  	(jumpByteTooBig jmpTarget:
  	(jumpLongTooBig jmpTarget:
  	(jumpNElementsNonInt jmpTarget: cogit Label))))).
  
  	^0!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSpur
  	instanceVariableNames: 'ceScheduleScavengeTrampoline ceSmallActiveContextInMethodTrampoline ceSmallActiveContextInBlockTrampoline ceLargeActiveContextInMethodTrampoline ceLargeActiveContextInBlockTrampoline'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogCompilationConstants VMBytecodeConstants VMSqueakClassIndices'
- 	poolDictionaries: 'CogCompilationConstants VMSqueakClassIndices VMSqueakV3BytecodeConstants'
  	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>valueOfAssociation: (in category 'sista support') -----
+ valueOfAssociation: associationOop
+ 	| association |
+ 	association := associationOop.
+ 	(objectMemory isForwarded: association) ifTrue:
+ 		[association := objectMemory followForwarded: association].
+ 	^objectMemory fetchPointer: ValueIndex ofObject: association!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>valueOfAssociation: (in category 'sista support') -----
+ valueOfAssociation: association
+ 	^objectMemory fetchPointer: ValueIndex ofObject: association!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCw PushR RISCTempReg ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits on
  	 a 32-bit architecture or 64-bits on a 64-bit architecture.  The abstract machine is mostly a 2 address machine
  	 with the odd three address instruction added to better exploit RISCs.
  			(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a `quick' constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word at an absolute address
  		Ab		- memory byte at an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		XbrR	- memory word whose address is r * byte size away from an address in a register
  		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
  		XwrR	- memory word whose address is r * word size away from an address in a register
  		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	 XowrR scaled index addressing mode since it requires 4 operands.
  
  	Note that there are no generic division instructions defined, but a processor may define some."
  
  	| opcodeNames refs |
  	self flag: 'GPRegMin and GPRegMax are poorly thought-out and should instead defer to the backEnd for allocateable registers.'.
  	"A small fixed set of abstract registers are defined and used in code generation
  	 for Smalltalk code, and executes on stack pages in the stack zone.
  	 These are mapped to processor-specific registers by concreteRegister:"
  	FPReg := -1.	"A frame pointer is used for Smalltalk frames."
  	SPReg := -2.
  	ReceiverResultReg := GPRegMax := -3. "The receiver at point of send, and return value from a send"
  	TempReg := -4.
  	ClassReg := -5.							"The inline send cache class tag is in this register, loaded at the send site"
  	SendNumArgsReg := -6.				"Sends > 2 args set the arg count in this reg"
  	Arg0Reg := -7.							"In the StackToregisterMappingCogit 1 & 2 arg sends marshall into these registers."
  	Arg1Reg := GPRegMin := -8.
  
  	"Floating-point registers"
  	DPFPReg0 := -9.
  	DPFPReg1 := -10.
  	DPFPReg2 := -11.
  	DPFPReg3 := -12.
  	DPFPReg4 := -13.
  	DPFPReg5 := -14.
  	DPFPReg6 := -15.
  	DPFPReg7 := -16.
  
  	"RISC-specific"
  	LinkReg := -17.
  	RISCTempReg := -18.
  	PCReg := -19.
  	VarBaseReg := -20. "If useful, points to base of interpreter variables."
  
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						AlignmentNops
  						FillBytesFrom	"output operand 0's worth of bytes from the address in operand 1"
  						Fill8				"output a byte's worth of bytes with operand 0"
  						Fill16			"output two byte's worth of bytes with operand 0"
  						Fill32			"output four byte's worth of bytes with operand 0"
  						FillFromWord	"output BytesPerWord's worth of bytes with operand 0 + operand 1"
  						Nop
  
  						"Control"
  						Call
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long jumps are contigiuous within them.  See FirstJump et al below"
  						JumpLong
  						JumpLongZero		"a.k.a. JumpLongEqual"
  						JumpLongNonZero	"a.k.a. JumpLongNotEqual"
  						Jump
  						JumpZero			"a.k.a. JumpEqual"
  						JumpNonZero		"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
  						MoveRdRd MoveM64rRd MoveRdM64r
+ 						PopR PushR PushCq PushCw
- 						PopR PushR PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR MulRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR XorCqR MulCqR
  						CmpCwR AddCwR SubCwR AndCwR OrCwR XorCwR MulCwR
  
  						AndCqRR
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd TstCqR SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpLong.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

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'
- 	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'
  	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'
- 	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
+ !Cogit commentStamp: 'eem 4/6/2015 15:56' prior: 0!
- !Cogit commentStamp: 'eem 2/13/2013 15:37' 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
- 	the index into blockStarts as they are being noted, and hence eventuakly teh 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 changed:
  ----- Method: Cogit class>>initializeBytecodeTable (in category 'class initialization') -----
  initializeBytecodeTable
  	"SimpleStackBasedCogit initializeBytecodeTableWith: Dictionary new"
  	"StackToRegisterMappingCogit initializeBytecodeTableWith: Dictionary new"
  
  	| initializer |
+ 	BytecodeSetHasDirectedSuperSend := false.
  	initializer := initializationOptions
  					at: #bytecodeTableInitializer
  					ifAbsent:
  						[NewspeakVM
  							ifTrue:
  								[MULTIPLEBYTECODESETS
  									ifTrue: [#initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid]
  									ifFalse: [#initializeBytecodeTableForNewspeakV4]]
  							ifFalse:
  								[#initializeBytecodeTableForSqueakV3PlusClosures]].
  	"Now make sure all classes in the hierarchy have initialized to the same bytecode table."
  	(self withAllSuperclasses copyUpTo: Cogit) reverseDo: "i.e. exclude Cogit"
  		[:cogitClass|
  		 cogitClass perform: initializer]!

Item was added:
+ ----- Method: Cogit>>PushCq: (in category 'abstract instructions') -----
+ PushCq: wordConstant
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self gen: PushCq operand: wordConstant!

Item was changed:
  ----- Method: Cogit>>annotationForMcpc:in: (in category 'method map') -----
  annotationForMcpc: mcpc in: cogHomeMethod
  	"Answer the annotation for mcpc in cogHomeMethod's map, or 0 if no entry exists."
  	<var: #cogHomeMethod type: #'CogMethod *'>
  	| mapLocation mapByte annotation |
  	mapLocation := self findMapLocationForMcpc: mcpc inMethod: cogHomeMethod.
  	mapLocation = 0 ifTrue:
  		[^0].
+ 	mapByte := objectMemory byteAt: mapLocation.
- 	mapByte := coInterpreter byteAt: mapLocation.
  	annotation := mapByte >> AnnotationShift.
  	annotation = IsSendCall ifTrue:
+ 		[mapByte := objectMemory byteAt: mapLocation - 1.
- 		[mapByte := coInterpreter byteAt: mapLocation - 1.
  		 mapByte >> AnnotationShift = IsAnnotationExtension ifTrue:
  			[annotation := annotation + (mapByte bitAnd: DisplacementMask)]].
  	^annotation!

Item was changed:
  ----- Method: Cogit>>findMapLocationForMcpc:inMethod: (in category 'method map') -----
  findMapLocationForMcpc: targetMcpc inMethod: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	| mcpc map mapByte annotation |
  	mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
  	map := self mapStartFor: cogMethod.
  	mcpc = targetMcpc ifTrue: [^map].
+ 	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
- 	[(mapByte := coInterpreter byteAt: map) ~= MapEnd] whileTrue:
  		[annotation := mapByte >> AnnotationShift.
  		 annotation ~= IsAnnotationExtension ifTrue:
  			[mcpc := mcpc + (annotation = IsDisplacementX2N
  								ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  								ifFalse: [mapByte bitAnd: DisplacementMask])].
  		 mcpc >= targetMcpc ifTrue:
  			[self assert: mcpc = targetMcpc.
  			 ^map].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- Method: Cogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 0
  					  arg: ReceiverResultReg
  					  arg: numArgs)].
  	ordinarySendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					called: (self trampolineName: 'ceSend' numArgs: -1)
  					arg: ClassReg
  					arg: 0
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
  	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
+ 	self cppIf: BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[0 to: NumSendTrampolines - 2 do:
+ 			[:numArgs|
+ 			directedSuperSendTrampolines
+ 				at: numArgs
+ 				put: (self genTrampolineFor: #ceSend:above:to:numArgs:
+ 						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
+ 						  arg: ClassReg
+ 						  arg: TempReg
+ 						  arg: ReceiverResultReg
+ 						  arg: numArgs)].
+ 		directedSuperSendTrampolines
+ 			at: NumSendTrampolines - 1
+ 			put: (self genTrampolineFor: #ceSend:above:to:numArgs:
+ 						called: (self trampolineName: 'ceDirectedSuperSend' numArgs: -1)
+ 						arg: ClassReg
+ 						arg: TempReg
+ 						arg: ReceiverResultReg
+ 						arg: SendNumArgsReg)].
  
  	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 1
  					  arg: ReceiverResultReg
  					  arg: numArgs)].
  	superSendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					called: (self trampolineName: 'ceSuperSend' numArgs: -1)
  					arg: ClassReg
  					arg: 1
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was changed:
  ----- Method: Cogit>>isDirectedSuper:extA:extB: (in category 'bytecode generator support') -----
  isDirectedSuper: descriptor extA: exta extB: extb
  	"235	(1)	11101011	iiiiijjj	ExtendB < 64
  										ifTrue: [Send To Superclass
  													Literal Selector #iiiii (+ Extend A * 32)
  													with jjj (+ Extend B * 8) Arguments]
  										ifFalse: [Send To Superclass of Stacked Class
  													Literal Selector #iiiii (+ Extend A * 32)
  													with jjj (+ (Extend B bitAnd: 63) * 8) Arguments]"
  	<inline: true>
  	^descriptor notNil
+ 	  and: [descriptor generator == #genExtSendSuperBytecode
- 	  and: [descriptor == #genExtSendSuperBytecode
  	  and: [extb >= 64]]!

Item was changed:
  ----- Method: Cogit>>mapEndFor: (in category 'method map') -----
  mapEndFor: cogMethod
  	"Answer the address of the null byte at the end of the method map."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	| end |
  	end := self mapStartFor: cogMethod.
+ 	[(objectMemory byteAt: end) ~= MapEnd] whileTrue:
- 	[(coInterpreter byteAt: end) ~= MapEnd] whileTrue:
  		[end := end - 1.
  		 self assert: end > (cogMethod asInteger + cmNoCheckEntryOffset)].
  	^end!

Item was changed:
  ----- Method: Cogit>>mapFor:performAllMapEntriesUntil:arg: (in category 'method map') -----
  mapFor: cogMethod performAllMapEntriesUntil: functionSymbol arg: arg
  	"Analysis support"
  	<doNotGenerate>
  	| mcpc map mapByte result |
  	mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
  	map := self mapStartFor: cogMethod.
+ 	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
- 	[(mapByte := coInterpreter byteAt: map) ~= MapEnd] whileTrue:
  		[mapByte >= FirstAnnotation
  			ifTrue:
  				[mcpc := mcpc + (mapByte bitAnd: DisplacementMask)]
  			ifFalse:
  				[mapByte < (IsAnnotationExtension << AnnotationShift) ifTrue:
  					[mcpc := mcpc + (mapByte - DisplacementX2N << AnnotationShift)]].
  		 result := self perform: functionSymbol
  					   with: mapByte >> AnnotationShift
  					   with: (self cCoerceSimple: mcpc to: #'char *')
  					   with: arg.
  		 result ~= 0 ifTrue:
  			[^result].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- Method: Cogit>>mapFor:performUntil:arg: (in category 'method map') -----
  mapFor: cogMethod performUntil: functionSymbol arg: arg
  	"Unlinking/GC/Disassembly support"
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #functionSymbol declareC: 'int (*functionSymbol)(sqInt annotation, char *mcpc, sqInt arg)'>
  	<inline: true>
  	| mcpc map mapByte annotation result |
  	mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
  	map := self mapStartFor: cogMethod.
+ 	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
- 	[(mapByte := coInterpreter byteAt: map) ~= MapEnd] whileTrue:
  		[mapByte >= FirstAnnotation
  			ifTrue:
  				[mcpc := mcpc + (mapByte bitAnd: DisplacementMask).
  				 "If this is an IsSendCall annotation, peek ahead for an IsAnnotationExtension, and consume it."
  				 ((annotation := mapByte >> AnnotationShift) = IsSendCall
+ 				  and: [(mapByte := objectMemory byteAt: map - 1) >> AnnotationShift = IsAnnotationExtension]) ifTrue:
- 				  and: [(mapByte := coInterpreter byteAt: map - 1) >> AnnotationShift = IsAnnotationExtension]) ifTrue:
  					[annotation := annotation + (mapByte bitAnd: DisplacementMask).
  					 map := map - 1].
  				 result := self perform: functionSymbol
  							   with: annotation
  							   with: (self cCoerceSimple: mcpc to: #'char *')
  							   with: arg.
  				 result ~= 0 ifTrue:
  					[^result]]
  			ifFalse:
  				[mapByte < (IsAnnotationExtension << AnnotationShift) ifTrue:
  					[mcpc := mcpc + (mapByte - DisplacementX2N << AnnotationShift)]].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- Method: Cogit>>nextDescriptorAndExtensionsInto: (in category 'bytecode generator support') -----
  nextDescriptorAndExtensionsInto: aTrinaryBlock
  	"Peek ahead and deliver the next descriptor plus extension bytes."
  	<inline: true>
  	| savedB0 savedB1 savedB2 savedB3 savedEA savedEB descriptor bcpc |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	descriptor := self generatorAt: byte0.
  	savedB0 := byte0. savedB1 := byte1. savedB2 := byte2. savedB3 := byte3.
  	savedEA := extA. savedEB := extB.
+ 	bcpc := bytecodePC + descriptor numBytes.
- 	bcpc := bytecodePC.
  	[bcpc > endPC ifTrue:
  		[^aTrinaryBlock value: nil value: 0 value: 0].
  	 byte0 := (objectMemory fetchByte: bcpc ofObject: methodObj)  + bytecodeSetOffset.
  	 descriptor := self generatorAt: byte0.
  	 self loadSubsequentBytesForDescriptor: descriptor at: bcpc.
  	 descriptor isExtension ifFalse:
  		[| eA eB |
  		 eA := extA. eB := extB.
  		 extA := savedEA. extB := savedEB.
  		 byte0 := savedB0. byte1 := savedB1. byte2 := savedB2. byte3 := savedB3.
  	 	 ^aTrinaryBlock value: descriptor value: eA value: eB].
  	 self perform: descriptor generator.
  	 bcpc := bcpc + descriptor numBytes.
  	 true] whileTrue!

Item was changed:
  ----- Method: Cogit>>printPCMapPairsFor:on: (in category 'method map') -----
  printPCMapPairsFor: cogMethod on: aStream
  	<doNotGenerate>
  	<inline: true>
  	| mcpc map mapByte annotation |
  	mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
  	map := self mapStartFor: cogMethod.
+ 	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
- 	[(mapByte := coInterpreter byteAt: map) ~= MapEnd] whileTrue:
  		[annotation := mapByte >> AnnotationShift.
  		 annotation ~= IsAnnotationExtension ifTrue:
  			[mcpc := mcpc + (annotation = IsDisplacementX2N
  								ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  								ifFalse: [mapByte bitAnd: DisplacementMask])].
  		 aStream ensureCr.
  		 map printOn: aStream base: 16.
  		 aStream nextPutAll: ': '.
  		 mapByte printOn: aStream base: 16.
  		 aStream space.
  		 annotation printOn: aStream base: 16.
  		 aStream nextPutAll: ' ('; print: (AnnotationConstantNames at: annotation + 1); nextPutAll: ') '.
  		 (mapByte bitAnd: DisplacementMask) printOn: aStream base: 16.
  		 aStream space.
  		 aStream nextPut: $@.
  		 mcpc printOn: aStream base: 16.
  		 aStream flush.
  		 map := map - 1]!

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 := 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 := 0].
  	extA := extB := 0!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>cr (in category 'printing') -----
+ cr
+ 	coInterpreter transcript cr; flush!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>print: (in category 'printing') -----
+ print: it
+ 	it isString ifTrue: [coInterpreter transcript nextPutAll: it] ifFalse: [it printOn: coInterpreter transcript]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>printHex: (in category 'printing') -----
  printHex: anInteger
+ 	| it16 |
+ 	it16 := anInteger radix: 16.
+ 	coInterpreter transcript
+ 		next: 8 - it16 size put: Character space;
+ 		nextPutAll: (anInteger storeStringBase: 16)!
- 	coInterpreter printHex: anInteger!

Item was changed:
  VMClass subclass: #InterpreterPrimitives
  	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields'
  	classVariableNames: 'CrossedX EndOfRun MillisecondClockMask'
+ 	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets'
- 	poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMSqueakV3BytecodeConstants VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !InterpreterPrimitives commentStamp: 'eem 12/11/2012 17:11' prior: 0!
  InterpreterPrimitives implements most of the VM's core primitives.  It is the root of the interpreter hierarchy so as to share the core primitives amongst the varioius interpreters.
  
  Instance Variables
  	argumentCount:	<Integer>
  	messageSelector:	<Integer>
  	newMethod:		<Integer>
  	nextProfileTick:		<Integer>
  	objectMemory:		<ObjectMemory> (simulation only)
  	preemptionYields:	<Boolean>
  	primFailCode:		<Integer>
  	profileMethod:		<Integer>
  	profileProcess:		<Integer>
  	profileSemaphore:	<Integer>
  
  argumentCount
  	- the number of arguments of the current message
  
  messageSelector
  	- the oop of the selector of the current message
  
  newMethod
  	- the oop of the result of looking up the current message
  
  nextProfileTick
  	- the millisecond clock value of the next profile tick (if profiling is in effect)
  
  objectMemory
  	- the memory manager and garbage collector that manages the heap
  
  preemptionYields
  	- a boolean controlling the process primitives.  If true (old, incorrect, blue-book semantics) a preempted process is sent to the back of its run-queue.  If false, a process preempted by a higher-priority process is put back at the head of its run queue, hence preserving cooperative scheduling within priorities.
  
  primFailCode
  	- primtiive success/failure flag, 0 for success, otherwise the reason code for failure
  
  profileMethod
  	- the oop of the method at the time nextProfileTick was reached
  
  profileProcess
  	- the oop of the activeProcess at the time nextProfileTick was reached
  
  profileSemaphore
  	- the oop of the semaphore to signal when nextProfileTick is reached
  !

Item was changed:
  VMStructType subclass: #InterpreterStackPage
  	instanceVariableNames: 'stackLimit headSP headFP baseFP baseAddress realStackLimit lastAddress trace nextPage prevPage'
  	classVariableNames: ''
+ 	poolDictionaries: 'VMBasicConstants VMBytecodeConstants'
- 	poolDictionaries: 'VMBasicConstants VMSqueakV3BytecodeConstants'
  	category: 'VMMaker-Interpreter'!
  
  !InterpreterStackPage commentStamp: '<historical>' prior: 0!
  I am a class that helps organize the StackInterpreter's collection of stack pages.  I represent the control block for a single stack page in the collection of stack pages represented by an InterpreterStackPages instance.!

Item was changed:
  VMClass subclass: #ObjectMemory
  	instanceVariableNames: 'memory youngStart endOfMemory memoryLimit nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount rootTableOverflowed extraRoots extraRootCount weakRoots weakRootCount child field parentField freeBlock lastHash allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount allocationsBetweenGCs tenuringThreshold gcBiasToGrow gcBiasToGrowGCLimit gcBiasToGrowThreshold statFullGCs statIncrGCs statFullGCUsecs statIncrGCUsecs statGCEndTime statIGCDeltaUsecs statTenures statRootTableOverflows freeContexts freeLargeContexts interruptCheckCounter totalObjectCount shrinkThreshold growHeadroom headerTypeBytes youngStartLocal statMarkCount statMarkCountLocal statSweepCount statMkFwdCount statCompMoveCount statGrowMemory statShrinkMemory statRootTableCount statAllocationCount statSurvivorCount statSpecialMarkCount forceTenureFlag gcStartUsecs'
  	classVariableNames: 'AllButHashBits AllButImmutabilityBit AllButMarkBit AllButMarkBitAndTypeMask AllButRootBit Done ExtraRootSize GCTopMarker HashBits HeaderTypeClass HeaderTypeExtraBytes HeaderTypeFree HeaderTypeGC LongSizeNumBits NilContext RemapBufferSize RootTableRedZone RootTableSize StartField StartObj Upward WeakRootTableSize WordMask'
+ 	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMObjectIndices VMSqueakClassIndices VMSqueakV3ObjectRepresentationConstants'
- 	poolDictionaries: 'VMBasicConstants VMObjectIndices VMSqueakClassIndices VMSqueakV3BytecodeConstants VMSqueakV3ObjectRepresentationConstants'
  	category: 'VMMaker-Interpreter'!
  
  !ObjectMemory commentStamp: '<historical>' prior: 0!
  This class describes a 32-bit direct-pointer object memory for Smalltalk.  The model is very simple in principle:  a pointer is either a SmallInteger or a 32-bit direct object pointer.
  
  SmallIntegers are tagged with a low-order bit equal to 1, and an immediate 31-bit 2s-complement signed value in the rest of the word.
  
  All object pointers point to a header, which may be followed by a number of data fields.  This object memory achieves considerable compactness by using a variable header size (the one complexity of the design).  The format of the 0th header word is as follows:
  
  	3 bits	reserved for gc (mark, root, unused)
  	12 bits	object hash (for HashSets)
  	5 bits	compact class index
  	4 bits	object format
  	6 bits	object size in 32-bit words
  	2 bits	header type (0: 3-word, 1: 2-word, 2: forbidden, 3: 1-word)
  
  If a class is in the compact class table, then this is the only header information needed.  If it is not, then it will have another header word at offset -4 bytes with its class in the high 30 bits, and the header type repeated in its low 2 bits.  It the objects size is greater than 255 bytes, then it will have yet another header word at offset -8 bytes with its full word size in the high 30 bits and its header type repeated in the low two bits.
  
  The object format field provides the remaining information as given in the formatOf: method (including isPointers, isVariable, isBytes, and the low 2 size bits of byte-sized objects).
  
  This implementation includes incremental (2-generation) and full garbage collection, each with compaction and rectification of direct pointers.  It also supports a bulk-become (exchange object identity) feature that allows many objects to be becomed at once, as when all instances of a class must be grown or shrunk.
  
  There is now a simple 64-bit version of the object memory.  It is the simplest possible change that could work.  It merely sign-extends all integer oops, and extends all object headers and oops by adding 32 zeroes in the high bits.  The format of the base header word is changed in one minor, not especially elegant, way.  Consider the old 32-bit header:
  	ggghhhhhhhhhhhhcccccffffsssssstt
  The 64-bit header is almost identical, except that the size field (now being in units of 8 bytes, has a zero in its low-order bit.  At the same time, the byte-size residue bits for byte objects, which are in the low order bits of formats 8-11 and 12-15, are now in need of another bit of residue.  So, the change is as follows:
  	ggghhhhhhhhhhhhcccccffffsssssrtt
  where bit r supplies the 4's bit of the byte size residue for byte objects.  Oh, yes, this is also needed now for 'variableWord' objects, since their size in 32-bit words requires a low-order bit.
  
  See the comment in formatOf: for the change allowing for 64-bit wide bitmaps, now dubbed 'variableLong'.!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"SimpleStackBasedCogit initializeBytecodeTableForSistaV1"
  
+ 	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushLiteralVariable16CasesBytecode	needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1   96 117 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
  		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 genExtTrapIfNotInstanceOfBehaviorsBytecode isMapped)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
  		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
  		(3 254 255	unknownBytecode))!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
+ 	NumTrampolines := 42
+ 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
+ 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!
- 	NumTrampolines := NewspeakVM
- 							ifTrue: [60]
- 							ifFalse: [42]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>annotationForSendTable: (in category 'bytecode generator support') -----
  annotationForSendTable: sendTable
  	"c.f. offsetAndSendTableFor:annotation:into:"
  	<inline: true>
  	<var: #sendTable type: #'sqInt *'>
  	(NewspeakVM and: [sendTable == selfSendTrampolines]) ifTrue:
  		[^IsNSSelfSend].
  	(NewspeakVM and: [sendTable == dynamicSuperSendTrampolines]) ifTrue:
  		[^IsNSDynamicSuperSend].
  	(NewspeakVM and: [sendTable == implicitReceiverSendTrampolines]) ifTrue:
  		[^IsNSImplicitReceiverSend].
+ 	(BytecodeSetHasDirectedSuperSend and: [sendTable == directedSuperSendTrampolines]) ifTrue:
+ 		[^IsDirectedSuperSend].
- 	(SistaVM and: [sendTable == directedSuperSendTrampolines]) ifTrue:
- 		[^IsNSImplicitReceiverSend].
  	sendTable == superSendTrampolines ifTrue:
  		[^IsSuperSend].
  	self assert: sendTable == ordinarySendTrampolines.
  	^IsSendCall!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushLiteralVariableGivenDirectedSuper: (in category 'bytecode generator support') -----
  genPushLiteralVariableGivenDirectedSuper: literalIndex
  	"This is a version of genPushLiteralVariable: that looks ahead for a directed super send bytecode
  	 and does not generate any code for the dereference yet if followed by a directed super send."
  	<inline: false>
  	self nextDescriptorAndExtensionsInto:
  		[:descriptor :exta :extb|
  		(self isDirectedSuper: descriptor extA: exta extB: extb) ifTrue:
+ 			[tempOop := self getLiteral: literalIndex.
- 			[self ssPushConstant: (self getLiteral: literalIndex).
  			 ^0]].
  	^self genPushLiteralVariable: literalIndex!

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.
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
+ 	(BytecodeSetHasDirectedSuperSend
+ 	 and: [annotation = IsDirectedSuperSend]) ifTrue:
+ 		[self annotate: (self MoveCw: tempOop R: TempReg) objRef: tempOop].
  	self MoveCw: selector R: ClassReg.
  	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
  		with: annotation.
  	self flag: 'currently caller pushes result'.
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendDirectedSuper:numArgs: (in category 'bytecode generator support') -----
  genSendDirectedSuper: selector numArgs: numArgs
  	<inline: false>
+ 	"N.B. genPushLiteralVariableGivenDirectedSuper: has already loaded tempOop with the association."
- 	self halt: 'do all that good stuff moving the literal variable to an argument reg, etc...'.
  	^self genSend: selector numArgs: numArgs sendTable: directedSuperSendTrampolines!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
+ 	NumTrampolines := 53
+ 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
+ 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!
- 	NumTrampolines := NewspeakVM
- 							ifTrue: [67]
- 							ifFalse: [53]!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>mapFor:bcpc:withAnnotationPerformUntil:arg: (in category 'method map') -----
+ mapFor: cogMethod bcpc: startbcpc withAnnotationPerformUntil: functionSymbol arg: arg
+ 	"A version of mapFor:bcpc:performUntil:arg: that passes the annotation instead of the isBackwardBranch flag."
+ 	<var: #cogMethod type: #'CogBlockMethod *'>
+ 	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(BytecodeDescriptor *desc, sqInt annotation, char *mcpc, sqInt bcpc, void *arg)'>
+ 	<var: #arg type: #'void *'>
+ 	<inline: true>
+ 	| isInBlock mcpc bcpc endbcpc map mapByte homeMethod aMethodObj result
+ 	  latestContinuation byte descriptor bsOffset nExts annotation |
+ 	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	<var: #homeMethod type: #'CogMethod *'>
+ 	self assert: cogMethod stackCheckOffset > 0.
+ 	"In both CMMethod and CMBlock cases find the start of the map and
+ 	 skip forward to the bytecode pc map entry for the stack check."
+ 	cogMethod cmType = CMMethod
+ 		ifTrue:
+ 			[isInBlock := false.
+ 			 homeMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'.
+ 			 self assert: startbcpc = (coInterpreter startPCOfMethodHeader: homeMethod methodHeader).
+ 			 map := self mapStartFor: homeMethod.
+ 			 annotation := (objectMemory byteAt: map) >> AnnotationShift.
+ 			 self assert: (annotation = IsAbsPCReference
+ 						 or: [annotation = IsObjectReference
+ 						 or: [annotation = IsRelativeCall
+ 						 or: [annotation = IsDisplacementX2N]]]).
+ 			 latestContinuation := startbcpc.
+ 			 aMethodObj := homeMethod methodObject.
+ 			 endbcpc := (objectMemory numBytesOf: aMethodObj) - 1.
+ 			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader]
+ 		ifFalse:
+ 			[isInBlock := true.
+ 			 homeMethod := cogMethod cmHomeMethod.
+ 			 map := self findMapLocationForMcpc: cogMethod asUnsignedInteger + (self sizeof: CogBlockMethod)
+ 						inMethod: homeMethod.
+ 			 self assert: map ~= 0.
+ 			 annotation := (objectMemory byteAt: map) >> AnnotationShift.
+ 			 self assert: (annotation >> AnnotationShift = HasBytecodePC "fiducial"
+ 						 or: [annotation >> AnnotationShift = IsDisplacementX2N]).
+ 			 [(annotation := (objectMemory byteAt: map) >> AnnotationShift) ~= HasBytecodePC] whileTrue:
+ 				[map := map - 1].
+ 			 map := map - 1. "skip fiducial; i.e. the map entry for the pc immediately following the method header."
+ 			 aMethodObj := homeMethod methodObject.
+ 			 bcpc := startbcpc - (self blockCreationBytecodeSizeForHeader: homeMethod methodHeader).
+ 			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader.
+ 			 byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
+ 			 descriptor := self generatorAt: byte.
+ 			 endbcpc := self nextBytecodePCFor: descriptor at: bcpc exts: -1 in: aMethodObj].
+ 	bcpc := startbcpc.
+ 	mcpc := cogMethod asUnsignedInteger + cogMethod stackCheckOffset.
+ 	nExts := 0.
+ 	"The stack check maps to the start of the first bytecode,
+ 	 the first bytecode being effectively after frame build."
+ 	result := self perform: functionSymbol
+ 					with: nil
+ 					with: annotation
+ 					with: (self cCoerceSimple: mcpc to: #'char *')
+ 					with: startbcpc
+ 					with: arg.
+ 	result ~= 0 ifTrue:
+ 		[^result].
+ 	"Now skip up through the bytecode pc map entry for the stack check." 
+ 	[(objectMemory byteAt: map) >> AnnotationShift ~= HasBytecodePC] whileTrue:
+ 		[map := map - 1].
+ 	map := map - 1.
+ 	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue: "defensive; we exit on bcpc"
+ 		[mapByte >= FirstAnnotation
+ 			ifTrue:
+ 				[| nextBcpc |
+ 				annotation := mapByte >> AnnotationShift.
+ 				mcpc := mcpc + (mapByte bitAnd: DisplacementMask).
+ 				(self isPCMappedAnnotation: annotation) ifTrue:
+ 					[(annotation = IsSendCall
+ 					  and: [(mapByte := objectMemory byteAt: map - 1) >> AnnotationShift = IsAnnotationExtension]) ifTrue:
+ 						[annotation := annotation + (mapByte bitAnd: DisplacementMask).
+ 						 map := map - 1].
+ 					[byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
+ 					  descriptor := self generatorAt: byte.
+ 					  isInBlock
+ 						ifTrue: [bcpc >= endbcpc ifTrue: [^0]]
+ 						ifFalse:
+ 							[(descriptor isReturn and: [bcpc >= latestContinuation]) ifTrue: [^0].
+ 							 (descriptor isBranch or: [descriptor isBlockCreation]) ifTrue:
+ 								[| targetPC |
+ 								 targetPC := self latestContinuationPCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
+ 								 latestContinuation := latestContinuation max: targetPC]].
+ 					  nextBcpc := self nextBytecodePCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
+ 					  descriptor isMapped
+ 					  or: [isInBlock and: [descriptor isMappedInBlock]]] whileFalse:
+ 						[bcpc := nextBcpc.
+ 						 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
+ 					result := self perform: functionSymbol
+ 									with: descriptor
+ 									with: annotation
+ 									with: (self cCoerceSimple: mcpc to: #'char *')
+ 									with: bcpc
+ 									with: arg.
+ 					 result ~= 0 ifTrue:
+ 						[^result].
+ 					 bcpc := nextBcpc.
+ 					 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]]
+ 			ifFalse:
+ 				[self assert: (mapByte >> AnnotationShift = IsDisplacementX2N
+ 							or: [mapByte >> AnnotationShift = IsAnnotationExtension]).
+ 				 mapByte < (IsAnnotationExtension << AnnotationShift) ifTrue:
+ 					[mcpc := mcpc + (mapByte - DisplacementX2N << AnnotationShift)]].
+ 		 map := map - 1].
+ 	^0!

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

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>picDataFor:IsBackwardBranch:Mcpc:Bcpc:Method: (in category 'method introspection') -----
- picDataFor: descriptor IsBackwardBranch: IsBackwardBranch Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
- 	<var: #descriptor type: #'BytecodeDescriptor *'>
- 	<var: #mcpc type: #'char *'>
- 	<var: #cogMethodArg type: #'void *'>
- 	| entryPoint tuple counter |
- 	<var: #counter type: #'unsigned long'>
- 
- 	descriptor isNil ifTrue:
- 		[^0].
- 	descriptor isBranch ifTrue:
- 		["it's a branch; conditional?"
- 		 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
- 			[counter := (self
- 							cCoerce: ((self
- 											cCoerceSimple: cogMethodArg
- 											to: #'CogMethod *') counters)
- 							to: #'unsigned long *')
- 								at: counterIndex.
- 			 tuple := self picDataForCounter: counter at: bcpc + 1.
- 			 tuple = 0 ifTrue: [^PrimErrNoMemory].
- 			 objectMemory storePointer: picDataIndex ofObject: picData withValue: tuple.
- 			 picDataIndex := picDataIndex + 1.
- 			 counterIndex := counterIndex + 1].
- 		 ^0].
- 	"infer it's a send; alas we can't just test the descriptor because of the bloody
- 	 doubleExtendedDoAnythingBytecode which does sends as well as other things."
- 	(backEnd isCallPreceedingReturnPC: mcpc asUnsignedInteger) ifFalse:
- 		[^0].
- 	entryPoint := backEnd callTargetFromReturnAddress: mcpc asUnsignedInteger.
- 	entryPoint <= methodZoneBase ifTrue: "send is not linked, or is not a send"
- 		[^0].
- 	self targetMethodAndSendTableFor: entryPoint into: "It's a linked send; find which kind."
- 		[:targetMethod :sendTable|
- 		 tuple := self picDataForSendTo: targetMethod
- 					methodClassIfSuper: (sendTable = superSendTrampolines
- 											ifTrue:
- 												[coInterpreter methodClassOf:
- 													(self cCoerceSimple: cogMethodArg to: #'CogMethod *') methodObject]
- 											ifFalse: "Difficult to find the directed send class at this point in time ;-)"
- 												[sendTable = directedSuperSendTrampolines ifTrue:
- 													[objectMemory nilObject]])
- 					at: mcpc
- 					bcpc: bcpc + 1].
- 	tuple = 0 ifTrue: [^PrimErrNoMemory].
- 	objectMemory storePointer: picDataIndex ofObject: picData withValue: tuple.
- 	picDataIndex := picDataIndex + 1.
- 	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>picDataFor:into: (in category 'method introspection') -----
  picDataFor: cogMethod into: arrayObj
  	"Collect the branch and send data for cogMethod, storing it into arrayObj."
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	| errCode |
  	cogMethod stackCheckOffset = 0 ifTrue:
  		[^0].
  	picDataIndex := counterIndex := 0.
  	picData := arrayObj.
  	errCode := self
  					mapFor: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *')
  					bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
+ 					withAnnotationPerformUntil: #picDataFor:Annotation:Mcpc:Bcpc:Method:
- 					performUntil: #picDataFor:IsBackwardBranch:Mcpc:Bcpc:Method:
  					arg: cogMethod asVoidPointer.
  	errCode ~= 0 ifTrue:
  		[self assert: errCode = PrimErrNoMemory.
  		 ^-1].
  	cogMethod blockEntryOffset ~= 0 ifTrue:
  		[errCode := self blockDispatchTargetsFor: cogMethod
  						perform: #picDataForBlockEntry:Method:
  						arg: cogMethod asInteger.
  		 errCode ~= 0 ifTrue:
  			[self assert: errCode = PrimErrNoMemory.
  			 ^-1]].
  	^picDataIndex!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>picDataForBlockEntry:Method: (in category 'method introspection') -----
  picDataForBlockEntry: blockEntryMcpc Method: cogMethod
  	"Collect the branch and send data for the block method starting at blockEntryMcpc, storing it into picData."
  	<returnTypeC: #usqInt>
  	| cogBlockMethod |
  	<var: #cogBlockMethod type: #'CogBlockMethod *'>
  	cogBlockMethod := self cCoerceSimple: blockEntryMcpc - (self sizeof: CogBlockMethod)
  							  to: #'CogBlockMethod *'.
  	cogBlockMethod stackCheckOffset = 0 ifTrue:
  		[^0].
  	^self
  		mapFor: cogBlockMethod
  		bcpc: cogBlockMethod startpc
+ 		withAnnotationPerformUntil: #picDataFor:Annotation:Mcpc:Bcpc:Method:
- 		performUntil: #picDataFor:IsBackwardBranch:Mcpc:Bcpc:Method:
  		arg: cogMethod asVoidPointer!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was added:
+ ----- Method: StackDepthFinder>>directedSuperSend:numArgs: (in category 'instruction decoding') -----
+ directedSuperSend: selector numArgs: numArgs
+ 	self drop: numArgs + 1!

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
  	instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue localAbsentReceiver extA extB primitiveFunctionPointer methodCache atCache isPrivateSend lkupClassTag lkupClass methodDictLinearSearchLimit highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptKeycode interruptPending savedWindowSize imageHeaderFlags fullScreenFlag deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable primitiveAccessorDepthTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2 theUnknownShort the2ndUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex classByteArrayCompactIndex statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents statPendingFinalizationSignals'
  	classVariableNames: 'AltBytecodeEncoderClassName AltLongStoreBytecode AlternateHeaderHasPrimFlag AlternateHeaderIsOptimizedFlag AlternateHeaderNumLiteralsMask AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable CacheProbeMax CheckPrivacyViolations DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex FailImbalancedPrimitives LongStoreBytecode MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MethodHeaderArgCountShift MethodHeaderFlagBitPosition MethodHeaderTempCountShift MixinIndex PrimitiveExternalCallIndex PrimitiveTable StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced StackPageUnreached V3PrimitiveBitsMask'
+ 	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices VMStackFrameOffsets'
- 	poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices VMSqueakV3BytecodeConstants VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !StackInterpreter commentStamp: 'eem 12/5/2014 11:32' prior: 0!
  This class is a complete implementation of the Smalltalk-80 virtual machine, derived originally from the Blue Book specification but quite different in some areas.  This VM supports Closures but *not* old-style BlockContexts.
  
  It has been modernized with 32-bit pointers, better management of Contexts (see next item), and attention to variable use that allows the CCodeGenerator (qv) to keep, eg, the instruction pointer and stack pointer in registers as well as keeping most simple variables in a global array that seems to improve performance for most platforms.
  
  The VM does not use Contexts directly.  Instead Contexts serve as proxies for a more conventional stack format that is invisible to the image.  There is considerable explanation at http://www.mirandabanda.org/cogblog/2009/01/14/under-cover-contexts-and-the-big-frame-up.  The VM maintains a fixed-size stack zone divided into pages, each page being capable of holding several method/block activations.  A send establishes a new frame in the current stack page, a return returns to the previous frame.  This eliminates allocation/deallocation of contexts and the moving of receiver and arguments from caller to callee on each send/return.  Contexts are created lazily when an activation needs a context (creating a block, explicit use of thisContext, access to sender when sender is a frame, or linking of stack pages together).  Contexts are either conventional and heap-resident ("single") or "married" and serve as proxies for their corresponding frame or "widowed", meaning that their spouse frame has been returned from (died).  A married context is specially marked (more details in the code) and refers to its frame.  Likewise a married frame is specially marked and refers to its context.
  
  In addition to SmallInteger arithmetic and Floats, the VM supports logic on 32-bit PositiveLargeIntegers, thus allowing it to simulate itself much more effectively than would otherwise be the case.
  
  StackInterpreter and subclasses support multiple memory managers.  Currently there are two.  NewMemoryManager is a slightly refined version of ObjectMemory, and is the memory manager and garbage collector for the original Squeak object representation as described in "Back to the Future The Story of Squeak, A Practical Smalltalk Written in Itself", see http://ftp.squeak.org/docs/OOPSLA.Squeak.html.  Spur is a faster, more regular object representation that is designed for more performance and functionality, and to have a common header format for both 32-bit and 64-bit versions.  You can read about it in SpurMemoryManager's class comment.  There is also a video of a presentation at ESUG 2014 (https://www.youtube.com/watch?v=k0nBNS1aHZ4), along with slides (http://www.slideshare.net/esug/spur-a-new-object-representation-for-cog?related=1).!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTable (in category 'initialization') -----
  initializeBytecodeTable
  	"StackInterpreter initializeBytecodeTable"
  
+ 	BytecodeSetHasDirectedSuperSend := false.
+ 
  	(initializationOptions at: #bytecodeTableInitializer ifAbsent: nil) ifNotNil:
  		[:initalizer| ^self perform: initalizer].
  
  	NewspeakVM ifTrue:
  		[^MULTIPLEBYTECODESETS
  			ifTrue: [self initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid]
  			ifFalse: [self initializeBytecodeTableForNewspeakV4]].
  
  	^self initializeBytecodeTableForSqueakV3PlusClosures!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSistaV1 (in category 'initialization') -----
  initializeBytecodeTableForSistaV1
  	"See e.g. the cass comment for EncoderForSistaV1"
  	"StackInterpreter initializeBytecodeTableForSistaV1"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForSistaV1.
+ 	BytecodeSetHasDirectedSuperSend := true.
+ 
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 pushConstantTrueBytecode)
  		( 78	 pushConstantFalseBytecode)
  		( 79	 pushConstantNilBytecode)
  		( 80	 pushConstantZeroBytecode)
  		( 81	 pushConstantOneBytecode)
  		( 82	 extPushPseudoVariable)
  		( 83	 duplicateTopBytecode)
  	
  		( 84 87	unknownBytecode)
  		( 88	returnReceiver)
  		( 89	returnTrue)
  		( 90	returnFalse)
  		( 91	returnNil)
  		( 92	returnTopFromMethod)
  		( 93	returnNilFromBlock)
  		( 94	returnTopFromBlock)
  		( 95	extNopBytecode)
  
  		( 96	 bytecodePrimAdd)
  		( 97	 bytecodePrimSubtract)
  		( 98	 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
  		( 99	 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
  		(100	 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(101	 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(102	 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
  		(103	 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
  		(104	 bytecodePrimMultiply)
  		(105	 bytecodePrimDivide)
  		(106	 bytecodePrimMod)
  		(107	 bytecodePrimMakePoint)
  		(108	 bytecodePrimBitShift)
  		(109	 bytecodePrimDiv)
  		(110	 bytecodePrimBitAnd)
  		(111	 bytecodePrimBitOr)
  
  		(112	 bytecodePrimAt)
  		(113	 bytecodePrimAtPut)
  		(114	 bytecodePrimSize)
  		(115	 bytecodePrimNext)		 "i.e. a 0 arg special selector"
  		(116	 bytecodePrimNextPut)		 "i.e. a 1 arg special selector"
  		(117	 bytecodePrimAtEnd)
  		(118	 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
  		(119	 bytecodePrimClass)
  		(120	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(121	 bytecodePrimValue)
  		(122	 bytecodePrimValueWithArg)
  		(123	 bytecodePrimDo)			"i.e. a 1 arg special selector"
  		(124	 bytecodePrimNew)			"i.e. a 0 arg special selector"
  		(125	 bytecodePrimNewWithArg)	"i.e. a 1 arg special selector"
  		(126	 bytecodePrimPointX)		"i.e. a 0 arg special selector"
  		(127	 bytecodePrimPointY)		"i.e. a 0 arg special selector"
  
  		(128 143	sendLiteralSelector0ArgsBytecode)
  		(144 159	sendLiteralSelector1ArgBytecode)
  		(160 175	sendLiteralSelector2ArgsBytecode)
  
  		(176 183	shortUnconditionalJump)
  		(184 191	shortConditionalJumpTrue)
  		(192 199	shortConditionalJumpFalse)
  	
  		(200 207	storeAndPopReceiverVariableBytecode)
  		(208 215	storeAndPopTemporaryVariableBytecode)
  		(216		popStackBytecode)
  		(217		unconditionnalTrapBytecode)
  
  		(218 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		longPushTemporaryVariableBytecode)
  		(230		pushClosureTempsBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
  		(236		extTrapIfNotInstanceOfBehaviorsBytecode)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
  		(240		extStoreAndPopReceiverVariableBytecode)
  		(241		extStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extStoreReceiverVariableBytecode)
  		(244		extStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		unknownBytecode) "reserved for Push Float"
  
  		(250		extPushClosureBytecode)
  		(251		pushRemoteTempLongBytecode)
  		(252		storeRemoteTempLongBytecode)
  		(253		storeAndPopRemoteTempLongBytecode)
  
  		(254 255	unknownBytecode)
  	)!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"StackToRegisterMappingCogit initializeBytecodeTableForSistaV1"
  
  	numPushNilsFunction := #sistaV1:Num:Push:Nils:.
  	pushNilSizeFunction := #sistaV1PushNilSize:numInitialNils:.
+ 	BytecodeSetHasDirectedSuperSend := true.
  	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode			needsFrameNever: 1)
  		(1  16   31 genPushLitVarDirSup16CasesBytecode	needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode		needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode					needsFrameNever: 1)
  		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1  96   96 genSpecialSelectorArithmetic isMapped AddRR)
  		(1  97   97 genSpecialSelectorArithmetic isMapped SubRR)
  		(1  98   98 genSpecialSelectorComparison isMapped JumpLess)
  		(1  99   99 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 100 100 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 101 101 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 102 102 genSpecialSelectorComparison isMapped JumpZero)
  		(1 103 103 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 104 109 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 110 110 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 111 111 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 112 117 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
  		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 217 genUnconditionnalTrapBytecode isMapped)
  
  		(1 218 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode		needsFrameNever: 1)
  		(2 227 227 genExtPushLitVarDirSupBytecode			needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 genExtTrapIfNotInstanceOfBehaviorsBytecode isMapped)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
  		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
  		(3 254 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
+ 	NumTrampolines := 52
+ 						+ (NewspeakVM ifTrue: [18] ifFalse: [0])
+ 						+ (BytecodeSetHasDirectedSuperSend ifTrue: [4] ifFalse: [0])!
- 	NumTrampolines := NewspeakVM
- 							ifTrue: [70]
- 							ifFalse: [52]!

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.
  	numArgs > 2 ifTrue:
  		[self MoveCq: numArgs R: SendNumArgsReg].
+ 	(BytecodeSetHasDirectedSuperSend
+ 	 and: [annotation = IsDirectedSuperSend]) ifTrue:
+ 		[self annotate: (self MoveCw: tempOop R: TempReg) objRef: tempOop].
  	self MoveCw: selector R: ClassReg.
  	self annotate: (self Call: (sendTable at: (numArgs min: NumSendTrampolines - 1)))
  		with: annotation.
  	optStatus isReceiverResultRegLive: false.
  	^self ssPushRegister: ReceiverResultReg!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPushLiteralVariableGivenDirectedSuper: (in category 'bytecode generator support') -----
+ genPushLiteralVariableGivenDirectedSuper: literalIndex
+ 	"This is a version of genPushLiteralVariable: that looks ahead for a directed super send bytecode
+ 	 and does not generate any code for the dereference yet if followed by a directed super send."
+ 	<inline: false>
+ 	self nextDescriptorAndExtensionsInto:
+ 		[:descriptor :exta :extb|
+ 		(self isDirectedSuper: descriptor extA: exta extB: extb) ifTrue:
+ 			[self ssPushConstant: (self getLiteral: literalIndex).
+ 			 ^0]].
+ 	^self genPushLiteralVariable: literalIndex!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendDirectedSuper:numArgs: (in category 'bytecode generator support') -----
  genSendDirectedSuper: selector numArgs: numArgs
+ 	self assert: self ssTop type = SSConstant.
+ 	tempOop := self ssTop constant.
+ 	self ssPop: 1.
- 	self halt: 'do all that good stuff moving the literal variable to an argument reg, etc...'.
  	self marshallSendArguments: numArgs.
+ 	^self genMarshalledSend: selector numArgs: numArgs sendTable: directedSuperSendTrampolines!
- 	^self genMarshalledSend: selector numArgs: numArgs sendTable: superSendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	"Override to generate code to push the register arg(s) for <= numRegArg arity sends."
  	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 0
  					  arg: ReceiverResultReg
  					  arg: numArgs)].
  	ordinarySendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					numArgs: self numRegArgs + 1
  					called: (self trampolineName: 'ceSend' numArgs: -1)
  					arg: ClassReg
  					arg: 0
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
  	self cppIf: NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
+ 	self cppIf: BytecodeSetHasDirectedSuperSend ifTrue:
+ 		[0 to: NumSendTrampolines - 2 do:
+ 			[:numArgs|
+ 			directedSuperSendTrampolines
+ 				at: numArgs
+ 				put: (self genSendTrampolineFor: #ceSend:above:to:numArgs:
+ 						  numArgs: numArgs
+ 						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
+ 						  arg: ClassReg
+ 						  arg: TempReg
+ 						  arg: ReceiverResultReg
+ 						  arg: numArgs)].
+ 		directedSuperSendTrampolines
+ 			at: NumSendTrampolines - 1
+ 			put: (self genSendTrampolineFor: #ceSend:above:to:numArgs:
+ 						numArgs: self numRegArgs + 1
+ 						called: (self trampolineName: 'ceDirectedSuperSend' numArgs: -1)
+ 						arg: ClassReg
+ 						arg: TempReg
+ 						arg: ReceiverResultReg
+ 						arg: SendNumArgsReg)].
  
  	0 to: NumSendTrampolines - 2 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
  					  arg: 1
  					  arg: ReceiverResultReg
  					  arg: numArgs)].
  	superSendTrampolines
  		at: NumSendTrampolines - 1
  		put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					numArgs: self numRegArgs + 1
  					called: (self trampolineName: 'ceSuperSend' numArgs: -1)
  					arg: ClassReg
  					arg: 1
  					arg: ReceiverResultReg
  					arg: SendNumArgsReg).
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was added:
+ SharedPool subclass: #VMBytecodeConstants
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'BytecodeSetHasDirectedSuperSend CtxtTempFrameStart LargeContextBit LargeContextSize LargeContextSlots SmallContextSize SmallContextSlots'
+ 	poolDictionaries: 'VMBasicConstants'
+ 	category: 'VMMaker-Interpreter'!
+ 
+ !VMBytecodeConstants commentStamp: '<historical>' prior: 0!
+ self ensureClassPool.
+ #(CtxtTempFrameStart LargeContextBit LargeContextSize SmallContextSize) do:
+ 	[:k|
+ 	self classPool declare: k from: ObjectMemory classPool]!

Item was removed:
- SharedPool subclass: #VMSqueakV3BytecodeConstants
- 	instanceVariableNames: ''
- 	classVariableNames: 'CtxtTempFrameStart LargeContextBit LargeContextSize LargeContextSlots SmallContextSize SmallContextSlots'
- 	poolDictionaries: 'VMBasicConstants'
- 	category: 'VMMaker-Interpreter'!
- 
- !VMSqueakV3BytecodeConstants commentStamp: '<historical>' prior: 0!
- self ensureClassPool.
- #(CtxtTempFrameStart LargeContextBit LargeContextSize SmallContextSize) do:
- 	[:k|
- 	self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list