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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 19 23:54:47 UTC 2016


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

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

Name: VMMaker.oscog-eem.1823
Author: eem
Time: 19 April 2016, 4:53:05.619923 pm
UUID: e74631f5-1c33-4aeb-b228-c4fe40959252
Ancestors: VMMaker.oscog-eem.1822

Cogit:
Add a primitive that answers pc map data for methods which can be used to better decorate methods in the VM Profiler.  Refactor the opc map enumeration facilities so that the Sista pic data primitive can share the same enumerator.  Do this by collapsing the isBackwardBranch and annotation parameters into a single parameter.  Nuke the Sista enumerator.  Rename SistaStackToRegisterMappingCogit to SistaCogit and correct its comment now it inherits from RegisterAllocatingCogit.

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

Item was changed:
  ----- Method: CoInterpreter>>ceCounterTripped: (in category 'cog jit support') -----
  ceCounterTripped: condition
  	"Two things are going on here.  The main one is catching a counter trip and attempting
  	 to send the SelectorCounterTripped selector.  In this case we would like to back-up
  	 the pc to the return address of the send that yields the boolean to be tested, so that
  	 after potential optimization, computation proceeds by retrying the jump.  But we cannot,
  	 since there may be no send, just a pop (as in and: [] and or: [] chains).  In this case we also
  	 want to prevent further callbacks until optimization is complete.  So we nil-out the
  	 SelectorCounterTripped entry in the specialSelectorArray.
  
  	 The minor case is that there is an unlikely  possibility that the cointer tripped but condition
  	 is not a boolean, in which case a mustBeBoolean response should occur."
  	<api>
+ 	<option: #SistaCogit>
- 	<option: #SistaStackToRegisterMappingCogit>
  	"Send e.g. thisContext conditionalBranchCounterTrippedOn: boolean."
  	| context counterTrippedSelector classTag classObj |
  	(condition = objectMemory falseObject
  	or: [condition = objectMemory trueObject]) ifFalse:
  		[^self ceSendMustBeBoolean: condition].
  
  	counterTrippedSelector := objectMemory maybeSplObj: SelectorCounterTripped.
  	(counterTrippedSelector isNil
  	or: [counterTrippedSelector = objectMemory nilObject]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
  	classTag := objectMemory
  					classTagForSpecialObjectsIndex: ClassMethodContext
  					compactClassIndex: ClassMethodContextCompactIndex.
  	(self lookupInMethodCacheSel: counterTrippedSelector classTag: classTag) ifFalse:
  	 	[messageSelector := counterTrippedSelector.
  		 classObj := objectMemory classForClassTag: classTag.
  		 (self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
  			[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  			 ^condition].
  		 self addNewMethodToCache: classObj].
  
  	(primitiveFunctionPointer ~= 0
  	or: [(self argumentCountOf: newMethod) ~= 1]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
  	objectMemory splObj: SelectorCounterTripped put: objectMemory nilObject.
  	instructionPointer := self popStack.
  	context := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	self push: context.
  	self push: condition.
  	self ifAppropriateCompileToNativeCode: newMethod selector: counterTrippedSelector.
  	self activateNewMethod.
  	"not reached"
  	^true!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>pcDataFor: (in category 'method introspection support') -----
+ pcDataFor: cogMethod
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	| cm nSlots nEntries data |
+ 	cm := cogMethod methodObject.
+ 	nSlots := (objectMemory byteSizeOf: cm) - (self startPCOfMethod: cm) * 2 + objectMemory minSlotsForShortening.
+ 	data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: nSlots.
+ 	data ifNil: [^-1].
+ 	nEntries := cogit mapPCDataFor: cogMethod into: data.
+ 	nEntries = 0 ifTrue:
+ 		[^0].
+ 	nEntries < nSlots ifTrue:
+ 		[objectMemory shorten: data toIndexableSize: nEntries].
+ 	^data!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>picDataFor: (in category 'method introspection support') -----
  picDataFor: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	| cm nSlots nEntries data |
  	cm := cogMethod methodObject.
  	nSlots := (objectMemory byteSizeOf: cm) - (self startPCOfMethod: cm) + objectMemory minSlotsForShortening.
  	data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: nSlots.
+ 	data ifNil: [^-1].
  	nEntries := cogit picDataFor: cogMethod into: data.
  	nEntries = 0 ifTrue:
  		[^0].
  	nEntries < nSlots ifTrue:
  		[objectMemory shorten: data toIndexableSize: nEntries].
  	^data!

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveMethodPCData (in category 'method introspection primitives') -----
+ primitiveMethodPCData
+ 	<export: true>
+ 	| methodReceiver data |
+ 	argumentCount ~= 0 ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadNumArgs].
+ 	methodReceiver := self stackTop.
+ 	data := 0.
+ 	(self methodHasCogMethod: methodReceiver) ifTrue:
+ 		[data := self pcDataFor: (self cogMethodOf: methodReceiver).
+ 		 data = -1 ifTrue:
+ 			[^self primitiveFailFor: PrimErrNoMemory]].
+ 	data = 0 ifTrue:
+ 		[data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: 0].
+ 	self pop: 1 thenPush: data!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveResetCountersInMethod (in category 'method introspection primitives') -----
  primitiveResetCountersInMethod
  	<export: true>
+ 	<option: #SistaCogit>
- 	<option: #SistaStackToRegisterMappingCogit>
  	| methodReceiver |
  	argumentCount ~= 0 ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  	methodReceiver := self stackTop.
  	(self methodHasCogMethod: methodReceiver) ifTrue:
  		[cogit resetCountersIn: (self cogMethodOf: methodReceiver)]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveSistaMethodPICAndCounterData (in category 'method introspection primitives') -----
  primitiveSistaMethodPICAndCounterData
  	<export: true>
+ 	<option: #SistaCogit>
- 	<option: #SistaStackToRegisterMappingCogit>
  	| methodReceiver data |
  	argumentCount ~= 0 ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  	methodReceiver := self stackTop.
  	data := 0.
  	(self methodHasCogMethod: methodReceiver) ifTrue:
  		[data := self picDataFor: (self cogMethodOf: methodReceiver).
  		 data = -1 ifTrue:
  			[^self primitiveFailFor: PrimErrNoMemory]].
  	data = 0 ifTrue:
  		[data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: 0].
  	self pop: 1 thenPush: data!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>freeCounters: (in category 'sista support') -----
  freeCounters: theCounters
  	<var: #theCounters type: #usqInt>
  	<inline: true>
+ 	<option: #SistaCogit>
- 	<option: #SistaStackToRegisterMappingCogit>
  	theCounters ~= 0 ifTrue:
  		[objectMemory freeObject: theCounters - objectMemory baseHeaderSize]!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>maybeMarkCounters: (in category 'sista support') -----
  maybeMarkCounters: theCounters
  	"In SIsta Spur counters are held on the heap in pinned objects which must be marked
  	 to avoid them being garbage collected.  This is the hook through which that happens."
  	<var: #theCounters type: #usqInt>
+ 	<option: #SistaCogit>
- 	<option: #SistaStackToRegisterMappingCogit>
  	<inline: true>
  	theCounters ~= 0 ifTrue:
  		[objectMemory markAndTrace: theCounters - objectMemory baseHeaderSize]!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>resetCountersIn: (in category 'sista support') -----
  resetCountersIn: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<api>
+ 	<option: #SistaCogit>
- 	<option: #SistaStackToRegisterMappingCogit>
  	cogit fillInCounters: (self numCountersFor: cogMethod counters) atStartAddress: cogMethod counters!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>resetCountersIn: (in category 'sista support') -----
  resetCountersIn: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<api>
+ 	<option: #SistaCogit>
- 	<option: #SistaStackToRegisterMappingCogit>
  	cogit
  		fillInCounters: (self numCountersFor: cogMethod counters)
  		atStartAddress: cogMethod counters!

Item was changed:
  ----- Method: Cogit>>find:IsBackwardBranch:Mcpc:Bcpc:MatchingBcpc: (in category 'method map') -----
+ find: descriptor IsBackwardBranch: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc MatchingBcpc: targetBcpc
- find: descriptor IsBackwardBranch: isBackwardBranch Mcpc: mcpc Bcpc: bcpc MatchingBcpc: targetBcpc
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #mcpc type: #'char *'>
  	<var: #targetBcpc type: #'void *'>
  	<inline: true>
+ 	^targetBcpc asInteger = ((descriptor isNil or: [isBackwardBranchAndAnnotation anyMask: 1])
+ 									ifTrue: [bcpc]
+ 									ifFalse: [bcpc + descriptor numBytes])
- 	^targetBcpc asInteger = ((descriptor isNil or: [isBackwardBranch]) ifTrue: [bcpc] ifFalse: [bcpc + descriptor numBytes])
  		ifTrue: [mcpc asInteger]
  		ifFalse: [0]!

Item was changed:
  ----- Method: Cogit>>find:IsBackwardBranch:Mcpc:Bcpc:MatchingMcpc: (in category 'method map') -----
+ find: descriptor IsBackwardBranch: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc MatchingMcpc: targetMcpc
- find: descriptor IsBackwardBranch: isBackwardBranch Mcpc: mcpc Bcpc: bcpc MatchingMcpc: targetMcpc
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #mcpc type: #'char *'>
  	<var: #targetMcpc type: #'void *'>
  	"Machine code addresses map to the following bytecode for all bytecodes
  	 except backward branches, where they map to the backward branch itself.
  	 This is so that loops continue, rather than terminate prematurely."
  	^targetMcpc = mcpc
+ 		ifTrue: [(descriptor isNil or: [isBackwardBranchAndAnnotation anyMask: 1])
- 		ifTrue: [(descriptor isNil or: [isBackwardBranch])
  					ifTrue: [bcpc]
  					ifFalse: [bcpc + descriptor numBytes]]
  		ifFalse: [0]!

Item was changed:
  ----- Method: Cogit>>findBackwardBranch:IsBackwardBranch:Mcpc:Bcpc:MatchingBcpc: (in category 'method map') -----
+ findBackwardBranch: descriptor IsBackwardBranch: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc MatchingBcpc: targetBcpc
- findBackwardBranch: descriptor IsBackwardBranch: isBackwardBranch Mcpc: mcpc Bcpc: bcpc MatchingBcpc: targetBcpc
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #mcpc type: #'char *'>
  	<var: #targetBcpc type: #'void *'>
  	<inline: true>
+ 	^((isBackwardBranchAndAnnotation anyMask: 1) and: [targetBcpc asInteger = bcpc])
- 	^(isBackwardBranch and: [targetBcpc asInteger = bcpc])
  		ifTrue: [mcpc asInteger]
  		ifFalse: [0]!

Item was changed:
  ----- Method: Cogit>>mapFor:bcpc:performUntil:arg: (in category 'method map') -----
  mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg
  	"Machine-code <-> bytecode pc mapping support.  Evaluate functionSymbol
  	 for each mcpc, bcpc pair in the map until the function returns non-zero,
+ 	 answering that result, or 0 if it fails to.  To cut down on number of arguments.
+ 	 and to be usable for both pc-mapping and method introspection, we encode
+ 	 the annotation and the isBackwardBranch flag in the same parameter.
+ 	 Guilty as charged."
- 	 answering that result, or 0 if it fails to.  This works only for frameful methods."
  	<var: #cogMethod type: #'CogBlockMethod *'>
+ 	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(BytecodeDescriptor *desc, sqInt annotationAndIsBackwardBranch, char *mcpc, sqInt bcpc, void *arg)'>
- 	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(BytecodeDescriptor *desc, sqInt isBackwardBranch, 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 |
- 	  latestContinuation byte descriptor bsOffset nExts |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #homeMethod type: #'CogMethod *'>
  
  	self assert: cogMethod stackCheckOffset > 0.
  	mcpc := cogMethod asUnsignedInteger + cogMethod stackCheckOffset.
  	"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: 0 + (HasBytecodePC << 1)
- 					with: false
  					with: (self cCoerceSimple: mcpc to: #'char *')
  					with: startbcpc
  					with: arg.
  	result ~= 0 ifTrue:
  		[^result].
  	bcpc := startbcpc.
  	"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]]]).
- 			 self assert: ((objectMemory byteAt: map) >> AnnotationShift = IsAbsPCReference
- 						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsObjectReference
- 						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsRelativeCall
- 						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsDisplacementX2N]]]).
  			 latestContinuation := startbcpc.
  			 aMethodObj := homeMethod methodObject.
  			 endbcpc := (objectMemory numBytesOf: aMethodObj) - 1.
  			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader.
  			"If the method has a primitive, skip it and the error code store, if any;
  			 Logically. these come before the stack check and so must be ignored."
  			 bcpc := bcpc + (self deltaToSkipPrimAndErrorStoreIn: aMethodObj
  									header: homeMethod methodHeader)]
  		ifFalse:
  			[isInBlock := true.
  			 self assert: bcpc = cogMethod startpc.
  			 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:
- 			 self assert: ((objectMemory byteAt: map) >> AnnotationShift = HasBytecodePC "fiducial"
- 						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsDisplacementX2N]).
- 			 [(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].
  	nExts := 0.
+ 	self inlineCacheTagsAreIndexes ifTrue:
+ 		[enumeratingCogMethod := homeMethod].
  	"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 isBackwardBranch |
- 				[| annotation nextBcpc isBackwardBranch |
  				annotation := mapByte >> AnnotationShift.
  				mcpc := mcpc + ((mapByte bitAnd: DisplacementMask) * backEnd codeGranularity).
  				(self isPCMappedAnnotation: annotation) ifTrue:
  					[[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]].
  					isBackwardBranch := descriptor isBranch
  										   and: [self isBackwardBranch: descriptor at: bcpc exts: nExts in: aMethodObj].
  					result := self perform: functionSymbol
  									with: descriptor
+ 									with: (isBackwardBranch ifTrue: [annotation << 1 + 1] ifFalse: [annotation << 1])
- 									with: isBackwardBranch
  									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) * backEnd codeGranularity)]].
  		 map := map - 1].
  	^0!

