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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 9 19:17:28 UTC 2014


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

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

Name: VMMaker.oscog-eem.670
Author: eem
Time: 9 April 2014, 12:15:08.933 pm
UUID: 071bf6af-04c0-4256-b053-d66378b73d27
Ancestors: VMMaker.oscog-eem.669

CoInterpreter:
Garbage collect/remap the primTraceLog correctly.  If a GC happens
ver early in start-up the log circular buffer may not be full and the
existing code assumed it always was.

Cogit:
Fix an assert fail in mapFor:bcpc:performUntil:arg: (this for
primitiveClass where the class table reference can be the first
map entry).

Newspeak:
Fix a bug in remapIfObjectRef:pc:hasYoung: with dynamic super
sends which could compute an invalid target method.

Rename pushExplicitOuterSendReceiverBytecode et al to
pushExplicitOuterReceiverBytecode et al.  These are not sends.

Sista:
Fix picDataFor: which must return integers or oops, never nil.
Cope with doubleExtendedDoAnythingBytecodes which /may/ be
sends or not, and hence are problematic for gathering send data.
Generate correct counting code for #==, which implies it can't be
frameless in Sista.
Annotate the right address (the return address of the
ceMustBeBooleanFoo call) in counting genJump:if:.
Sista now starts up a Pharo image and can gather send and branch
data for all methods.

Simulator:
Evaluate the cogit's break block on each bytecode in the
CogVMSimulator.
Add missing ObjectMemory>>ioLoadModule:OfLength:.
Cope more gracefully with not finding an image.

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

Item was changed:
  ----- Method: CoInterpreter>>mapPrimTraceLog (in category 'debug support') -----
  mapPrimTraceLog
  	"The prim trace log is a circular buffer of selectors. If there is
  	 an entry at primTraceLogIndex - 1 \\ PrimTraceBufferSize it has entries.
  	 If there is something at primTraceLogIndex it has wrapped."
  	<inline: false>
+ 	(primTraceLog at: (self safe: primTraceLogIndex - 1 mod: PrimTraceLogSize)) = 0 ifTrue:
+ 		[^self].
- 	| limit |
- 	limit := self safe: primTraceLogIndex - 1 mod: PrimTraceLogSize.
- 	(primTraceLog at: limit) = 0 ifTrue: [^self].
  	(primTraceLog at: primTraceLogIndex) ~= 0 ifTrue:
+ 		[primTraceLogIndex to: PrimTraceLogSize - 1 do:
+ 			[:i| | selector |
+ 			 selector := primTraceLog at: i.
+ 			 (selector ~= 0
+ 			  and: [objectMemory shouldRemapOop: selector]) ifTrue:
+ 				[primTraceLog at: i put: (objectMemory remapObj: selector)]]].
+ 	0 to: primTraceLogIndex - 1 do:
- 		[limit := PrimTraceLogSize - 1].
- 	0 to: limit do:
  		[:i| | selector |
+ 		 selector := primTraceLog at: i.
+ 		 (selector ~= 0
+ 		  and: [objectMemory shouldRemapOop: selector]) ifTrue:
- 		selector := primTraceLog at: i.
- 		(objectMemory shouldRemapOop: selector) ifTrue:
  			[primTraceLog at: i put: (objectMemory remapObj: selector)]]!

Item was changed:
  ----- Method: CoInterpreter>>markAndTracePrimTraceLog (in category 'debug support') -----
  markAndTracePrimTraceLog
  	"The prim trace log is a circular buffer of selectors. If there is
  	 an entry at primTraceLogIndex - 1 \\ PrimTraceBufferSize it has entries.
  	 If there is something at primTraceLogIndex it has wrapped."
  	<inline: false>
+ 	(primTraceLog at: (self safe: primTraceLogIndex - 1 mod: PrimTraceLogSize)) = 0 ifTrue:
+ 		[^self].
- 	| limit |
- 	limit := self safe: primTraceLogIndex - 1 mod: PrimTraceLogSize.
- 	(primTraceLog at: limit) = 0 ifTrue: [^self].
  	(primTraceLog at: primTraceLogIndex) ~= 0 ifTrue:
+ 		[primTraceLogIndex to: PrimTraceLogSize - 1 do:
+ 			[:i| | selector |
+ 			 selector := primTraceLog at: i.
+ 			 (selector ~= 0
+ 			  and: [objectMemory isNonImmediate: selector]) ifTrue:
+ 				[objectMemory markAndTrace: selector]]].
+ 	0 to: primTraceLogIndex - 1 do:
- 		[limit := PrimTraceLogSize - 1].
- 	0 to: limit do:
  		[:i| | selector |
  		selector := primTraceLog at: i.
+ 		(selector ~= 0
+ 		  and: [objectMemory isNonImmediate: selector]) ifTrue:
- 		(objectMemory isImmediate: selector) ifFalse:
  			[objectMemory markAndTrace: selector]]!