Item was changed:
  Cogit subclass: #SimpleStackBasedCogit
+ 	instanceVariableNames: 'primitiveGeneratorTable primSetFunctionLabel primInvokeInstruction externalPrimCallOffsets externalPrimJumpOffsets externalSetPrimOffsets introspectionDataIndex introspectionData'
- 	instanceVariableNames: 'primitiveGeneratorTable primSetFunctionLabel primInvokeInstruction externalPrimCallOffsets externalPrimJumpOffsets externalSetPrimOffsets'
  	classVariableNames: ''
  	poolDictionaries: 'VMMethodCacheConstants VMObjectIndices'
  	category: 'VMMaker-JIT'!
  
  !SimpleStackBasedCogit commentStamp: '<historical>' prior: 0!
  I am the stage one JIT for Cog that does not attempt to eliminate the stack via deferred code generation.!

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

Item was added:
+ ----- Method: SimpleStackBasedCogit>>pcDataFor:Annotation:Mcpc:Bcpc:Method: (in category 'method introspection') -----
+ pcDataFor: descriptor Annotation: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
+ 	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	<var: #mcpc type: #'char *'>
+ 	<var: #cogMethodArg type: #'void *'>
+ 
+ 	descriptor ifNil: "this is the stackCheck offset"
+ 		[self assert: introspectionDataIndex = 0.
+ 		 (self cCoerceSimple: cogMethodArg to: #'CogMethod *') cmIsFullBlock
+ 			ifTrue:
+ 				[objectMemory
+ 					storePointerUnchecked: introspectionDataIndex + 0 ofObject: introspectionData withValue: objectMemory nilObject;
+ 					storePointerUnchecked: introspectionDataIndex + 1 ofObject: introspectionData withValue: (objectMemory integerObjectOf: cbNoSwitchEntryOffset);
+ 					storePointerUnchecked: introspectionDataIndex + 2 ofObject: introspectionData withValue: objectMemory nilObject;
+ 					storePointerUnchecked: introspectionDataIndex + 3 ofObject: introspectionData withValue: (objectMemory integerObjectOf: cbEntryOffset)]
+ 			ifFalse:
+ 				[objectMemory
+ 					storePointerUnchecked: introspectionDataIndex + 0 ofObject: introspectionData withValue: objectMemory nilObject;
+ 					storePointerUnchecked: introspectionDataIndex + 1 ofObject: introspectionData withValue: (objectMemory integerObjectOf: cmEntryOffset);
+ 					storePointerUnchecked: introspectionDataIndex + 2 ofObject: introspectionData withValue: objectMemory nilObject;
+ 					storePointerUnchecked: introspectionDataIndex + 3 ofObject: introspectionData withValue: (objectMemory integerObjectOf: cmNoCheckEntryOffset)].
+ 		 introspectionDataIndex := introspectionDataIndex + 4.
+ 		 ^0].
+ 
+ 	(self isPCMappedAnnotation: isBackwardBranchAndAnnotation >> 1) ifTrue:
+ 		[| actualBcpc actualMcpc |
+ 		 actualBcpc := (isBackwardBranchAndAnnotation anyMask: 1)
+ 							ifTrue: [bcpc + 1]
+ 							ifFalse: [bcpc + descriptor numBytes + 1].
+ 		 actualMcpc := mcpc asUnsignedInteger - cogMethodArg asUnsignedInteger.
+ 		 objectMemory
+ 			storePointerUnchecked: introspectionDataIndex + 0 ofObject: introspectionData withValue: (objectMemory integerObjectOf: actualBcpc);
+ 			storePointerUnchecked: introspectionDataIndex + 1 ofObject: introspectionData withValue: (objectMemory integerObjectOf: actualMcpc).
+ 		 introspectionDataIndex := introspectionDataIndex + 2].
+ 
+ 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>pcDataForBlockEntry:Method: (in category 'method introspection') -----
+ pcDataForBlockEntry: blockEntryMcpc Method: cogMethod
+ 	"Collect the branch and send data for the block method starting at blockEntryMcpc, storing it into picData."
+ 	<returnTypeC: #usqInt>
+ 	objectMemory
+ 		storePointerUnchecked: introspectionDataIndex + 0 ofObject: introspectionData withValue: objectMemory nilObject;
+ 		storePointerUnchecked: introspectionDataIndex + 1 ofObject: introspectionData withValue: (objectMemory integerObjectOf: blockEntryMcpc - blockNoContextSwitchOffset);
+ 		storePointerUnchecked: introspectionDataIndex + 2 ofObject: introspectionData withValue: objectMemory nilObject;
+ 		storePointerUnchecked: introspectionDataIndex + 3 ofObject: introspectionData withValue: (objectMemory integerObjectOf: blockEntryMcpc).
+ 	introspectionDataIndex := introspectionDataIndex + 4.
+ 	^0!

Item was added:
+ RegisterAllocatingCogit subclass: #SistaCogit
+ 	instanceVariableNames: 'numCounters counters counterIndex initialCounterValue ceTrapTrampoline branchReachedOnlyForCounterTrip'
+ 	classVariableNames: 'CounterBytes MaxCounterValue'
+ 	poolDictionaries: 'VMSqueakClassIndices'
+ 	category: 'VMMaker-JIT'!
+ 
+ !SistaCogit commentStamp: 'eem 4/19/2016 14:22' prior: 0!
+ A SistaCogit is a refinement of RegisterAllocatingCogit that generates code suitable for dynamic optimization by Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Sista is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.
+ 
+ The basic scheme is that SistaCogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Sista analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
+ 
+ SistaCogit adds counters to conditional branches.  Each branch has an executed and a taken count, implemented at the two 16-bit halves of a single 32-bit word.  Each counter pair is initialized with initialCounterValue.  On entry to the branch the executed count is decremented and if the count goes below zero the ceMustBeBooleanAdd[True|False] trampoline called.  The trampoline distinguishes between true mustBeBoolean and counter trips because in the former the register temporarily holding the counter value will contain zero.  Then the condition is tested, and if the branch is taken the taken count is decremented.  The two counter values allow an optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
+ 
+ SistaCogit implements picDataFor:into: that fills an Array with the state of the counters in a method and the state of each linked send in a method.  This is used to implement a primitive used by the optimizer to answer the branch and send data for a method as an Array.
+ 
+ Instance Variables
+ 	counterIndex:			<Integer>
+ 	counterMethodCache:	<CogMethod>
+ 	counters:				<Array of AbstractInstruction>
+ 	initialCounterValue:		<Integer>
+ 	numCounters:			<Integer>
+ 	picData:				<Integer Oop>
+ 	picDataIndex:			<Integer>
+ 	prevMapAbsPCMcpc:	<Integer>
+ 
+ counterIndex
+ 	- xxxxx
+ 
+ counterMethodCache
+ 	- xxxxx
+ 
+ counters
+ 	- xxxxx
+ 
+ initialCounterValue
+ 	- xxxxx
+ 
+ numCounters
+ 	- xxxxx
+ 
+ picData
+ 	- xxxxx
+ 
+ picDataIndex
+ 	- xxxxx
+ 
+ prevMapAbsPCMcpc
+ 	- xxxxx
+ !

Item was added:
+ ----- Method: SistaCogit class>>additionalHeadersDo: (in category 'translation') -----
+ additionalHeadersDo: aBinaryBlock
+ 	"Evaluate aBinaryBlock with the names and contents of
+ 	 any additional header files that need to be generated."
+ 	aBinaryBlock
+ 		value: 'cogmethod.h'
+ 		value: SistaCogMethod cogMethodHeader!

Item was added:
+ ----- Method: SistaCogit class>>ancilliaryClasses: (in category 'translation') -----
+ ancilliaryClasses: options
+ 	^(super ancilliaryClasses: options) copyWith: SistaCogMethod!

Item was added:
+ ----- Method: SistaCogit class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: aCodeGen
+ 	aCodeGen var: 'counters' type: #usqInt!

Item was added:
+ ----- Method: SistaCogit class>>initializeWithOptions: (in category 'class initialization') -----
+ initializeWithOptions: optionsDictionary
+ 
+ 	super initializeWithOptions: optionsDictionary.
+ 	CounterBytes := 4.
+ 	MaxCounterValue := (1 << 16) - 1!

Item was added:
+ ----- Method: SistaCogit class>>numTrampolines (in category 'accessing') -----
+ numTrampolines
+ 	^super numTrampolines + 1
+ 
+ 	"Cogit withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
+ 	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!

Item was added:
+ ----- Method: SistaCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
+ compileBlockBodies
+ 	"override to maintain counterIndex when recompiling blocks; sigh."
+ 	<inline: false>
+ 	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
+ 	  initialStackPtr initialOpcodeIndex initialCounterIndex initialIndexOfIRC |
+ 	<var: #blockStart type: #'BlockStart *'>
+ 	self assert: blockCount > 0.
+ 	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
+ 	savedNeedsFrame := needsFrame.
+ 	savedNumArgs := methodOrBlockNumArgs.
+ 	savedNumTemps := methodOrBlockNumTemps.
+ 	inBlock := true.
+ 	compiledBlocksCount := 0.
+ 	[compiledBlocksCount < blockCount] whileTrue:
+ 		[blockStart := self blockStartAt: compiledBlocksCount.
+ 		 self scanBlock: blockStart.
+ 		 initialOpcodeIndex := opcodeIndex.
+ 		 initialCounterIndex := counterIndex.
+ 		 NewspeakVM ifTrue:
+ 			[initialIndexOfIRC := indexOfIRC].
+ 		 [self compileBlockEntry: blockStart.
+ 		  initialStackPtr := simStackPtr.
+ 		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)
+ 						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
+ 			[^result].
+ 		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
+ 		   estimated the number of initial nils (because it assumed one or more pushNils to
+ 		   produce an operand were pushNils to initialize temps.  This is very rare, so
+ 		   compensate by checking, adjusting numInitialNils and recompiling the block body.
+ 		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
+ 		  initialStackPtr = simStackPtr]
+ 			whileFalse:
+ 				[self assert: initialStackPtr > simStackPtr.
+ 				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
+ 				 blockStart fakeHeader dependent: nil.
+ 				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
+ 					through: blockStart startpc + blockStart span - 1.
+ 				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
+ 									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
+ 					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
+ 									[:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].
+ 				 opcodeIndex := initialOpcodeIndex.
+ 				 counterIndex := initialCounterIndex.
+ 				 NewspeakVM ifTrue:
+ 					[indexOfIRC := initialIndexOfIRC]].
+ 		compiledBlocksCount := compiledBlocksCount + 1].
+ 	needsFrame := savedNeedsFrame.
+ 	methodOrBlockNumArgs := savedNumArgs.
+ 	methodOrBlockNumTemps := savedNumTemps.
+ 	^0!

Item was added:
+ ----- Method: SistaCogit>>compileCogFullBlockMethod: (in category 'compile abstract instructions') -----
+ compileCogFullBlockMethod: numCopied
+ 	<option: #SistaV1BytecodeSet>
+ 	counters := 0.
+ 	^super compileCogFullBlockMethod: numCopied!

Item was added:
+ ----- Method: SistaCogit>>compileCogMethod: (in category 'compile abstract instructions') -----
+ compileCogMethod: selector
+ 	counters := 0.
+ 	^super compileCogMethod: selector!

Item was added:
+ ----- Method: SistaCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
+ compileFrameBuild
+ 	"Override to prefetch counters, if any."
+ 	super compileFrameBuild.
+ 	counters ~= 0 ifTrue:
+ 		[self PrefetchAw: counters]!

Item was added:
+ ----- Method: SistaCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
+ compileFullBlockMethodFrameBuild: numCopied
+ 	"Override to prefetch counters if any"
+ 	super compileFullBlockMethodFrameBuild: numCopied.
+ 	counters ~= 0 ifTrue:
+ 		[self PrefetchAw: counters]!

Item was added:
+ ----- Method: SistaCogit>>disassembleMethod:on: (in category 'disassembly') -----
+ disassembleMethod: surrogateOrAddress on: aStream
+ 	<doNotGenerate>
+ 	| cogMethod |
+ 	cogMethod := super disassembleMethod: surrogateOrAddress on: aStream.
+ 	(cogMethod cmType = CMMethod
+ 	 and: [cogMethod counters ~= 0]) ifTrue:
+ 		[aStream nextPutAll: 'counters:'; cr.
+ 		 numCounters := objectRepresentation numCountersFor: counters.
+ 		 0 to: numCounters - 1 do:
+ 			[:i| | addr |
+ 			 addr := i * CounterBytes + counters.
+ 			 addr printOn: aStream base: 16.
+ 			 aStream nextPut: $:; space.
+ 			 (objectMemory longAt: addr) printOn: aStream base: 16.
+ 			 aStream cr].
+ 		 aStream flush]!

Item was added:
+ ----- Method: SistaCogit>>estimateOfAbstractOpcodesPerBytecodes (in category 'accessing') -----
+ estimateOfAbstractOpcodesPerBytecodes
+ 	"Due to the counter logic, the estimation is higher"
+ 	<inline: true>
+ 	^ 11!

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

Item was added:
+ ----- Method: SistaCogit>>fillInCounters:atEndAddress: (in category 'generate machine code') -----
+ fillInCounters: nCounters atEndAddress: endAddress
+ 	endAddress - (nCounters * CounterBytes)
+ 		to: endAddress - CounterBytes
+ 		by: CounterBytes
+ 		do: [:address|
+ 			objectMemory
+ 				long32At: address
+ 				put: (initialCounterValue << 16 + initialCounterValue)]!

Item was added:
+ ----- Method: SistaCogit>>fillInCounters:atStartAddress: (in category 'generate machine code') -----
+ fillInCounters: nCounters atStartAddress: startAddress
+ 	startAddress
+ 		to: startAddress + (nCounters - 1 * CounterBytes)
+ 		by: CounterBytes
+ 		do: [:address|
+ 			objectMemory
+ 				long32At: address
+ 				put: (initialCounterValue << 16 + initialCounterValue)]!

Item was added:
+ ----- Method: SistaCogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
+ fillInMethodHeader: method size: size selector: selector
+ 	super fillInMethodHeader: method size: size selector: selector.
+ 	self fillInCounters: numCounters atStartAddress: counters.
+ 	method counters: counters.
+ 	^method!

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

Item was added:
+ ----- Method: SistaCogit>>genCounterTripOnlyJumpIf:to: (in category 'bytecode generator support') -----
+ genCounterTripOnlyJumpIf: boolean to: targetBytecodePC 
+ 	"Specific version if the branch is only reached while falling through if the counter trips after an inlined #== branch. We do not regenerate the counter logic in this case to avoid 24 bytes instructions."
+ 	
+ 	<var: #ok type: #'AbstractInstruction *'>
+ 	<var: #mustBeBooleanTrampoline type: #'AbstractInstruction *'>
+ 
+ 	| ok mustBeBooleanTrampoline |
+ 
+ 	extA := 0.
+ 
+ 	self ssFlushTo: simStackPtr - 1.
+ 	
+ 	self ssTop popToReg: TempReg.
+ 	
+ 	self ssPop: 1.
+ 
+ 	counterIndex := counterIndex + 1. "counters are increased / decreased in the inlined branch"
+ 
+ 	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
+ 	self ssAllocateRequiredReg: SendNumArgsReg.
+ 	self MoveCq: 1 R: SendNumArgsReg.
+ 	
+ 	"The first time this is reached, it calls necessarily the counter trip for the trampoline because SendNumArgsReg is non zero"
+ 	mustBeBooleanTrampoline := self CallRT: (boolean == objectMemory falseObject
+ 						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
+ 						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
+ 
+ 	self annotateBytecode: self Label.
+ 
+ 	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
+ 	 Correct result is either 0 or the distance between them.  If result is not 0 or
+ 	 their distance send mustBeBoolean."
+ 	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
+ 	self genSubConstant: boolean R: TempReg.
+ 	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
+ 
+ 	self CmpCq: (boolean == objectMemory falseObject
+ 					ifTrue: [objectMemory trueObject - objectMemory falseObject]
+ 					ifFalse: [objectMemory falseObject - objectMemory trueObject])
+ 		R: TempReg.
+ 		
+ 	ok := self JumpZero: 0.
+ 	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."		
+ 
+ 	self Jump: mustBeBooleanTrampoline.
+ 	
+ 	ok jmpTarget: self Label.
+ 	^0!

Item was added:
+ ----- Method: SistaCogit>>genExecutionCountLogicInto:counterReg: (in category 'bytecode generator support') -----
+ genExecutionCountLogicInto: binaryBlock counterReg: counterReg
+ 	<var: #countTripped type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	| counterAddress countTripped |
+ 	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
+ 	self flag: 'will need to use MoveAw32:R: if 64 bits'.
+ 	self assert: objectMemory wordSize = CounterBytes.
+ 	self MoveAw: counterAddress R: counterReg.
+ 	self SubCq: 16r10000 R: counterReg. "Count executed"
+ 	"If counter trips simply abort the comparison continuing to the following
+ 	 branch *without* writing back.  A double decrement will not trip the second time."
+ 	countTripped := self JumpCarry: 0.
+ 	self MoveR: counterReg Aw: counterAddress. "write back"
+ 	binaryBlock value: counterAddress value: countTripped!

Item was added:
+ ----- Method: SistaCogit>>genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'bytecode generators') -----
+ genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode
+ 	"SistaV1: *	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
+ 								
+ 	| reg literal distance targetFixUp |
+ 	
+ 	"We loose the information of in which register is stack top 
+ 	when jitting the branch target so we need to flush everything. 
+ 	We could use a fixed register here...."
+ 	reg := self allocateRegForStackEntryAt: 0.
+ 	self ssTop popToReg: reg.
+ 	self ssFlushTo: simStackPtr. "flushed but the value is still in reg"
+ 	
+ 	literal := self getLiteral: (extA * 256 + byte1).
+ 	extA := 0.
+ 	distance := extB * 256 + byte2.
+ 	extB := 0.
+ 	
+ 	targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'.
+ 		
+ 	(objectMemory isArrayNonImm: literal)
+ 		ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp]
+ 		ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp].
+ 						
+ 	self genPopStackBytecode.
+ 	
+ 	^0!

Item was added:
+ ----- Method: SistaCogit>>genFallsThroughCountLogicCounterReg:counterAddress: (in category 'bytecode generator support') -----
+ genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress
+ 	<inline: true>
+ 	"Gen this when the branch has not been taken and forwarders have been followed."
+ 	self SubCq: 1 R: counterReg. "Count untaken"
+ 	self MoveR: counterReg Aw: counterAddress. "write back"!

Item was added:
+ ----- Method: SistaCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
+ genJumpIf: boolean to: targetBytecodePC
+ 	"The heart of performance counting in Sista.  Conditional branches are 6 times less
+ 	 frequent than sends and can provide basic block frequencies (send counters can't).
+ 	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
+ 	 and a lower half counting untaken executions of the branch.  Executing the branch
+ 	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
+ 	 decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)
+ 	 so that scanning for send and branch data is simplified and that branch data is correct."
+ 	<inline: false>
+ 	| ok counterAddress countTripped retry nextPC nextDescriptor |
+ 	<var: #ok type: #'AbstractInstruction *'>
+ 	<var: #retry type: #'AbstractInstruction *'>
+ 	<var: #countTripped type: #'AbstractInstruction *'>
+ 	<var: #nextDescriptor type: #'AbstractInstruction *'>
+ 
+ 	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
+ 	
+ 	branchReachedOnlyForCounterTrip ifTrue: 
+ 		[ branchReachedOnlyForCounterTrip := false.
+ 		^ self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC ].
+ 	
+ 	boolean == objectMemory falseObject ifTrue:
+ 		[ "detection of and: / or:"
+ 		nextPC := bytecodePC + (self generatorAt: byte0) numBytes.
+ 		nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.
+ 		nextDescriptor generator ==  #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
+ 		nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset.
+ 		nextDescriptor generator ==  #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].  ].
+ 
+ 	extA := 0.
+ 
+ 	self ssFlushTo: simStackPtr - 1.
+ 	self ssTop popToReg: TempReg.
+ 	self ssPop: 1.
+ 
+ 	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
+ 	self ssAllocateRequiredReg: SendNumArgsReg.
+ 
+ 	retry := self Label.
+ 	self 
+ 		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
+ 			counterAddress := cAddress. 
+ 			countTripped := countTripBranch ] 
+ 		counterReg: SendNumArgsReg.
+ 	counterIndex := counterIndex + 1.
+ 
+ 	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
+ 	 Correct result is either 0 or the distance between them.  If result is not 0 or
+ 	 their distance send mustBeBoolean."
+ 	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
+ 	self genSubConstant: boolean R: TempReg.
+ 	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
+ 
+ 	self genFallsThroughCountLogicCounterReg: SendNumArgsReg counterAddress: counterAddress.
+ 
+ 	self CmpCq: (boolean == objectMemory falseObject
+ 					ifTrue: [objectMemory trueObject - objectMemory falseObject]
+ 					ifFalse: [objectMemory falseObject - objectMemory trueObject])
+ 		R: TempReg.
+ 	ok := self JumpZero: 0.
+ 	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."
+ 	
+ 	countTripped jmpTarget:
+ 		(self CallRT: (boolean == objectMemory falseObject
+ 						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
+ 						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
+ 						
+ 	"If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:
+ 	 trampoline will return directly to machine code, returning the boolean.  So the code should
+ 	 jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."
+ 	self annotateBytecode: self Label.
+ 
+ 	self Jump: retry.
+ 	
+ 	ok jmpTarget: self Label.
+ 	^0!

Item was added:
+ ----- Method: SistaCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
+ genMustBeBooleanTrampolineFor: boolean called: trampolineName
+ 	"This can be entered in one of two states, depending on SendNumArgsReg. See
+ 	 e.g. genJumpIf:to:.  If SendNumArgsReg is non-zero then this has been entered via
+ 	 the initial test of the counter in the jump executed count (i.e. the counter has
+ 	 tripped).  In this case TempReg contains the boolean to be tested and should not
+ 	 be offset, and ceCounterTripped should be invoked with the unoffset TempReg.
+ 	 If SendNumArgsReg is zero then this has been entered for must-be-boolean
+ 	 processing. TempReg has been offset by boolean and must be corrected and
+ 	 ceSendMustBeBoolean: invoked with the corrected value."
+ 	<var: #trampolineName type: #'char *'>
+ 	| jumpMBB |
+ 	<var: #jumpMBB type: #'AbstractInstruction *'>
+ 	<inline: false>
+ 	self zeroOpcodeIndex.
+ 	self CmpCq: 0 R: SendNumArgsReg.
+ 	jumpMBB := self JumpZero: 0.
+ 	"Open-code self compileTrampolineFor: #ceCounterTripped: numArgs: 1 arg: TempReg ...
+ 	 so we can restore ResultReceiverReg."
+ 	self genSmalltalkToCStackSwitch: true.
+ 	self
+ 		compileCallFor: #ceCounterTripped:
+ 		numArgs: 1
+ 		arg: TempReg
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		resultReg: TempReg "(*)"
+ 		regsToSave: self emptyRegisterMask.
+ 	"(*) For the case where the ceCounterTripped: call returns (e.g. because there's no callback selector
+ 	 installed), the call to the ceSendMustBeBooleanAddTrue/FalseTrampoline is followed by a jump
+ 	 back to the start of the counter/condition test sequence.  For this case copy the C result to
+ 	 TempReg (the register that is tested), to reload it with the boolean to be tested."
+ 	backEnd genLoadStackPointers.
+ 	backEnd hasLinkRegister ifTrue:
+ 		[self PopR: LinkReg].
+ 	"To keep ResultReceiverReg live if optStatus thought it was, simply reload it
+ 	 from the frame pointer.  This avoids having to reload it in the common case
+ 	 (counter does not trip) if it was live.  Note we can't use putSelfInReceiverResultReg
+ 	 when generating trampolines because simSelf has not yet been initialized."
+ 	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
+ 	self RetN: 0.
+ 	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
+ 	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
+ 	jumpMBB jmpTarget: (self AddCq: boolean R: TempReg).
+ 	^self genTrampolineFor: #ceSendMustBeBoolean:
+ 		called: trampolineName
+ 		numArgs: 1
+ 		arg: TempReg
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		regsToSave: self emptyRegisterMask
+ 		pushLinkReg: true
+ 		resultReg: NoReg
+ 		appendOpcodes: true!

Item was added:
+ ----- Method: SistaCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
+ genSpecialSelectorComparison
+ 	"Override to count inlined branches if followed by a conditional branch.
+ 	 We borrow the following conditional branch's counter and when about to
+ 	 inline the comparison we decrement the counter (without writing it back)
+ 	 and if it trips simply abort the inlining, falling back to the normal send which
+ 	 will then continue to the conditional branch which will trip and enter the abort."
+ 	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
+ 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB
+ 	  counterAddress countTripped counterReg index |
+ 	<var: #countTripped type: #'AbstractInstruction *'>
+ 	<var: #primDescriptor type: #'BytecodeDescriptor *'>
+ 	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
+ 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
+ 
+ 	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ self genSpecialSelectorComparisonWithoutCounters ].
+ 
+ 	self ssFlushTo: simStackPtr - 2.
+ 	primDescriptor := self generatorAt: byte0.
+ 	argIsInt := self ssTop type = SSConstant
+ 				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
+ 	rcvrIsInt := (self ssValue: 1) type = SSConstant
+ 				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
+ 
+ 	"short-cut the jump if operands are SmallInteger constants."
+ 	(argIsInt and: [rcvrIsInt]) ifTrue:
+ 		[^ self genStaticallyResolvedSpecialSelectorComparison].
+ 
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
+ 	
+ 	"Only interested in inlining if followed by a conditional branch."
+ 	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
+ 	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
+ 	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
+ 	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
+ 		[inlineCAB := argIsInt or: [rcvrIsInt]].
+ 	inlineCAB ifFalse:
+ 		[^self genSpecialSelectorSend].
+ 
+ 	argIsInt
+ 		ifTrue:
+ 			[(self ssValue: 1) popToReg: ReceiverResultReg.
+ 			 self ssPop: 2.
+ 			 self MoveR: ReceiverResultReg R: TempReg]
+ 		ifFalse:
+ 			[self marshallSendArguments: 1.
+ 			 self MoveR: Arg0Reg R: TempReg].
+ 	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
+ 							ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
+ 							ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg].
+ 
+ 	counterReg := self allocateRegNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg).
+ 	self 
+ 		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
+ 			counterAddress := cAddress. 
+ 			countTripped := countTripBranch ] 
+ 		counterReg: counterReg.
+ 
+ 	argIsInt
+ 		ifTrue: [self CmpCq: argInt R: ReceiverResultReg]
+ 		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
+ 	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
+ 	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
+ 	self genConditionalBranch: (branchDescriptor isBranchTrue
+ 				ifTrue: [primDescriptor opcode]
+ 				ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ 		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+ 		
+ 	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
+ 	
+ 	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
+ 	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
+ 	
+ 	argIsInt ifTrue:
+ 		[self MoveCq: argInt R: Arg0Reg].
+ 	index := byte0 - self firstSpecialSelectorBytecodeOffset.
+ 	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was added:
+ ----- Method: SistaCogit>>genSpecialSelectorComparisonWithoutCounters (in category 'bytecode generators') -----
+ genSpecialSelectorComparisonWithoutCounters
+ 	"This method is there because if I put directly the super send in genSpecialSelectorComparison Slang does not correctly translte the code to C, it does not correctly type one of the branchDescriptor to BytecodeDescriptor"
+ 	^ super genSpecialSelectorComparison!

Item was added:
+ ----- Method: SistaCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
+ genSpecialSelectorEqualsEqualsWithForwarders
+ 	"Override to count inlined branches if followed by a conditional branch.
+ 	 We borrow the following conditional branch's counter and when about to
+ 	 inline the comparison we decrement the counter (without writing it back)
+ 	 and if it trips simply abort the inlining, falling back to the normal send which
+ 	 will then continue to the conditional branch which will trip and enter the abort."
+ 	| nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual
+ 	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask |
+ 	<var: #fixup type: #'BytecodeFixup *'>
+ 	<var: #countTripped type: #'AbstractInstruction *'>
+ 	<var: #label type: #'AbstractInstruction *'>
+ 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
+ 	<var: #jumpEqual type: #'AbstractInstruction *'>
+ 	<var: #jumpNotEqual type: #'AbstractInstruction *'>
+ 
+ 	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue:
+ 		[^super genSpecialSelectorEqualsEqualsWithForwarders].
+ 
+ 	regMask := 0.
+ 	
+ 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
+ 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
+ 	
+ 	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
+ 	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
+ 	
+ 	"If an operand is an annotable constant, it may be forwarded, so we need to store it into a 
+ 	register so the forwarder check can jump back to the comparison after unforwarding the constant.
+ 	However, if one of the operand is an unnanotable constant, does not allocate a register for it 
+ 	(machine code will use operations on constants)."
+ 	rcvrReg:= argReg := NoReg.
+ 	self 
+ 		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
+ 		rcvrNeedsReg: unforwardRcvr 
+ 		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
+ 		
+ 	argReg ~= NoReg ifTrue: [ regMask := self registerMaskFor: argReg ].
+ 	rcvrReg ~= NoReg ifTrue: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
+ 	
+ 	"Only interested in inlining if followed by a conditional branch."
+ 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
+ 		[^ self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
+ 	
+ 	"If branching the stack must be flushed for the merge"
+ 	self ssFlushTo: simStackPtr - 2.
+ 	
+ 	unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ].
+ 	unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ].
+ 	
+ 	counterReg := self allocateRegNotConflictingWith: regMask.
+ 	self 
+ 		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
+ 			counterAddress := cAddress. 
+ 			countTripped := countTripBranch ] 
+ 		counterReg: counterReg.
+ 	
+ 	self assert: (unforwardArg or: [ unforwardRcvr ]).
+ 	
+ 	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
+ 	
+ 	self ssPop: 2.
+ 	
+ 	branchDescriptor isBranchTrue 
+ 		ifTrue: 
+ 			[ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC.
+ 			self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. ]
+ 		ifFalse: 
+ 			[ fixup := self ensureNonMergeFixupAt: targetBytecodePC - initialPC.
+ 			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. ].
+ 	
+ 	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
+ 	self Jump: fixup.
+ 	
+ 	countTripped jmpTarget: self Label.
+ 	
+ 	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
+ 	self ssPop: -2. 
+ 	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
+ 	self ssPop: 2. 
+ 	
+ 	"This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. 
+ 	We therefore directly assign the result to TempReg to save one move instruction"
+ 	jumpEqual := self JumpZero: 0.
+ 	self genMoveFalseR: TempReg.
+ 	jumpNotEqual := self Jump: 0.
+ 	jumpEqual jmpTarget: (self genMoveTrueR: TempReg).
+ 	jumpNotEqual jmpTarget: self Label.
+ 	self ssPushRegister: TempReg.
+ 	
+ 	(self fixupAt: nextPC - initialPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ].
+ 	
+ 	^ 0!