Item was changed:
  ----- Method: CoInterpreter>>printPrimLogEntryAt: (in category 'debug support') -----
  printPrimLogEntryAt: i
  	<inline: false>
  	| intOrSelector |
  	intOrSelector := primTraceLog at: i.
  	(objectMemory isImmediate: intOrSelector)
  		ifTrue:
  			[intOrSelector = TraceIncrementalGC ifTrue:
  				[self print: '**IncrementalGC**'. ^nil].
  			 intOrSelector = TraceFullGC ifTrue:
  				[self print: '**FullGC**'. ^nil].
  			 intOrSelector = TraceCodeCompaction ifTrue:
  				[self print: '**CompactCode**'. ^nil].
  			 self print: '???']
  		ifFalse:
+ 			[intOrSelector = 0
+ 				ifTrue: [self printNum: i; print: '!!!!!!']
+ 				ifFalse: [objectMemory safePrintStringOf: intOrSelector]]!
- 			[objectMemory safePrintStringOf: intOrSelector]!

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.
  	nEntries := cogit picDataFor: cogMethod into: data.
  	nEntries = 0 ifTrue:
+ 		[^0].
- 		[^nil].
  	nEntries < nSlots ifTrue:
  		[objectMemory shorten: data toIndexableSize: nEntries].
  	^data!

Item was changed:
  ----- Method: CogVMSimulator>>dispatchOn:in: (in category 'interpreter shell') -----
  dispatchOn: anInteger in: selectorArray
  	"Simulate a case statement via selector table lookup.
  	The given integer must be between 0 and selectorArray size-1, inclusive.
  	For speed, no range test is done, since it is done by the at: operation.
  	Note that, unlike many other arrays used in the Interpreter, this method expect NO CArrayAccessor wrapping - it would duplicate the +1. Maybe this would be better updated to make it all uniform"
+ 	cogit breakBlock ifNotNil:
+ 		[:bb| (bb value: cogit) ifTrue: [self halt: 'breakpoint reached']].
- 
  	self perform: (selectorArray at: (anInteger + 1)).!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize
  	  hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize |
  	"open image file and read the header"
  
- 	["begin ensure block..."
  	f := FileStream readOnlyFileNamed: fileName.
+ 	f ifNil: [^self error: 'no image found'].
+ 
+ 	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
+ 
  	version := self nextLongFrom: f.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getLongFromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getLongFromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [self defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = 40.
  	hdrEdenBytes	:= self getLongFromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = 48.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * BytesPerWord.
  	primTraceLogSize := primTraceLog size * BytesPerWord.
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
  	heapBase := (Cogit guardPageSize
  				+ cogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  	heapSize := dataSize
  				+ extraBytes
  				+ objectMemory newSpaceBytes
  				+ self interpreterAllocationReserveBytes
  				+ (objectMemory hasSpurMemoryManagerAPI
  					ifTrue: [headerSize]
  					ifFalse: [0]).
  	heapBase := objectMemory
  					setHeapBase: heapBase
  					memoryLimit:  heapBase + heapSize
  					endOfMemory: heapBase + dataSize.
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	objectMemory memory: ((cogit processor endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: objectMemory memoryLimit // 4).
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	count ~= dataSize ifTrue: [self halt].
  	]
  		ensure: [f close].
  	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize.
  	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
  	self initializeCodeGenerator!

Item was added:
+ ----- Method: Cogit>>breakBlock (in category 'simulation only') -----
+ breakBlock
+ 	<doNotGenerate>
+ 	^breakBlock!

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.  This works only for frameful methods."
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(char *mcpc, sqInt bcpc, void *arg)'>
  	<var: #arg type: #'void *'>
  	| isInBlock mcpc bcpc endbcpc map mapByte homeMethod aMethodObj result
  	  latestContinuation byte descriptor bsOffset nExts |
  	<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.
  			 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]]]).