Item was added:
+ ----- Method: SistaCogit>>genUnconditionalTrapBytecode (in category 'bytecode generators') -----
+ genUnconditionalTrapBytecode
+ 	"SistaV1: *	217		Trap"
+ 	self ssFlushTo: simStackPtr.
+ 	self CallRT: ceTrapTrampoline.
+ 	self annotateBytecode: self Label.
+ 	^0!

Item was added:
+ ----- Method: SistaCogit>>genUnoptimizedSpecialSelectorComparison (in category 'bytecode generators') -----
+ genUnoptimizedSpecialSelectorComparison
+ 	"This method is there because if I put directly the super send in genSpecialSelectorComparison Slang does not correctly translte the code to C, it does not correctly type one of the branchDescriptor to BytecodeDescriptor"
+ 	^ super genSpecialSelectorComparison!

Item was added:
+ ----- Method: SistaCogit>>generateSistaRuntime (in category 'initialization') -----
+ generateSistaRuntime
+ 	"Trap sends Sista trap message to context with top of stack, so we don't need any arguments..."
+ 	ceTrapTrampoline := self genTrampolineFor: #ceSistaTrap called: 'ceSistaTrapTrampoline'!

Item was added:
+ ----- Method: SistaCogit>>getJumpTargetPCAt: (in category 'method introspection') -----
+ getJumpTargetPCAt: pc
+ 	<api>
+ 	^backEnd jumpTargetPCAt: pc!

Item was added:
+ ----- Method: SistaCogit>>initialize (in category 'initialization') -----
+ initialize
+ 	super initialize.
+ 	branchReachedOnlyForCounterTrip := false.
+ 	cogMethodSurrogateClass := (objectMemory ifNil: [self class objectMemoryClass]) wordSize = 4
+ 										ifTrue: [CogSistaMethodSurrogate32]
+ 										ifFalse: [CogSistaMethodSurrogate64]!

Item was added:
+ ----- Method: SistaCogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress
+ 	initialCounterValue := MaxCounterValue.
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was added:
+ ----- Method: SistaCogit>>maybeAllocAndInitCounters (in category 'compile abstract instructions') -----
+ maybeAllocAndInitCounters
+ 	<inline: true>
+ 	self assert: counters = 0.
+ 	counterIndex := 0.
+ 	numCounters = 0 ifTrue:
+ 		[^true].
+ 	counters := objectRepresentation allocateCounters: numCounters.
+ 	^counters ~= 0!

Item was added:
+ ----- Method: SistaCogit>>maybeFreeCounters (in category 'compile abstract instructions') -----
+ maybeFreeCounters
+ 	<inline: true>
+ 	counters ~= 0 ifTrue:
+ 		[objectRepresentation freeCounters: counters]!

Item was added:
+ ----- Method: SistaCogit>>maybeFreeCountersOf: (in category 'compaction') -----
+ maybeFreeCountersOf: aCogMethod
+ 	"Free any counters in the method."
+ 	<inline: true>
+ 	objectRepresentation freeCounters: aCogMethod counters!

Item was added:
+ ----- Method: SistaCogit>>maybeMarkCountersIn: (in category 'garbage collection') -----
+ maybeMarkCountersIn: cogMethod
+ 	"In SIsta Spur counters are held on the heap in pinned objects which must be marked
+ 	 to avoid them being garbage collected.  This is the hook through which that happens."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<inline: true>
+ 	objectRepresentation maybeMarkCounters: cogMethod counters!

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

Item was added:
+ ----- Method: SistaCogit>>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].
+ 	introspectionDataIndex := counterIndex := 0.
+ 	introspectionData := arrayObj.
+ 	errCode := self
+ 					mapFor: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *')
+ 					bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
+ 					performUntil: #picDataFor:Annotation: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]].
+ 	^introspectionDataIndex!

Item was added:
+ ----- Method: SistaCogit>>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
+ 		performUntil: #picDataFor:Annotation:Mcpc:Bcpc:Method:
+ 		arg: cogMethod asVoidPointer!

Item was added:
+ ----- Method: SistaCogit>>picDataForCounter:at: (in category 'method introspection') -----
+ picDataForCounter: counter at: bcpc
+ 	| executedCount tuple untakenCount |
+ 	<var: #counter type: #'unsigned long'>
+ 	tuple := objectMemory
+ 				eeInstantiateClassIndex: ClassArrayCompactIndex
+ 				format: objectMemory arrayFormat
+ 				numSlots: 3.
+ 	tuple = 0 ifTrue:
+ 		[^0].
+ 	self assert: CounterBytes = 4.
+ 	executedCount := initialCounterValue - (counter >> 16).
+ 	untakenCount := initialCounterValue - (counter bitAnd: 16rFFFF).
+ 	objectMemory
+ 		storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: bcpc);
+ 		storePointerUnchecked: 1 ofObject: tuple withValue: (objectMemory integerObjectOf: executedCount);
+ 		storePointerUnchecked: 2 ofObject: tuple withValue: (objectMemory integerObjectOf: untakenCount).
+ 	^tuple!

Item was added:
+ ----- Method: SistaCogit>>picDataForSendTo:methodClassIfSuper:at:bcpc: (in category 'method introspection') -----
+ picDataForSendTo: cogMethod methodClassIfSuper: methodClassOrNil at: sendMcpc bcpc: sendBcpc
+ 	"Answer a tuple with the send data for a linked send to cogMethod.
+ 	 If the target is a CogMethod (monomorphic send) answer
+ 		{ bytecode pc, inline cache class, target method }
+ 	 If the target is an open PIC (megamorphic send) answer
+ 		{ bytecode pc, nil, send selector }
+ 	If the target is a closed PIC (polymorphic send) answer
+ 		{ bytecode pc, first class, target method, second class, second target method, ... }"
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<var: #sendMcpc type: #'char *'>
+ 	| tuple class |
+ 	tuple := objectMemory
+ 					eeInstantiateClassIndex: ClassArrayCompactIndex
+ 					format: objectMemory arrayFormat
+ 					numSlots: (cogMethod cmType = CMClosedPIC
+ 								ifTrue: [2 * cogMethod cPICNumCases + 1]
+ 								ifFalse: [3]).
+ 	tuple = 0 ifTrue:
+ 		[^0].
+ 	objectMemory storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: sendBcpc).
+ 	cogMethod cmType = CMMethod ifTrue:
+ 		[class := methodClassOrNil ifNil:
+ 					[objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger)].
+ 		 objectMemory
+ 			storePointer: 1 ofObject: tuple withValue: class;
+ 			storePointer: 2 ofObject: tuple withValue: cogMethod methodObject.
+ 		^tuple].
+ 	cogMethod cmType = CMClosedPIC ifTrue:
+ 		[self populate: tuple withPICInfoFor: cogMethod firstCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger).
+ 		^tuple].
+ 	cogMethod cmType = CMOpenPIC ifTrue:
+ 		[objectMemory
+ 			storePointerUnchecked: 1 ofObject: tuple withValue: objectMemory nilObject;
+ 			storePointer: 2 ofObject: tuple withValue: cogMethod selector.
+ 		^tuple].
+ 	self error: 'invalid method type'.
+ 	^0 "to get Slang to type this method as answering sqInt"!

Item was added:
+ ----- Method: SistaCogit>>populate:withPICInfoFor:firstCacheTag: (in category 'method introspection') -----
+ populate: tuple withPICInfoFor: cPIC firstCacheTag: firstCacheTag
+ 	"Populate tuple (which must be large enough) with the ClosedPIC's target method class pairs.
+ 	 The first entry in tuple contains the bytecode pc for the send, so skip the tuple's first field."
+ 	<var: #cPIC type: #'CogMethod *'>
+ 	| pc cacheTag classOop entryPoint targetMethod value |
+ 	<var: #targetMethod type: #'CogMethod *'>
+ 
+ 	1 to: cPIC cPICNumCases do:
+ 		[:i|
+ 		pc := self addressOfEndOfCase: i inCPIC: cPIC.
+ 		cacheTag := i = 1
+ 						ifTrue: [firstCacheTag]
+ 						ifFalse: [backEnd literalBeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize].
+ 		classOop := objectRepresentation classForInlineCacheTag: cacheTag.
+ 		objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.
+ 		entryPoint := i = 1
+ 						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
+ 						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
+ 		"Find target from jump.  A jump to the MNU entry-point should collect #doesNotUnderstand:"
+ 		(cPIC containsAddress: entryPoint)
+ 			ifTrue:
+ 				[value := objectMemory splObj: SelectorDoesNotUnderstand]
+ 			ifFalse:
+ 				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				 self assert: targetMethod cmType = CMMethod.
+ 				 value := targetMethod methodObject].
+ 		objectMemory storePointer: i * 2 ofObject: tuple withValue: value]!

Item was added:
+ ----- Method: SistaCogit>>printPICDataForMethods (in category 'tests') -----
+ printPICDataForMethods
+ 	<doNotGenerate>
+ 	methodZone methodsDo:
+ 		[:cogMethod|
+ 		cogMethod cmType = CMMethod ifTrue:
+ 			[(coInterpreter picDataFor: cogMethod) ifNotNil:
+ 				[:thePicData|
+ 				coInterpreter printOop: thePicData]]]!

Item was added:
+ ----- Method: SistaCogit>>resetCountersIn: (in category 'sista callbacks') -----
+ resetCountersIn: cogMethod
+ 	<doNotGenerate>
+ 	objectRepresentation resetCountersIn: cogMethod!

Item was added:
+ ----- Method: SistaCogit>>scanMethod (in category 'compile abstract instructions') -----
+ scanMethod
+ 	"Scan the method (and all embedded blocks) to determine
+ 		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
+ 		- if the method needs a frame or not
+ 		- what are the targets of any backward branches.
+ 		- how many blocks it creates
+ 		- how many counters it needs/conditional branches it contains
+ 	 Answer the block count or on error a negative error code"
+ 	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
+ 	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	needsFrame := false.
+ 	numFixups := 0.
+ 	prevBCDescriptor := nil.
+ 	numCounters := 0.
+ 	NewspeakVM ifTrue:
+ 		[numIRCs := 0].
+ 	(primitiveIndex > 0
+ 	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
+ 		[^0].
+ 	pc := latestContinuation := initialPC.
+ 	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
+ 	[pc <= endPC] whileTrue:
+ 		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
+ 		 descriptor := self generatorAt: byte0.
+ 		 descriptor isExtension ifTrue:
+ 			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
+ 				[^EncounteredUnknownBytecode].
+ 			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
+ 			 self perform: descriptor generator].
+ 		 (descriptor isReturn
+ 		  and: [pc >= latestContinuation]) ifTrue:
+ 			[endPC := pc].
+ 		 needsFrame ifFalse:
+ 			[(descriptor needsFrameFunction isNil
+ 			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
+ 				ifTrue: [needsFrame := true]
+ 				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
+ 		 descriptor isBranch ifTrue:
+ 			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
+ 			 targetPC := pc + descriptor numBytes + distance.
+ 			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
+ 				ifTrue: [self initializeFixupAt: targetPC - initialPC]
+ 				ifFalse:
+ 					[latestContinuation := latestContinuation max: targetPC.
+ 					numFixups := numFixups + 1.
+ 					 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
+ 						[numCounters := numCounters + 1]]].
+ 		 descriptor isBlockCreation ifTrue:
+ 			[numBlocks := numBlocks + 1.
+ 			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
+ 			 targetPC := pc + descriptor numBytes + distance.
+ 			 latestContinuation := latestContinuation max: targetPC.
+ 			 numFixups := numFixups + 1].
+ 		 NewspeakVM ifTrue:
+ 			[descriptor hasIRC ifTrue:
+ 				[numIRCs := numIRCs + 1]].
+ 		 pc := pc + descriptor numBytes.
+ 		 descriptor isExtension
+ 			ifTrue: [nExts := nExts + 1]
+ 			ifFalse: [nExts := extA := extB := 0].
+ 		 prevBCDescriptor := descriptor].
+ 	^numBlocks!