- 						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsDisplacementX2N]]).
  			 latestContinuation := startbcpc.
  			 aMethodObj := homeMethod methodObject.
  			 endbcpc := (objectMemory byteLengthOf: 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.
  			 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.
  	mcpc := cogMethod asUnsignedInteger + cogMethod stackCheckOffset.
  	nExts := 0.
  	"The stack check maps to the start of the first bytecode,
  	 the first bytecode being effectively after frame build."
  	result := self perform: functionSymbol
  					with: (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:
  				[| annotation nextBcpc |
  				annotation := mapByte >> AnnotationShift.
  				mcpc := mcpc + (mapByte bitAnd: DisplacementMask).
  				(self isPCMappedAnnotation: annotation alternateInstructionSet: bsOffset > 0) 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]].
  					"All subsequent bytecodes except backward branches map to the
  					 following bytecode. Backward branches map to themselves other-
  					 wise mapping could cause premature breaking out of loops." 
  					result := self perform: functionSymbol
  									with: (self cCoerceSimple: mcpc to: #'char *')
  									with: ((descriptor isBranch
  										   and: [self isBackwardBranch: descriptor at: bcpc exts: nExts in: aMethodObj])
  											ifTrue: [bcpc]
  											ifFalse: [bcpc + descriptor numBytes])
  									with: arg.
  					 result ~= 0 ifTrue:
  						[^result].
  					 bcpc := nextBcpc.
  					 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]]
  			ifFalse:
  				[mcpc := mcpc + (mapByte >= DisplacementX2N
  									ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  									ifFalse: [mapByte])].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- Method: Cogit>>remapIfObjectRef:pc:hasYoung: (in category 'garbage collection') -----
  remapIfObjectRef: annotation pc: mcpc hasYoung: hasYoungPtr
  	<var: #mcpc type: #'char *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
  				[backEnd storeLiteral: mappedLiteral beforeFollowingAddress: mcpc asInteger.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  	(self isSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | mappedCacheTag |
  			 (tagCouldBeObj
  			  and: [objectRepresentation couldBeObject: cacheTag]) ifTrue:
  				[mappedCacheTag := objectRepresentation remapObject: cacheTag.
  				 cacheTag ~= mappedCacheTag ifTrue:
  					[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asInteger.
  					 codeModified := true].
  				 (hasYoungPtr ~= 0
  				  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  			 (self cppIf: NewspeakVM
  					ifTrue: [entryPoint = ceImplicitReceiverTrampoline]
  					ifFalse: [false])
  				ifTrue:
  					[| pc oop mappedOop |
  					 pc := mcpc asInteger + backEnd jumpShortByteSize.
  					 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
  						[mappedOop := objectRepresentation remapOop: oop.
  						 mappedOop ~= oop ifTrue:
  							[backEnd unalignedLongAt: pc put: mappedOop].
  						 (hasYoungPtr ~= 0
  						  and: [objectMemory isYoung: mappedOop]) ifTrue:
  							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true].
  						 pc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
  						 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
  							[mappedOop := objectRepresentation remapOop: oop.
  							 mappedOop ~= oop ifTrue:
  								[backEnd unalignedLongAt: pc put: mappedOop].
  						 (hasYoungPtr ~= 0
  						  and: [objectMemory isYoung: mappedOop]) ifTrue:
  							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]
  				ifFalse:
  					[hasYoungPtr ~= 0 ifTrue:
+ 						["Since the unlinking routines may rewrite the cacheTag to the send's selector, and
- 						[| offset targetMethod |
- 						 "Since the unlinking routines may rewrite the cacheTag to the send's selector, and
  						  since they don't have the cogMethod to hand and can't add it to youngReferrers,
  						  the method must remain in youngReferrers if the targetMethod's selector is young."
  						 entryPoint > methodZoneBase ifTrue: "It's a linked send."
+ 							[self targetMethodAndSendTableFor: entryPoint into:
+ 								[:targetMethod :ignored|
+ 								 (objectMemory isYoung: targetMethod selector) ifTrue:
+ 									[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]]].
- 							[offset := (entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
- 										ifTrue: [cmEntryOffset]
- 										ifFalse: [cmNoCheckEntryOffset].
- 							targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 							(objectMemory isYoung: targetMethod selector) ifTrue:
- 								[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: NewspeakInterpreter class>>initializeBytecodeTable (in category 'initialization') -----
  initializeBytecodeTable
  	"NewspeakInterpreter initializeBytecodeTable"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	self table: BytecodeTable from:
  	#(
  		(  0  15 pushReceiverVariableBytecode)
  		( 16  31 pushTemporaryVariableBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  95 pushLiteralVariableBytecode)
  		( 96 103 storeAndPopReceiverVariableBytecode)
  		(104 111 storeAndPopTemporaryVariableBytecode)
  		(112 pushReceiverBytecode)
  		(113 pushConstantTrueBytecode)
  		(114 pushConstantFalseBytecode)
  		(115 pushConstantNilBytecode)
  		(116 pushConstantMinusOneBytecode)
  		(117 pushConstantZeroBytecode)
  		(118 pushConstantOneBytecode)
  		(119 pushConstantTwoBytecode)
  		(120 returnReceiver)
  		(121 returnTrue)
  		(122 returnFalse)
  		(123 returnNil)
  		(124 returnTopFromMethod)
  		(125 returnTopFromBlock)
  
  		"Newspeak bytecodes"
  		(126 dynamicSuperSendBytecode)
  		(127 pushImplicitReceiverBytecode)
  
  		(128 extendedPushBytecode)
  		(129 extendedStoreBytecode)
  		(130 extendedStoreAndPopBytecode)
  		(131 singleExtendedSendBytecode)
  		(132 doubleExtendedDoAnythingBytecode)
  		(133 singleExtendedSuperBytecode)
  		(134 secondExtendedSendBytecode)
  		(135 popStackBytecode)
  		(136 duplicateTopBytecode)
  		(137 pushActiveContextBytecode)
  
  		"Closure & Newspeak bytecodes"
  		(138 pushNewArrayBytecode)
+ 		(139 pushExplicitOuterReceiverBytecode)
- 		(139 pushExplicitOuterSendReceiverBytecode)
  		(140 pushRemoteTempLongBytecode)
  		(141 storeRemoteTempLongBytecode)
  		(142 storeAndPopRemoteTempLongBytecode)
  		(143 pushClosureCopyCopiedValuesBytecode)
  
  		(144 151 shortUnconditionalJump)
  		(152 159 shortConditionalJump)
  		(160 167 longUnconditionalJump)
  		(168 171 longJumpIfTrue)
  		(172 175 longJumpIfFalse)
  
  		"176-191 were sendArithmeticSelectorBytecode"
  		(176 bytecodePrimAdd)
  		(177 bytecodePrimSubtract)
  		(178 bytecodePrimLessThan)
  		(179 bytecodePrimGreaterThan)
  		(180 bytecodePrimLessOrEqual)
  		(181 bytecodePrimGreaterOrEqual)
  		(182 bytecodePrimEqual)
  		(183 bytecodePrimNotEqual)
  		(184 bytecodePrimMultiply)
  		(185 bytecodePrimDivide)
  		(186 bytecodePrimMod)
  		(187 bytecodePrimMakePoint)
  		(188 bytecodePrimBitShift)
  		(189 bytecodePrimDiv)
  		(190 bytecodePrimBitAnd)
  		(191 bytecodePrimBitOr)	
  
  		"192-207 were sendCommonSelectorBytecode"
  		(192 bytecodePrimAt)
  		(193 bytecodePrimAtPut)
  		(194 bytecodePrimSize)
  		(195 bytecodePrimNext)
  		(196 bytecodePrimNextPut)
  		(197 bytecodePrimAtEnd)
  		(198 bytecodePrimEquivalent)
  		(199 bytecodePrimClass)
  		(200 bytecodePrimBlockCopy)
  		(201 bytecodePrimValue)
  		(202 bytecodePrimValueWithArg)
  		(203 bytecodePrimDo)
  		(204 bytecodePrimNew)
  		(205 bytecodePrimNewWithArg)
  		(206 bytecodePrimPointX)
  		(207 bytecodePrimPointY)
  
  		(208 223 sendLiteralSelector0ArgsBytecode)
  		(224 239 sendLiteralSelector1ArgBytecode)
  		(240 255 sendLiteralSelector2ArgsBytecode)
  	).!

Item was added:
+ ----- Method: NewspeakInterpreter>>pushExplicitOuterReceiverBytecode (in category 'stack bytecodes') -----
+ pushExplicitOuterReceiverBytecode
+ 	"Find the appropriate implicit receiver for outer N"
+ 	|  mClassMixin  litIndex  n anInt |
+ 	<inline: true>
+ 	litIndex := self fetchByte.
+ 	anInt := self literal: litIndex.
+ 	n := self checkedIntegerValueOf: anInt.
+ 	self fetchNextBytecode.
+ 	mClassMixin := self methodClassOf: method.
+ 	self internalPush:(self 
+ 		explicitOuterReceiver: n 
+ 		withObject: receiver 
+ 		withMixin: mClassMixin
+ 		)
+ !

Item was added:
+ ----- Method: ObjectMemory>>ioLoadModule:OfLength: (in category 'simulation') -----
+ ioLoadModule: moduleNameIndex OfLength: moduleLength
+ 	<doNotGenerate>
+ 	<returnTypeC: #'void *'>
+ 	"Dummy - provided by support code"
+ 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushTemporaryVariableBytecode)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(3 126 126 genDynamicSuperSendBytecode isMapped)		"Newspeak"
  		(2 127 127 genPushImplicitReceiverBytecode isMapped)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)
  
+ 		(2 139 139 genPushExplicitOuterReceiverBytecode isMapped)	"Newspeak"
- 		(2 139 139 genPushExplicitOuterSendReceiverBytecode isMapped)	"Newspeak"
  
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 197 genSpecialSelectorSend isMapped)
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped)
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtPushPseudoVariableOrOuterBytecode (in category 'bytecode generators') -----
  genExtPushPseudoVariableOrOuterBytecode
  	"77			01001101		Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]"
  	| ext |
  	ext := extB.
  	extB := 0.
  	ext caseOf: {
  		[0]	->	[^self genPushLiteral: objectMemory falseObject].
  		[1]	->	[^self genPushLiteral: objectMemory trueObject].
  		[2]	->	[^self genPushLiteral: objectMemory nilObject].
  		[3]	->	[^self genPushActiveContextBytecode]
  		}
  		otherwise:
  			[ext < 0 ifTrue:
+ 				[^self genPushExplicitOuterReceiver: 0 - ext].
- 				[^self genPushExplicitOuterSendReceiver: 0 - ext].
  			 self warning: 'undefined extension for extPushPseudoVariableOrOuter'.
  			 ^self unknownBytecode].
  	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPushExplicitOuterReceiver: (in category 'bytecode generators') -----
+ genPushExplicitOuterReceiver: level
+ 	"Uncached push explicit outer send receiver"
+ 	self assert: needsFrame. "because this should always be followed by a send"
+ 	self MoveCq: level R: SendNumArgsReg.
+ 	self CallRT: ceExplicitReceiverTrampoline.
+ 	self PushR: ReceiverResultReg.
+ 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPushExplicitOuterReceiverBytecode (in category 'bytecode generators') -----
+ genPushExplicitOuterReceiverBytecode
+ 	"Uncached push explicit outer send receiver"
+ 	| levelOop |
+ 	levelOop := self getLiteral: byte1.
+ 	self assert: (objectMemory isIntegerObject: levelOop).
+ 	^self genPushExplicitOuterReceiver: (objectMemory integerValueOf: levelOop)!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushExplicitOuterSendReceiver: (in category 'bytecode generators') -----
- genPushExplicitOuterSendReceiver: level
- 	"Uncached push explicit outer send receiver"
- 	self assert: needsFrame. "because this should always be followed by a send"
- 	self MoveCq: level R: SendNumArgsReg.
- 	self CallRT: ceExplicitReceiverTrampoline.
- 	self PushR: ReceiverResultReg.
- 	^0!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genPushExplicitOuterSendReceiverBytecode (in category 'bytecode generators') -----
- genPushExplicitOuterSendReceiverBytecode
- 	"Uncached push explicit outer send receiver"
- 	| levelOop |
- 	levelOop := self getLiteral: byte1.
- 	self assert: (objectMemory isIntegerObject: levelOop).
- 	^self genPushExplicitOuterSendReceiver: (objectMemory integerValueOf: levelOop)!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit class>>generatorTableFrom: (in category 'class initialization') -----
+ generatorTableFrom: anArray
+ 	"Override to replace the unmapped, non-counting inlined #== with a mapped counting inlined #==."
+ 	| table |
+ 	table := super generatorTableFrom: anArray.
+ 	table object do:
+ 		[:descriptor|
+ 		 descriptor generator == #genSpecialSelectorEqualsEquals ifTrue:
+ 			[descriptor
+ 				isMapped: true;
+ 				isMappedInBlock: true;
+ 				needsFrameFunction: nil]].
+ 	^table!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generators') -----
  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>
  	| desc ok counter countTripped retry |
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	<var: #counter type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	desc popToReg: TempReg.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counter := self addressOf: (counters at: counterIndex).
  	counterIndex := counterIndex + 1.
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: BytesPerWord = CounterBytes.
  	retry := counter addDependent: (self annotateAbsolutePCRef:
  				(self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"Don't write back if we trip; avoids wrapping count back to initial value, and if we trip we don't execute."
  	countTripped := self JumpCarry: 0.
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	"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 annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	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 SendNumArgsReg 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.
  	 This is always the point at which the boolean is tested. The register to be tested must be reloaded with
  	 the return value of the trampoline, if it differs from cResultRegister.
  
  	 In images with the Sista code loaded, return must be via backing up the PC to after the send, and returning
  	 (this time answering the boolean via ReceiverResultReg).  For this case, and for normal mustBeBoolean
+ 	 processing, the return address of the mustBeBoolean trampoline call must be annotated as a bytecode pc."
+ 	self annotateBytecode: self Label.
+ 	backEnd cResultRegister ~= TempReg ifTrue:
+ 		[self MoveR: backEnd cResultRegister R: TempReg].
+ 	self Jump: retry.
- 	 processing, the instruction after the mustBeBoolean trampoline must be annotated as having a bytecode pc."
- 	backEnd cResultRegister ~= TempReg
- 		ifTrue:
- 			[self annotateBytecode: (self MoveR: backEnd cResultRegister R: TempReg).
- 			 self Jump: retry]
- 		ifFalse:
- 			[self annotateBytecode: (self Jump: retry)].
  	ok jmpTarget: self Label.
  	^0!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
+ genSpecialSelectorEqualsEquals
+ 	"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 nExts
+ 	  counter countTripped |
+ 	<var: #primDescriptor type: #'BytecodeDescriptor *'>
+ 	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
+ 	<var: #counter type: #'AbstractInstruction *'>
+ 	<var: #countTripped type: #'AbstractInstruction *'>
+ 	self ssFlushTo: simStackPtr - 2.
+ 	primDescriptor := self generatorAt: byte0.
+ 
+ 	nextPC := bytecodePC + primDescriptor numBytes.
+ 	nExts := 0.
+ 	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
+ 	 branchDescriptor isExtension] whileTrue:
+ 		[nExts := nExts + 1.
+ 		 nextPC := nextPC + branchDescriptor numBytes].
+ 	"Only interested in inlining if followed by a conditional branch."
+ 	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
+ 		[^self genSpecialSelectorSend].
+ 
+ 	targetBytecodePC := nextPC
+ 							+ branchDescriptor numBytes
+ 							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
+ 	postBranchPC := nextPC + branchDescriptor numBytes.
+ 	self marshallSendArguments: 1.
+ 
+ 	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
+ 	counter := self addressOf: (counters at: counterIndex).
+ 	self flag: 'will need to use MoveAw32:R: if 64 bits'.
+ 	self assert: BytesPerWord = CounterBytes.
+ 	counter addDependent: (self annotateAbsolutePCRef:
+ 		(self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
+ 	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
+ 	"If counter trips simply abort the inlined comparison and send continuing to the following
+ 	 branch *without* writing back.  A double decrement will not trip the second time."
+ 	countTripped := self JumpCarry: 0.
+ 	counter addDependent: (self annotateAbsolutePCRef:
+ 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
+ 
+ 	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 gen: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
+ 		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+ 	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
+ 	counter addDependent: (self annotateAbsolutePCRef:
+ 		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
+ 	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
+ 	countTripped jmpTarget: self Label.
+ 	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
+ 		numArgs: 1!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>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.  This works only for frameful methods."
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(BytecodeDescriptor * desc, char *mcpc, sqInt bcpc, void *arg)'>
  	<var: #arg type: #'void *'>
  	| isInBlock mcpc bcpc endbcpc map mapByte homeMethod aMethodObj result
  	  latestContinuation byte descriptor bsOffset nExts |
  	<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.
  			 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]]]).
- 						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsDisplacementX2N]]).
  			 latestContinuation := startbcpc.
  			 aMethodObj := homeMethod methodObject.
  			 endbcpc := (objectMemory byteLengthOf: 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.
  			 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.
  	mcpc := cogMethod asUnsignedInteger + cogMethod stackCheckOffset.
  	nExts := 0.
  	"as a hack for collecting counters, remember the prev mcpc in a static variable."
  	prevMapAbsPCMcpc := 0.
  	"The stack check maps to the start of the first bytecode,
  	 the first bytecode being effectively after frame build."
  	result := self perform: functionSymbol
  					with: nil
  					with: (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:
  				[| annotation nextBcpc |
  				annotation := mapByte >> AnnotationShift.
  				mcpc := mcpc + (mapByte bitAnd: DisplacementMask).
  				(self isPCMappedAnnotation: annotation alternateInstructionSet: bsOffset > 0) 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]].
  					"All subsequent bytecodes except backward branches map to the
  					 following bytecode. Backward branches map to themselves other-
  					 wise mapping could cause premature breaking out of loops." 
  					result := self perform: functionSymbol
  									with: descriptor
  									with: (self cCoerceSimple: mcpc to: #'char *')
  									with: ((descriptor isBranch
  										   and: [self isBackwardBranch: descriptor at: bcpc exts: nExts in: aMethodObj])
  											ifTrue: [bcpc]
  											ifFalse: [bcpc + descriptor numBytes])
  									with: arg.
  					 result ~= 0 ifTrue:
  						[^result].
  					 bcpc := nextBcpc.
  					 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  				annotation = IsAbsPCReference ifTrue:
  					[self assert: mcpc ~= 0.
  					 prevMapAbsPCMcpc := mcpc]]
  			ifFalse:
  				[mcpc := mcpc + (mapByte >= DisplacementX2N
  									ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  									ifFalse: [mapByte])].
  		 map := map - 1].
  	^0!

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

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"StackInterpreter initializeBytecodeTableForNewspeakV3PlusClosures"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	self table: BytecodeTable from:
  	#(
  		(  0  15 pushReceiverVariableBytecode)
  		( 16  31 pushTemporaryVariableBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  95 pushLiteralVariableBytecode)
  		( 96 103 storeAndPopReceiverVariableBytecode)
  		(104 111 storeAndPopTemporaryVariableBytecode)
  		(112 pushReceiverBytecode)
  		(113 pushConstantTrueBytecode)
  		(114 pushConstantFalseBytecode)
  		(115 pushConstantNilBytecode)
  		(116 pushConstantMinusOneBytecode)
  		(117 pushConstantZeroBytecode)
  		(118 pushConstantOneBytecode)
  		(119 pushConstantTwoBytecode)
  		(120 returnReceiver)
  		(121 returnTrue)
  		(122 returnFalse)
  		(123 returnNil)
  		(124 returnTopFromMethod)
  		(125 returnTopFromBlock)
  
  		"2 of the 3 Newspeak bytecodes"
  		(126 dynamicSuperSendBytecode)
  		(127 pushImplicitReceiverBytecode)
  
  		(128 extendedPushBytecode)
  		(129 extendedStoreBytecode)
  		(130 extendedStoreAndPopBytecode)
  		(131 singleExtendedSendBytecode)
  		(132 doubleExtendedDoAnythingBytecode)
  		(133 singleExtendedSuperBytecode)
  		(134 secondExtendedSendBytecode)
  		(135 popStackBytecode)
  		(136 duplicateTopBytecode)
  
  		(137 pushActiveContextBytecode)
  		(138 pushNewArrayBytecode)
  
  		"The last of 3 Newspeak bytecodes"
+ 		(139 pushExplicitOuterReceiverBytecode)
- 		(139 pushExplicitOuterSendReceiverBytecode)
  
  		(140 pushRemoteTempLongBytecode)
  		(141 storeRemoteTempLongBytecode)
  		(142 storeAndPopRemoteTempLongBytecode)
  		(143 pushClosureCopyCopiedValuesBytecode)
  
  		(144 151 shortUnconditionalJump)
  		(152 159 shortConditionalJumpFalse)
  		(160 167 longUnconditionalJump)
  		(168 171 longJumpIfTrue)
  		(172 175 longJumpIfFalse)
  
  		"176-191 were sendArithmeticSelectorBytecode"
  		(176 bytecodePrimAdd)
  		(177 bytecodePrimSubtract)
  		(178 bytecodePrimLessThan)
  		(179 bytecodePrimGreaterThan)
  		(180 bytecodePrimLessOrEqual)
  		(181 bytecodePrimGreaterOrEqual)
  		(182 bytecodePrimEqual)
  		(183 bytecodePrimNotEqual)
  		(184 bytecodePrimMultiply)
  		(185 bytecodePrimDivide)
  		(186 bytecodePrimMod)
  		(187 bytecodePrimMakePoint)
  		(188 bytecodePrimBitShift)
  		(189 bytecodePrimDiv)
  		(190 bytecodePrimBitAnd)
  		(191 bytecodePrimBitOr)
  
  		"192-207 were sendCommonSelectorBytecode"
  		(192 bytecodePrimAt)
  		(193 bytecodePrimAtPut)
  		(194 bytecodePrimSize)
  		(195 bytecodePrimNext)
  		(196 bytecodePrimNextPut)
  		(197 bytecodePrimAtEnd)
  		(198 bytecodePrimIdentical)
  		(199 bytecodePrimClass)
  		(200 bytecodePrimSpecialSelector24)
  		(201 bytecodePrimValue)
  		(202 bytecodePrimValueWithArg)
  		(203 bytecodePrimDo)
  		(204 bytecodePrimNew)
  		(205 bytecodePrimNewWithArg)
  		(206 bytecodePrimPointX)
  		(207 bytecodePrimPointY)
  
  		(208 223 sendLiteralSelector0ArgsBytecode)
  		(224 239 sendLiteralSelector1ArgBytecode)
  		(240 255 sendLiteralSelector2ArgsBytecode)
  	)!

Item was added:
+ ----- Method: StackInterpreter>>pushExplicitOuterReceiverBytecode (in category 'stack bytecodes') -----
+ pushExplicitOuterReceiverBytecode
+ 	"Find the appropriate implicit receiver for outer N"
+ 	| litIndex  n anIntOop |
+ 	<inline: true>
+ 	litIndex := self fetchByte.
+ 	anIntOop := self literal: litIndex.
+ 	n := (objectMemory isIntegerObject: anIntOop)
+ 			ifTrue: [objectMemory integerValueOf: anIntOop]
+ 			ifFalse: [0].
+ 	self fetchNextBytecode.
+ 	self internalPush:(self 
+ 						explicitOuterReceiver: n 
+ 						withObject: self receiver 
+ 						withMixin: (self methodClassOf: method))!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"StackInterpreterSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags heapBase firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize |
  	"open image file and read the header"
  
- 	["begin ensure block..."
  	f := FileStream readOnlyFileNamed: fileName.
+ 	f ifNil: [^self error: 'no image found'].
+ 
+ 	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
+ 
  	version := self nextLongFrom: f.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getLongFromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getLongFromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 It is used for the cog code size in Cog.  Preserve it to be polite to other VMs."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = 40.
  	hdrEdenBytes		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory edenBytes: (hdrEdenBytes = 0
  							ifTrue: [objectMemory defaultEdenBytes]
  							ifFalse: [hdrEdenBytes]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = 48.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"allocate interpreter memory"
  	heapBase := objectMemory startOfMemory.
  	heapSize := dataSize
  				+ extraBytes
  				+ objectMemory newSpaceBytes
  				+ self interpreterAllocationReserveBytes
  				+ (objectMemory hasSpurMemoryManagerAPI
  					ifTrue: [headerSize]
  					ifFalse: [0]).
  	objectMemory
  		setHeapBase: heapBase
  		memoryLimit: heapBase + heapSize
  		endOfMemory: heapBase + dataSize. "bogus for Spur"
  	objectMemory memory: (Bitmap new: objectMemory memoryLimit // 4).
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	count ~= dataSize ifTrue: [self halt].
  	]
  		ensure: [f close].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities informUser: 'Relocating object pointers...'
  				during: [self initializeInterpreter: bytesToShift].
  !

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	isPushNilFunction := #v3:Is:Push:Nil:.
  	pushNilSizeFunction := #v3PushNilSize:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(3 126 126 genDynamicSuperSendBytecode isMapped)		"Newspeak"
  		(2 127 127 genPushImplicitReceiverBytecode isMapped)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)
  
+ 		(2 139 139 genPushExplicitOuterReceiverBytecode isMapped)	"Newspeak"
- 		(2 139 139 genPushExplicitOuterSendReceiverBytecode isMapped)	"Newspeak"
  
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>newInitializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  newInitializeBytecodeTableForNewspeakV3PlusClosures
  	"StackToRegisterMappingCogit newInitializeBytecodeTableForNewspeakV3PlusClosures"
  
  	isPushNilFunction := #v3:Is:Push:Nil:.
  	pushNilSizeFunction := #v3PushNilSize:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(3 126 126 genDynamicSuperSendBytecode isMapped)		"Newspeak"
  		(2 127 127 genPushImplicitReceiverBytecode isMapped)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)
  
+ 		(2 139 139 genPushExplicitOuterReceiverBytecode isMapped)	"Newspeak"
- 		(2 139 139 genPushExplicitOuterSendReceiverBytecode isMapped)	"Newspeak"
  
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPushExplicitOuterReceiver: (in category 'bytecode generators') -----
+ genPushExplicitOuterReceiver: level
+ 	"Uncached push explicit outer send receiver"
+ 	self assert: needsFrame. "because this should always be followed by a send"
+ 	optStatus isReceiverResultRegLive: false.
+ 	self ssAllocateCallReg: SendNumArgsReg.
+ 	self MoveCq: level R: SendNumArgsReg.
+ 	self CallRT: ceExplicitReceiverTrampoline.
+ 	^self ssPushRegister: ReceiverResultReg!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPushExplicitOuterSendReceiver: (in category 'bytecode generators') -----
- genPushExplicitOuterSendReceiver: level
- 	"Uncached push explicit outer send receiver"
- 	self assert: needsFrame. "because this should always be followed by a send"
- 	optStatus isReceiverResultRegLive: false.
- 	self ssAllocateCallReg: SendNumArgsReg.
- 	self MoveCq: level R: SendNumArgsReg.
- 	self CallRT: ceExplicitReceiverTrampoline.
- 	^self ssPushRegister: ReceiverResultReg!



More information about the Vm-dev mailing list