Item was removed:
- RegisterAllocatingCogit subclass: #SistaStackToRegisterMappingCogit
- 	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue ceTrapTrampoline branchReachedOnlyForCounterTrip'
- 	classVariableNames: 'CounterBytes MaxCounterValue'
- 	poolDictionaries: 'VMSqueakClassIndices'
- 	category: 'VMMaker-JIT'!
- 
- !SistaStackToRegisterMappingCogit commentStamp: 'eem 4/7/2014 12:23' prior: 0!
- A SistaStackToRegisterMappingCogit is a refinement of StackToRegisterMappingCogit that generates code suitable for dynamic optimization by Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Sista is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.
- 
- The basic scheme is that SistaStackToRegisterMappingCogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Sista analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
- 
- SistaStackToRegisterMappingCogit adds counters to conditional branches.  Each branch has an executed and a taken count, implemented at the two 16-bit halves of a single 32-bit word.  Each counter pair is initialized with initialCounterValue.  On entry to the branch the executed count is decremented and if the count goes below zero the ceMustBeBooleanAdd[True|False] trampoline called.  The trampoline distinguishes between true mustBeBoolean and counter trips because in the former the register temporarily holding the counter value will contain zero.  Then the condition is tested, and if the branch is taken the taken count is decremented.  The two counter values allow an optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
- 
- SistaStackToRegisterMappingCogit implements picDataFor:into: that fills an Array with the state of the counters in a method and the state of each linked send in a method.  This is used to implement a primitive used by the optimizer to answer the branch and send data for a method as an Array.
- 
- Instance Variables
- 	counterIndex:			<Integer>
- 	counterMethodCache:	<CogMethod>
- 	counters:				<Array of AbstractInstruction>
- 	initialCounterValue:		<Integer>
- 	numCounters:			<Integer>
- 	picData:				<Integer Oop>
- 	picDataIndex:			<Integer>
- 	prevMapAbsPCMcpc:	<Integer>
- 
- counterIndex
- 	- xxxxx
- 
- counterMethodCache
- 	- xxxxx
- 
- counters
- 	- xxxxx
- 
- initialCounterValue
- 	- xxxxx
- 
- numCounters
- 	- xxxxx
- 
- picData
- 	- xxxxx
- 
- picDataIndex
- 	- xxxxx
- 
- prevMapAbsPCMcpc
- 	- xxxxx
- !

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit class>>additionalHeadersDo: (in category 'translation') -----
- additionalHeadersDo: aBinaryBlock
- 	"Evaluate aBinaryBlock with the names and contents of
- 	 any additional header files that need to be generated."
- 	aBinaryBlock
- 		value: 'cogmethod.h'
- 		value: SistaCogMethod cogMethodHeader!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	^(super ancilliaryClasses: options) copyWith: SistaCogMethod!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit class>>declareCVarsIn: (in category 'translation') -----
- declareCVarsIn: aCodeGen
- 	aCodeGen var: 'counters' type: #usqInt!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit class>>initializeWithOptions: (in category 'class initialization') -----
- initializeWithOptions: optionsDictionary
- 
- 	super initializeWithOptions: optionsDictionary.
- 	CounterBytes := 4.
- 	MaxCounterValue := (1 << 16) - 1!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit class>>numTrampolines (in category 'accessing') -----
- numTrampolines
- 	^super numTrampolines + 1
- 
- 	"Cogit withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
- 	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
- compileBlockBodies
- 	"override to maintain counterIndex when recompiling blocks; sigh."
- 	<inline: false>
- 	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
- 	  initialStackPtr initialOpcodeIndex initialCounterIndex initialIndexOfIRC |
- 	<var: #blockStart type: #'BlockStart *'>
- 	self assert: blockCount > 0.
- 	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
- 	savedNeedsFrame := needsFrame.
- 	savedNumArgs := methodOrBlockNumArgs.
- 	savedNumTemps := methodOrBlockNumTemps.
- 	inBlock := true.
- 	compiledBlocksCount := 0.
- 	[compiledBlocksCount < blockCount] whileTrue:
- 		[blockStart := self blockStartAt: compiledBlocksCount.
- 		 self scanBlock: blockStart.
- 		 initialOpcodeIndex := opcodeIndex.
- 		 initialCounterIndex := counterIndex.
- 		 NewspeakVM ifTrue:
- 			[initialIndexOfIRC := indexOfIRC].
- 		 [self compileBlockEntry: blockStart.
- 		  initialStackPtr := simStackPtr.
- 		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)
- 						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
- 			[^result].
- 		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
- 		   estimated the number of initial nils (because it assumed one or more pushNils to
- 		   produce an operand were pushNils to initialize temps.  This is very rare, so
- 		   compensate by checking, adjusting numInitialNils and recompiling the block body.
- 		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
- 		  initialStackPtr = simStackPtr]
- 			whileFalse:
- 				[self assert: initialStackPtr > simStackPtr.
- 				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
- 				 blockStart fakeHeader dependent: nil.
- 				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
- 					through: blockStart startpc + blockStart span - 1.
- 				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
- 									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
- 					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
- 									[:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].
- 				 opcodeIndex := initialOpcodeIndex.
- 				 counterIndex := initialCounterIndex.
- 				 NewspeakVM ifTrue:
- 					[indexOfIRC := initialIndexOfIRC]].
- 		compiledBlocksCount := compiledBlocksCount + 1].
- 	needsFrame := savedNeedsFrame.
- 	methodOrBlockNumArgs := savedNumArgs.
- 	methodOrBlockNumTemps := savedNumTemps.
- 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>compileCogFullBlockMethod: (in category 'compile abstract instructions') -----
- compileCogFullBlockMethod: numCopied
- 	<option: #SistaV1BytecodeSet>
- 	counters := 0.
- 	^super compileCogFullBlockMethod: numCopied!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>compileCogMethod: (in category 'compile abstract instructions') -----
- compileCogMethod: selector
- 	counters := 0.
- 	^super compileCogMethod: selector!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
- compileFrameBuild
- 	"Override to prefetch counters, if any."
- 	super compileFrameBuild.
- 	counters ~= 0 ifTrue:
- 		[self PrefetchAw: counters]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
- compileFullBlockMethodFrameBuild: numCopied
- 	"Override to prefetch counters if any"
- 	super compileFullBlockMethodFrameBuild: numCopied.
- 	counters ~= 0 ifTrue:
- 		[self PrefetchAw: counters]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>disassembleMethod:on: (in category 'disassembly') -----
- disassembleMethod: surrogateOrAddress on: aStream
- 	<doNotGenerate>
- 	| cogMethod |
- 	cogMethod := super disassembleMethod: surrogateOrAddress on: aStream.
- 	(cogMethod cmType = CMMethod
- 	 and: [cogMethod counters ~= 0]) ifTrue:
- 		[aStream nextPutAll: 'counters:'; cr.
- 		 numCounters := objectRepresentation numCountersFor: counters.
- 		 0 to: numCounters - 1 do:
- 			[:i| | addr |
- 			 addr := i * CounterBytes + counters.
- 			 addr printOn: aStream base: 16.
- 			 aStream nextPut: $:; space.
- 			 (objectMemory longAt: addr) printOn: aStream base: 16.
- 			 aStream cr].
- 		 aStream flush]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>estimateOfAbstractOpcodesPerBytecodes (in category 'accessing') -----
- estimateOfAbstractOpcodesPerBytecodes
- 	"Due to the counter logic, the estimation is higher"
- 	<inline: true>
- 	^ 11!

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

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>fillInCounters:atEndAddress: (in category 'generate machine code') -----
- fillInCounters: nCounters atEndAddress: endAddress
- 	endAddress - (nCounters * CounterBytes)
- 		to: endAddress - CounterBytes
- 		by: CounterBytes
- 		do: [:address|
- 			objectMemory
- 				long32At: address
- 				put: (initialCounterValue << 16 + initialCounterValue)]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>fillInCounters:atStartAddress: (in category 'generate machine code') -----
- fillInCounters: nCounters atStartAddress: startAddress
- 	startAddress
- 		to: startAddress + (nCounters - 1 * CounterBytes)
- 		by: CounterBytes
- 		do: [:address|
- 			objectMemory
- 				long32At: address
- 				put: (initialCounterValue << 16 + initialCounterValue)]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
- fillInMethodHeader: method size: size selector: selector
- 	super fillInMethodHeader: method size: size selector: selector.
- 	self fillInCounters: numCounters atStartAddress: counters.
- 	method counters: counters.
- 	^method!

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

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genCounterTripOnlyJumpIf:to: (in category 'bytecode generator support') -----
- genCounterTripOnlyJumpIf: boolean to: targetBytecodePC 
- 	"Specific version if the branch is only reached while falling through if the counter trips after an inlined #== branch. We do not regenerate the counter logic in this case to avoid 24 bytes instructions."
- 	
- 	<var: #ok type: #'AbstractInstruction *'>
- 	<var: #mustBeBooleanTrampoline type: #'AbstractInstruction *'>
- 
- 	| ok mustBeBooleanTrampoline |
- 
- 	extA := 0.
- 
- 	self ssFlushTo: simStackPtr - 1.
- 	
- 	self ssTop popToReg: TempReg.
- 	
- 	self ssPop: 1.
- 
- 	counterIndex := counterIndex + 1. "counters are increased / decreased in the inlined branch"
- 
- 	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
- 	self ssAllocateRequiredReg: SendNumArgsReg.
- 	self MoveCq: 1 R: SendNumArgsReg.
- 	
- 	"The first time this is reached, it calls necessarily the counter trip for the trampoline because SendNumArgsReg is non zero"
- 	mustBeBooleanTrampoline := self CallRT: (boolean == objectMemory falseObject
- 						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
- 						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
- 
- 	self annotateBytecode: self Label.
- 
- 	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
- 	 Correct result is either 0 or the distance between them.  If result is not 0 or
- 	 their distance send mustBeBoolean."
- 	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
- 	self genSubConstant: boolean R: TempReg.
- 	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
- 
- 	self CmpCq: (boolean == objectMemory falseObject
- 					ifTrue: [objectMemory trueObject - objectMemory falseObject]
- 					ifFalse: [objectMemory falseObject - objectMemory trueObject])
- 		R: TempReg.
- 		
- 	ok := self JumpZero: 0.
- 	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."		
- 
- 	self Jump: mustBeBooleanTrampoline.
- 	
- 	ok jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genExecutionCountLogicInto:counterReg: (in category 'bytecode generator support') -----
- genExecutionCountLogicInto: binaryBlock counterReg: counterReg
- 	<var: #countTripped type: #'AbstractInstruction *'>
- 	<inline: true>
- 	| counterAddress countTripped |
- 	counterAddress := counters + ((self sizeof: #sqInt) * counterIndex).
- 	self flag: 'will need to use MoveAw32:R: if 64 bits'.
- 	self assert: objectMemory wordSize = CounterBytes.
- 	self MoveAw: counterAddress R: counterReg.
- 	self SubCq: 16r10000 R: counterReg. "Count executed"
- 	"If counter trips simply abort the comparison continuing to the following
- 	 branch *without* writing back.  A double decrement will not trip the second time."
- 	countTripped := self JumpCarry: 0.
- 	self MoveR: counterReg Aw: counterAddress. "write back"
- 	binaryBlock value: counterAddress value: countTripped!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'bytecode generators') -----
- genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode
- 	"SistaV1: *	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
- 								
- 	| reg literal distance targetFixUp |
- 	
- 	"We loose the information of in which register is stack top 
- 	when jitting the branch target so we need to flush everything. 
- 	We could use a fixed register here...."
- 	reg := self allocateRegForStackEntryAt: 0.
- 	self ssTop popToReg: reg.
- 	self ssFlushTo: simStackPtr. "flushed but the value is still in reg"
- 	
- 	literal := self getLiteral: (extA * 256 + byte1).
- 	extA := 0.
- 	distance := extB * 256 + byte2.
- 	extB := 0.
- 	
- 	targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'.
- 		
- 	(objectMemory isArrayNonImm: literal)
- 		ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp]
- 		ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp].
- 						
- 	self genPopStackBytecode.
- 	
- 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genFallsThroughCountLogicCounterReg:counterAddress: (in category 'bytecode generator support') -----
- genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress
- 	<inline: true>
- 	"Gen this when the branch has not been taken and forwarders have been followed."
- 	self SubCq: 1 R: counterReg. "Count untaken"
- 	self MoveR: counterReg Aw: counterAddress. "write back"!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
- genJumpIf: boolean to: targetBytecodePC
- 	"The heart of performance counting in Sista.  Conditional branches are 6 times less
- 	 frequent than sends and can provide basic block frequencies (send counters can't).
- 	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
- 	 and a lower half counting untaken executions of the branch.  Executing the branch
- 	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
- 	 decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)
- 	 so that scanning for send and branch data is simplified and that branch data is correct."
- 	<inline: false>
- 	| ok counterAddress countTripped retry nextPC nextDescriptor |
- 	<var: #ok type: #'AbstractInstruction *'>
- 	<var: #retry type: #'AbstractInstruction *'>
- 	<var: #countTripped type: #'AbstractInstruction *'>
- 	<var: #nextDescriptor type: #'AbstractInstruction *'>
- 
- 	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
- 	
- 	branchReachedOnlyForCounterTrip ifTrue: 
- 		[ branchReachedOnlyForCounterTrip := false.
- 		^ self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC ].
- 	
- 	boolean == objectMemory falseObject ifTrue:
- 		[ "detection of and: / or:"
- 		nextPC := bytecodePC + (self generatorAt: byte0) numBytes.
- 		nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.
- 		nextDescriptor generator ==  #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
- 		nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset.
- 		nextDescriptor generator ==  #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].  ].
- 
- 	extA := 0.
- 
- 	self ssFlushTo: simStackPtr - 1.
- 	self ssTop popToReg: TempReg.
- 	self ssPop: 1.
- 
- 	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
- 	self ssAllocateRequiredReg: SendNumArgsReg.
- 
- 	retry := self Label.
- 	self 
- 		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
- 			counterAddress := cAddress. 
- 			countTripped := countTripBranch ] 
- 		counterReg: SendNumArgsReg.
- 	counterIndex := counterIndex + 1.
- 
- 	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
- 	 Correct result is either 0 or the distance between them.  If result is not 0 or
- 	 their distance send mustBeBoolean."
- 	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
- 	self genSubConstant: boolean R: TempReg.
- 	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
- 
- 	self genFallsThroughCountLogicCounterReg: SendNumArgsReg counterAddress: counterAddress.
- 
- 	self CmpCq: (boolean == objectMemory falseObject
- 					ifTrue: [objectMemory trueObject - objectMemory falseObject]
- 					ifFalse: [objectMemory falseObject - objectMemory trueObject])
- 		R: TempReg.
- 	ok := self JumpZero: 0.
- 	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."
- 	
- 	countTripped jmpTarget:
- 		(self CallRT: (boolean == objectMemory falseObject
- 						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
- 						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
- 						
- 	"If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:
- 	 trampoline will return directly to machine code, returning the boolean.  So the code should
- 	 jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."
- 	self annotateBytecode: self Label.
- 
- 	self Jump: retry.
- 	
- 	ok jmpTarget: self Label.
- 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
- genMustBeBooleanTrampolineFor: boolean called: trampolineName
- 	"This can be entered in one of two states, depending on SendNumArgsReg. See
- 	 e.g. genJumpIf:to:.  If SendNumArgsReg is non-zero then this has been entered via
- 	 the initial test of the counter in the jump executed count (i.e. the counter has
- 	 tripped).  In this case TempReg contains the boolean to be tested and should not
- 	 be offset, and ceCounterTripped should be invoked with the unoffset TempReg.
- 	 If SendNumArgsReg is zero then this has been entered for must-be-boolean
- 	 processing. TempReg has been offset by boolean and must be corrected and
- 	 ceSendMustBeBoolean: invoked with the corrected value."
- 	<var: #trampolineName type: #'char *'>
- 	| jumpMBB |
- 	<var: #jumpMBB type: #'AbstractInstruction *'>
- 	<inline: false>
- 	self zeroOpcodeIndex.
- 	self CmpCq: 0 R: SendNumArgsReg.
- 	jumpMBB := self JumpZero: 0.
- 	"Open-code self compileTrampolineFor: #ceCounterTripped: numArgs: 1 arg: TempReg ...
- 	 so we can restore ResultReceiverReg."
- 	self genSmalltalkToCStackSwitch: true.
- 	self
- 		compileCallFor: #ceCounterTripped:
- 		numArgs: 1
- 		arg: TempReg
- 		arg: nil
- 		arg: nil
- 		arg: nil
- 		resultReg: TempReg "(*)"
- 		regsToSave: self emptyRegisterMask.
- 	"(*) For the case where the ceCounterTripped: call returns (e.g. because there's no callback selector
- 	 installed), the call to the ceSendMustBeBooleanAddTrue/FalseTrampoline is followed by a jump
- 	 back to the start of the counter/condition test sequence.  For this case copy the C result to
- 	 TempReg (the register that is tested), to reload it with the boolean to be tested."
- 	backEnd genLoadStackPointers.
- 	backEnd hasLinkRegister ifTrue:
- 		[self PopR: LinkReg].
- 	"To keep ResultReceiverReg live if optStatus thought it was, simply reload it
- 	 from the frame pointer.  This avoids having to reload it in the common case
- 	 (counter does not trip) if it was live.  Note we can't use putSelfInReceiverResultReg
- 	 when generating trampolines because simSelf has not yet been initialized."
- 	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
- 	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
- 	jumpMBB jmpTarget: (self AddCq: boolean R: TempReg).
- 	^self genTrampolineFor: #ceSendMustBeBoolean:
- 		called: trampolineName
- 		numArgs: 1
- 		arg: TempReg
- 		arg: nil
- 		arg: nil
- 		arg: nil
- 		regsToSave: self emptyRegisterMask
- 		pushLinkReg: true
- 		resultReg: NoReg
- 		appendOpcodes: true!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
- genSpecialSelectorComparison
- 	"Override to count inlined branches if followed by a conditional branch.
- 	 We borrow the following conditional branch's counter and when about to
- 	 inline the comparison we decrement the counter (without writing it back)
- 	 and if it trips simply abort the inlining, falling back to the normal send which
- 	 will then continue to the conditional branch which will trip and enter the abort."
- 	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
- 	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB
- 	  counterAddress countTripped counterReg index |
- 	<var: #countTripped type: #'AbstractInstruction *'>
- 	<var: #primDescriptor type: #'BytecodeDescriptor *'>
- 	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
- 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
- 
- 	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ self genSpecialSelectorComparisonWithoutCounters ].
- 
- 	self ssFlushTo: simStackPtr - 2.
- 	primDescriptor := self generatorAt: byte0.
- 	argIsInt := self ssTop type = SSConstant
- 				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
- 	rcvrIsInt := (self ssValue: 1) type = SSConstant
- 				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
- 
- 	"short-cut the jump if operands are SmallInteger constants."
- 	(argIsInt and: [rcvrIsInt]) ifTrue:
- 		[^ self genStaticallyResolvedSpecialSelectorComparison].
- 
- 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
- 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
- 	
- 	"Only interested in inlining if followed by a conditional branch."
- 	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
- 	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
- 	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
- 	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
- 		[inlineCAB := argIsInt or: [rcvrIsInt]].
- 	inlineCAB ifFalse:
- 		[^self genSpecialSelectorSend].
- 
- 	argIsInt
- 		ifTrue:
- 			[(self ssValue: 1) popToReg: ReceiverResultReg.
- 			 self ssPop: 2.
- 			 self MoveR: ReceiverResultReg R: TempReg]
- 		ifFalse:
- 			[self marshallSendArguments: 1.
- 			 self MoveR: Arg0Reg R: TempReg].
- 	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
- 							ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
- 							ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg].
- 
- 	counterReg := self allocateRegNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg).
- 	self 
- 		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
- 			counterAddress := cAddress. 
- 			countTripped := countTripBranch ] 
- 		counterReg: counterReg.
- 
- 	argIsInt
- 		ifTrue: [self CmpCq: argInt R: ReceiverResultReg]
- 		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
- 	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
- 	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
- 	self genConditionalBranch: (branchDescriptor isBranchTrue
- 				ifTrue: [primDescriptor opcode]
- 				ifFalse: [self inverseBranchFor: primDescriptor opcode])
- 		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
- 		
- 	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
- 	
- 	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
- 	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
- 	
- 	argIsInt ifTrue:
- 		[self MoveCq: argInt R: Arg0Reg].
- 	index := byte0 - self firstSpecialSelectorBytecodeOffset.
- 	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparisonWithoutCounters (in category 'bytecode generators') -----
- genSpecialSelectorComparisonWithoutCounters
- 	"This method is there because if I put directly the super send in genSpecialSelectorComparison Slang does not correctly translte the code to C, it does not correctly type one of the branchDescriptor to BytecodeDescriptor"
- 	^ super genSpecialSelectorComparison!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEqualsWithForwarders (in category 'bytecode generators') -----
- genSpecialSelectorEqualsEqualsWithForwarders
- 	"Override to count inlined branches if followed by a conditional branch.
- 	 We borrow the following conditional branch's counter and when about to
- 	 inline the comparison we decrement the counter (without writing it back)
- 	 and if it trips simply abort the inlining, falling back to the normal send which
- 	 will then continue to the conditional branch which will trip and enter the abort."
- 	| nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual
- 	  counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask |
- 	<var: #fixup type: #'BytecodeFixup *'>
- 	<var: #countTripped type: #'AbstractInstruction *'>
- 	<var: #label type: #'AbstractInstruction *'>
- 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
- 	<var: #jumpEqual type: #'AbstractInstruction *'>
- 	<var: #jumpNotEqual type: #'AbstractInstruction *'>
- 
- 	((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue:
- 		[^super genSpecialSelectorEqualsEqualsWithForwarders].
- 
- 	regMask := 0.
- 	
- 	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
- 		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
- 	
- 	unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
- 	unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
- 	
- 	"If an operand is an annotable constant, it may be forwarded, so we need to store it into a 
- 	register so the forwarder check can jump back to the comparison after unforwarding the constant.
- 	However, if one of the operand is an unnanotable constant, does not allocate a register for it 
- 	(machine code will use operations on constants)."
- 	rcvrReg:= argReg := NoReg.
- 	self 
- 		allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg 
- 		rcvrNeedsReg: unforwardRcvr 
- 		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
- 		
- 	argReg ~= NoReg ifTrue: [ regMask := self registerMaskFor: argReg ].
- 	rcvrReg ~= NoReg ifTrue: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ].
- 	
- 	"Only interested in inlining if followed by a conditional branch."
- 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
- 		[^ self genEqualsEqualsNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg].
- 	
- 	"If branching the stack must be flushed for the merge"
- 	self ssFlushTo: simStackPtr - 2.
- 	
- 	unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ].
- 	unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ].
- 	
- 	counterReg := self allocateRegNotConflictingWith: regMask.
- 	self 
- 		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
- 			counterAddress := cAddress. 
- 			countTripped := countTripBranch ] 
- 		counterReg: counterReg.
- 	
- 	self assert: (unforwardArg or: [ unforwardRcvr ]).
- 	
- 	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
- 	
- 	self ssPop: 2.
- 	
- 	branchDescriptor isBranchTrue 
- 		ifTrue: 
- 			[ fixup := self ensureNonMergeFixupAt: postBranchPC - initialPC.
- 			self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. ]
- 		ifFalse: 
- 			[ fixup := self ensureNonMergeFixupAt: targetBytecodePC - initialPC.
- 			self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. ].
- 	
- 	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
- 	self Jump: fixup.
- 	
- 	countTripped jmpTarget: self Label.
- 	
- 	"inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer"
- 	self ssPop: -2. 
- 	self genEqualsEqualsComparisonArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
- 	self ssPop: 2. 
- 	
- 	"This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. 
- 	We therefore directly assign the result to TempReg to save one move instruction"
- 	jumpEqual := self JumpZero: 0.
- 	self genMoveFalseR: TempReg.
- 	jumpNotEqual := self Jump: 0.
- 	jumpEqual jmpTarget: (self genMoveTrueR: TempReg).
- 	jumpNotEqual jmpTarget: self Label.
- 	self ssPushRegister: TempReg.
- 	
- 	(self fixupAt: nextPC - initialPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ].
- 	
- 	^ 0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genUnconditionalTrapBytecode (in category 'bytecode generators') -----
- genUnconditionalTrapBytecode
- 	"SistaV1: *	217		Trap"
- 	self ssFlushTo: simStackPtr.
- 	self CallRT: ceTrapTrampoline.
- 	self annotateBytecode: self Label.
- 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>genUnoptimizedSpecialSelectorComparison (in category 'bytecode generators') -----
- genUnoptimizedSpecialSelectorComparison
- 	"This method is there because if I put directly the super send in genSpecialSelectorComparison Slang does not correctly translte the code to C, it does not correctly type one of the branchDescriptor to BytecodeDescriptor"
- 	^ super genSpecialSelectorComparison!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>generateSistaRuntime (in category 'initialization') -----
- generateSistaRuntime
- 	"Trap sends Sista trap message to context with top of stack, so we don't need any arguments..."
- 	ceTrapTrampoline := self genTrampolineFor: #ceSistaTrap called: 'ceSistaTrapTrampoline'!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>getJumpTargetPCAt: (in category 'method introspection') -----
- getJumpTargetPCAt: pc
- 	<api>
- 	^backEnd jumpTargetPCAt: pc!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>initialize (in category 'initialization') -----
- initialize
- 	super initialize.
- 	branchReachedOnlyForCounterTrip := false.
- 	cogMethodSurrogateClass := (objectMemory ifNil: [self class objectMemoryClass]) wordSize = 4
- 										ifTrue: [CogSistaMethodSurrogate32]
- 										ifFalse: [CogSistaMethodSurrogate64]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress
- 	initialCounterValue := MaxCounterValue.
- 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was removed:
- ----- 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. Evaluate functionSymbol for each mcpc, bcpc pair in the map until the function returns non-zero,
- 	 answering that result, or 0 if it fails to.  This works only for frameful methods"
- 	<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.
- 	self inlineCacheTagsAreIndexes ifTrue:
- 		[enumeratingCogMethod := homeMethod].
- 	"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) * backEnd codeGranularity).
- 				(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) * backEnd codeGranularity)]].
- 		 map := map - 1].
- 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>maybeAllocAndInitCounters (in category 'compile abstract instructions') -----
- maybeAllocAndInitCounters
- 	<inline: true>
- 	self assert: counters = 0.
- 	counterIndex := 0.
- 	numCounters = 0 ifTrue:
- 		[^true].
- 	counters := objectRepresentation allocateCounters: numCounters.
- 	^counters ~= 0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>maybeFreeCounters (in category 'compile abstract instructions') -----
- maybeFreeCounters
- 	<inline: true>
- 	counters ~= 0 ifTrue:
- 		[objectRepresentation freeCounters: counters]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>maybeFreeCountersOf: (in category 'compaction') -----
- maybeFreeCountersOf: aCogMethod
- 	"Free any counters in the method."
- 	<inline: true>
- 	objectRepresentation freeCounters: aCogMethod counters!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>maybeMarkCountersIn: (in category 'garbage collection') -----
- maybeMarkCountersIn: cogMethod
- 	"In SIsta Spur counters are held on the heap in pinned objects which must be marked
- 	 to avoid them being garbage collected.  This is the hook through which that happens."
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<inline: true>
- 	objectRepresentation maybeMarkCounters: cogMethod counters!

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

Item was removed:
- ----- 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:
- 					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 removed:
- ----- 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:
- 		arg: cogMethod asVoidPointer!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>picDataForCounter:at: (in category 'method introspection') -----
- picDataForCounter: counter at: bcpc
- 	| executedCount tuple untakenCount |
- 	<var: #counter type: #'unsigned long'>
- 	tuple := objectMemory
- 				eeInstantiateClassIndex: ClassArrayCompactIndex
- 				format: objectMemory arrayFormat
- 				numSlots: 3.
- 	tuple = 0 ifTrue:
- 		[^0].
- 	self assert: CounterBytes = 4.
- 	executedCount := initialCounterValue - (counter >> 16).
- 	untakenCount := initialCounterValue - (counter bitAnd: 16rFFFF).
- 	objectMemory
- 		storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: bcpc);
- 		storePointerUnchecked: 1 ofObject: tuple withValue: (objectMemory integerObjectOf: executedCount);
- 		storePointerUnchecked: 2 ofObject: tuple withValue: (objectMemory integerObjectOf: untakenCount).
- 	^tuple!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>picDataForSendTo:methodClassIfSuper:at:bcpc: (in category 'method introspection') -----
- picDataForSendTo: cogMethod methodClassIfSuper: methodClassOrNil at: sendMcpc bcpc: sendBcpc
- 	"Answer a tuple with the send data for a linked send to cogMethod.
- 	 If the target is a CogMethod (monomorphic send) answer
- 		{ bytecode pc, inline cache class, target method }
- 	 If the target is an open PIC (megamorphic send) answer
- 		{ bytecode pc, nil, send selector }
- 	If the target is a closed PIC (polymorphic send) answer
- 		{ bytecode pc, first class, target method, second class, second target method, ... }"
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<var: #sendMcpc type: #'char *'>
- 	| tuple class |
- 	tuple := objectMemory
- 					eeInstantiateClassIndex: ClassArrayCompactIndex
- 					format: objectMemory arrayFormat
- 					numSlots: (cogMethod cmType = CMClosedPIC
- 								ifTrue: [2 * cogMethod cPICNumCases + 1]
- 								ifFalse: [3]).
- 	tuple = 0 ifTrue:
- 		[^0].
- 	objectMemory storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: sendBcpc).
- 	cogMethod cmType = CMMethod ifTrue:
- 		[class := methodClassOrNil ifNil:
- 					[objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger)].
- 		 objectMemory
- 			storePointer: 1 ofObject: tuple withValue: class;
- 			storePointer: 2 ofObject: tuple withValue: cogMethod methodObject.
- 		^tuple].
- 	cogMethod cmType = CMClosedPIC ifTrue:
- 		[self populate: tuple withPICInfoFor: cogMethod firstCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger).
- 		^tuple].
- 	cogMethod cmType = CMOpenPIC ifTrue:
- 		[objectMemory
- 			storePointerUnchecked: 1 ofObject: tuple withValue: objectMemory nilObject;
- 			storePointer: 2 ofObject: tuple withValue: cogMethod selector.
- 		^tuple].
- 	self error: 'invalid method type'.
- 	^0 "to get Slang to type this method as answering sqInt"!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>populate:withPICInfoFor:firstCacheTag: (in category 'method introspection') -----
- populate: tuple withPICInfoFor: cPIC firstCacheTag: firstCacheTag
- 	"Populate tuple (which must be large enough) with the ClosedPIC's target method class pairs.
- 	 The first entry in tuple contains the bytecode pc for the send, so skip the tuple's first field."
- 	<var: #cPIC type: #'CogMethod *'>
- 	| pc cacheTag classOop entryPoint targetMethod value |
- 	<var: #targetMethod type: #'CogMethod *'>
- 
- 	1 to: cPIC cPICNumCases do:
- 		[:i|
- 		pc := self addressOfEndOfCase: i inCPIC: cPIC.
- 		cacheTag := i = 1
- 						ifTrue: [firstCacheTag]
- 						ifFalse: [backEnd literalBeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize].
- 		classOop := objectRepresentation classForInlineCacheTag: cacheTag.
- 		objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.
- 		entryPoint := i = 1
- 						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
- 						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
- 		"Find target from jump.  A jump to the MNU entry-point should collect #doesNotUnderstand:"
- 		(cPIC containsAddress: entryPoint)
- 			ifTrue:
- 				[value := objectMemory splObj: SelectorDoesNotUnderstand]
- 			ifFalse:
- 				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
- 				 self assert: targetMethod cmType = CMMethod.
- 				 value := targetMethod methodObject].
- 		objectMemory storePointer: i * 2 ofObject: tuple withValue: value]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>printPICDataForMethods (in category 'tests') -----
- printPICDataForMethods
- 	<doNotGenerate>
- 	methodZone methodsDo:
- 		[:cogMethod|
- 		cogMethod cmType = CMMethod ifTrue:
- 			[(coInterpreter picDataFor: cogMethod) ifNotNil:
- 				[:thePicData|
- 				coInterpreter printOop: thePicData]]]!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>resetCountersIn: (in category 'sista callbacks') -----
- resetCountersIn: cogMethod
- 	<doNotGenerate>
- 	objectRepresentation resetCountersIn: cogMethod!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
- scanMethod
- 	"Scan the method (and all embedded blocks) to determine
- 		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
- 		- if the method needs a frame or not
- 		- what are the targets of any backward branches.
- 		- how many blocks it creates
- 		- how many counters it needs/conditional branches it contains
- 	 Answer the block count or on error a negative error code"
- 	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
- 	<var: #descriptor type: #'BytecodeDescriptor *'>
- 	needsFrame := false.
- 	numFixups := 0.
- 	prevBCDescriptor := nil.
- 	numCounters := 0.
- 	NewspeakVM ifTrue:
- 		[numIRCs := 0].
- 	(primitiveIndex > 0
- 	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
- 		[^0].
- 	pc := latestContinuation := initialPC.
- 	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
- 	[pc <= endPC] whileTrue:
- 		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
- 		 descriptor := self generatorAt: byte0.
- 		 descriptor isExtension ifTrue:
- 			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
- 				[^EncounteredUnknownBytecode].
- 			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
- 			 self perform: descriptor generator].
- 		 (descriptor isReturn
- 		  and: [pc >= latestContinuation]) ifTrue:
- 			[endPC := pc].
- 		 needsFrame ifFalse:
- 			[(descriptor needsFrameFunction isNil
- 			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
- 				ifTrue: [needsFrame := true]
- 				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
- 		 descriptor isBranch ifTrue:
- 			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
- 			 targetPC := pc + descriptor numBytes + distance.
- 			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
- 				ifTrue: [self initializeFixupAt: targetPC - initialPC]
- 				ifFalse:
- 					[latestContinuation := latestContinuation max: targetPC.
- 					numFixups := numFixups + 1.
- 					 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
- 						[numCounters := numCounters + 1]]].
- 		 descriptor isBlockCreation ifTrue:
- 			[numBlocks := numBlocks + 1.
- 			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
- 			 targetPC := pc + descriptor numBytes + distance.
- 			 latestContinuation := latestContinuation max: targetPC.
- 			 numFixups := numFixups + 1].
- 		 NewspeakVM ifTrue:
- 			[descriptor hasIRC ifTrue:
- 				[numIRCs := numIRCs + 1]].
- 		 pc := pc + descriptor numBytes.
- 		 descriptor isExtension
- 			ifTrue: [nExts := nExts + 1]
- 			ifFalse: [nExts := extA := extB := 0].
- 		 prevBCDescriptor := descriptor].
- 	^numBlocks!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
  	| primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result
  	 jumpNotSmallInts jumpContinue index |
+ 	<var: #jumpContinue type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
- 	<var: #jumpContinue type: #'AbstractInstruction *'>
- 	<var: #instToAnnotate type: #'AbstractInstruction *'>
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := (argIsConst := self ssTop type = SSConstant)
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[rcvrInt := objectMemory integerValueOf: rcvrInt.
  		 argInt := objectMemory integerValueOf: argInt.
  		 primDescriptor opcode caseOf: {
  			[AddRR]	-> [result := rcvrInt + argInt].
  			[SubRR]	-> [result := rcvrInt - argInt].
  			[AndRR]	-> [result := rcvrInt bitAnd: argInt].
  			[OrRR]	-> [result := rcvrInt bitOr: argInt] }.
  		(objectMemory isIntegerValue: result) ifTrue:
  			["Must annotate the bytecode for correct pc mapping."
  			^self ssPop: 2; ssPushAnnotatedConstant: (objectMemory integerObjectOf: result)].
  		^self genSpecialSelectorSend].
  
  	"If there's any constant involved other than a SmallInteger don't attempt to inline."
  	((rcvrIsConst and: [rcvrIsInt not])
  	 or: [argIsConst and: [argIsInt not]]) ifTrue:
  		[^self genSpecialSelectorSend].
  
  	"If we know nothing about the types then better not to inline as the inline cache and
  	 primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
  	(argIsInt or: [rcvrIsInt]) ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[self ssFlushTo: simStackPtr - 2.
  			 (self ssValue: 1) popToReg: ReceiverResultReg.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg].
  	jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  							ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
  							ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg].
  	primDescriptor opcode caseOf: {
  		[AddRR] -> [argIsInt
  						ifTrue:
  							[self AddCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self SubCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							jumpContinue := self JumpNoOverflow: 0.
  							"overflow; must undo the damage before continuing"
  							 rcvrIsInt
  								ifTrue: [self MoveCq: rcvrInt R: ReceiverResultReg]
  								ifFalse:
  									[self SubR: Arg0Reg R: ReceiverResultReg.
  									 objectRepresentation genSetSmallIntegerTagsIn: ReceiverResultReg]]].
  		[SubRR] -> [argIsInt
  						ifTrue:
  							[self SubCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
  							 self SubR: Arg0Reg R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							 objectRepresentation genSetSmallIntegerTagsIn: Arg0Reg]].
  		[AndRR] -> [argIsInt
  						ifTrue: [self AndCq: argInt R: ReceiverResultReg]
  						ifFalse: [self AndR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0].
  		[OrRR]	-> [argIsInt
  						ifTrue: [self OrCq: argInt R: ReceiverResultReg]
  						ifFalse: [self OrR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0] }.
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines.
  	jumpContinue jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogSista64VM (in category 'configurations') -----
  generateSqueakSpurCogSista64VM
  	^VMMaker
  		generate: CoInterpreter
+ 		and: SistaCogit
- 		and: SistaStackToRegisterMappingCogit
  		with: #(	SistaVM true
  				ObjectMemory Spur64BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/spursista64src')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogSistaVM (in category 'configurations') -----
  generateSqueakSpurCogSistaVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
+ 		and: SistaCogit
- 		and: SistaStackToRegisterMappingCogit
  		with: #(	SistaVM true
  				ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/spursistasrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!



More information about the Vm-dev mailing list