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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 14 17:49:53 UTC 2016


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

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

Name: VMMaker.oscog-eem.1803
Author: eem
Time: 14 April 2016, 10:48:07.170501 am
UUID: e0d388d5-d8fa-4752-ac00-a33f5b8d3f1c
Ancestors: VMMaker.oscog-cb.1802

JIT and execution-time support for full block closures.  Use the old cpicHasMNUFlag in CMMethod to mark full block code, hence renaming the flag to cpicHasMNUCaseOrCMIsFullBlock.  Provide isVanillaBlockClosure: to ditinguish between standard and full block closures.  Use it in makeBaseFrameFor:.  Fix a bug with the methodLabel remembering the "is block activation" flag from previous full block compilations, clearing the offset in preenMethodLabel.  Update CogMethod header printing to print the cpicHasMNUCase or cmIsFullBlock state.  Add pool vars for the names of the bytecode sets (SistaV1BytecodeSet et al) to allow them to be tested in code, not merely in <option:> pragmas.

The first full block closure example works, but there's at least a bug with young methods if the second example is run without AssemblerMethod implementing pushFullClosure:numCopied:.

=============== Diff against VMMaker.oscog-cb.1802 ===============

Item was changed:
  ----- Method: CoInterpreter>>convertToMachineCodeFrame:bcpc: (in category 'frame access') -----
  convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
  	<var: #cogHomeMethod type: #'CogMethod *'>
  	<returnTypeC: #usqInt>
  	"Convert the current interpreter frame into a machine code frame
  	 and answer the machine code pc matching bcpc."
  	| startBcpc methodField closure cogMethod pc |
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #p type: #'char *'>
  	self assert: (self isMachineCodeFrame: framePointer) not.
  	"Update the return pc, perhaps saving it in the caller's iframeSavedIP."
  	(self isBaseFrame: framePointer)
  		ifTrue:
  			[stackPages
  				longAt: framePointer + FoxCallerSavedIP
  				put: cogit ceBaseFrameReturnPC]
  		ifFalse:
  			[(self isMachineCodeFrame: (self frameCallerFP: framePointer)) ifFalse:
  				[self iframeSavedIP: (self frameCallerFP: framePointer)
  					put: (self frameCallerSavedIP: framePointer) asInteger.
  				 stackPages
  					longAt: framePointer + FoxCallerSavedIP
  					put: cogit ceReturnToInterpreterPC]].
  	"Compute the cog method field"
  	(self iframeIsBlockActivation: framePointer)
  		ifTrue:
  			[closure := self pushedReceiverOrClosureOfFrame: framePointer.
+ 			 (self isVanillaBlockClosure: closure)
+ 				ifTrue:
+ 					[startBcpc := self startPCOfClosure: closure.
+ 					 cogMethod := cogit
+ 										findMethodForStartBcpc: startBcpc
+ 										inHomeMethod: cogHomeMethod]
+ 				ifFalse:
+ 					[startBcpc := self startPCOfMethodHeader: cogHomeMethod methodHeader.
+ 					 cogMethod := self cCoerceSimple: cogHomeMethod to: #'CogBlockMethod *'].
- 			 startBcpc := self startPCOfClosure: closure.
- 			 cogMethod := cogit
- 								findMethodForStartBcpc: startBcpc
- 								inHomeMethod: cogHomeMethod.
  			 methodField := cogMethod asInteger + MFMethodFlagIsBlockFlag]
  		ifFalse:
  			[startBcpc := self startPCOfMethodHeader: cogHomeMethod methodHeader.
  			 cogMethod := self cCoerceSimple: cogHomeMethod to: #'CogBlockMethod *'.
  			 methodField := cogHomeMethod asInteger].
  	"compute the pc before converting the frame to help with debugging."
  	pc := cogit mcPCForBackwardBranch: bcpc startBcpc: startBcpc in: cogMethod.
  	self assert: pc > (cogMethod asUnsignedInteger + cogit noCheckEntryOffset).
  	self assert: bcpc = (cogit bytecodePCFor: pc startBcpc: startBcpc in: cogMethod).
  	"now convert to a machine code frame"
  	stackPages
  		longAt: framePointer + FoxMethod
  		put: methodField
  			+ ((self iframeHasContext: framePointer)
  				ifTrue: [MFMethodFlagHasContextFlag]
  				ifFalse: [0]).
  	framePointer + FoxIFReceiver to: stackPointer by: objectMemory wordSize negated do:
  		[:p|
  		stackPages longAt: p + FoxMFReceiver - FoxIFReceiver put: (stackPages longAt: p)].
  	stackPointer := stackPointer + FoxMFReceiver - FoxIFReceiver.
  	^pc!

Item was changed:
  ----- Method: CoInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page.  Override to
  	 hold the caller context in a different place,  In the StackInterpreter we use
  	 the caller saved ip, but in the Cog VM caller saved ip is the ceBaseReturn:
  	 trampoline.  Simply hold the caller context in the first word of the stack."
  	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	"theIP must be typed as signed because it is assigned ceCannotResumePC and so maybe implicitly typed as unsigned."
  	<var: #theIP type: #sqInt>
  	self assert: (objectMemory isContext: aContext).
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	self assert: HasBeenReturnedFromMCPC < 0.
  	theIP := (objectMemory isIntegerObject: theIP)
  				ifTrue: [objectMemory integerValueOf: theIP]
  				ifFalse: [HasBeenReturnedFromMCPC].
  	theMethod := objectMemory followObjField: MethodIndex ofObject: aContext.
  	page := stackPages newStackPage.
  	"first word on stack is caller context of base frame"
  	stackPages
  		longAt: (pointer := page baseAddress)
  		put: (objectMemory followObjField: SenderIndex ofObject: aContext).
  	"second word is the context itself; needed for cannotReturn processing; see ceBaseReturn:."
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: aContext.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receive the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[(objectMemory isForwarded: maybeClosure) ifTrue:
  				[maybeClosure := objectMemory fixFollowedField: ClosureIndex ofObject: aContext withInitialValue: maybeClosure].
  			 numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := objectMemory methodHeaderOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  			 ((self methodHeaderHasPrimitive: header)
  			  and: [theIP = (1 + (objectMemory lastPointerOfMethodHeader: header))]) ifTrue:
  				[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)].
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is base return trampoline"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: cogit ceBaseFrameReturnPC.
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: 0.
  	"N.B.  Don't set the baseFP, which marks the page as in use, until after
  	 ensureMethodIsCogged: and/or instructionPointer:forContext:frame:. These
  	 can cause a compiled code compaction which, if marked as in use, will
  	 examine this partially initialized page and crash."
  	page headFP: pointer.
  	"Create either a machine code frame or an interpreter frame based on the pc.  If the pc is -ve
  	 it is a machine code pc and so we produce a machine code frame.  If +ve an interpreter frame.
  	 N.B. Do *not* change this to try and map from a bytecode pc to a machine code frame under
  	 any circumstances.  See ensureContextIsExecutionSafeAfterAssignToStackPointer:"
  	theIP < 0
  		ifTrue:
  			[| cogMethod |
  			 "Since we would have to generate a machine-code method to be able to map
  			  the native pc anyway we should create a native method and native frame."
  			 cogMethod := self ensureMethodIsCogged: theMethod.
  			 theMethod := cogMethod asInteger.
  			 maybeClosure ~= objectMemory nilObject
  				ifTrue:
+ 					[(self isVanillaBlockClosure: maybeClosure)
- 					["If the pc is the special HasBeenReturnedFromMCPC pc set the pc
- 					  appropriately so that the frame stays in the cannotReturn: state."
- 					 theIP = HasBeenReturnedFromMCPC
  						ifTrue:
+ 							["If the pc is the special HasBeenReturnedFromMCPC pc set the pc
+ 							  appropriately so that the frame stays in the cannotReturn: state."
+ 							 theIP = HasBeenReturnedFromMCPC
+ 								ifTrue:
+ 									[theMethod := (cogit findMethodForStartBcpc: (self startPCOfClosure: maybeClosure)
+ 														inHomeMethod: (self cCoerceSimple: theMethod
+ 																			to: #'CogMethod *')) asInteger.
+ 									 theMethod = 0 ifTrue:
+ 										[self error: 'cannot find machine code block matching closure''s startpc'].
+ 									 theIP := cogit ceCannotResumePC]
+ 								ifFalse:
+ 									[self assert: (theIP signedBitShift: -16) < -1. "See contextInstructionPointer:frame:"
+ 									 theMethod := theMethod - ((theIP signedBitShift: -16) * cogit blockAlignment).
+ 									 theIP := theMethod - theIP signedIntFromShort]]
- 							[theMethod := (cogit findMethodForStartBcpc: (self startPCOfClosure: maybeClosure)
- 												inHomeMethod: (self cCoerceSimple: theMethod
- 																	to: #'CogMethod *')) asInteger.
- 							 theMethod = 0 ifTrue:
- 								[self error: 'cannot find machine code block matching closure''s startpc'].
- 							 theIP := cogit ceCannotResumePC]
  						ifFalse:
+ 							[self assert: (theIP signedBitShift: -16) >= -1.
+ 							 "If the pc is the special HasBeenReturnedFromMCPC pc set the pc
+ 							  appropriately so that the frame stays in the cannotReturn: state."
+ 							 theIP := theIP = HasBeenReturnedFromMCPC
+ 										ifTrue: [cogit ceCannotResumePC]
+ 										ifFalse: [theMethod asInteger - theIP]].
- 							[self assert: (theIP signedBitShift: -16) < -1. "See contextInstructionPointer:frame:"
- 							 theMethod := theMethod - ((theIP signedBitShift: -16) * cogit blockAlignment).
- 							 theIP := theMethod - theIP signedIntFromShort].
  					 stackPages
  						longAt: (pointer := pointer - objectMemory wordSize)
  						put: theMethod + MFMethodFlagHasContextFlag + MFMethodFlagIsBlockFlag]
  				ifFalse:
  					[self assert: (theIP signedBitShift: -16) >= -1.
  					 "If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP := theIP = HasBeenReturnedFromMCPC
  								ifTrue: [cogit ceCannotResumePC]
  								ifFalse: [theMethod asInteger - theIP].
  					 stackPages
  						longAt: (pointer := pointer - objectMemory wordSize)
  						put: theMethod + MFMethodFlagHasContextFlag].
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: aContext]
  		ifFalse:
  			[stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: theMethod.
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: aContext.
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: 0. "FoxIFSavedIP"
  			theIP := self iframeInstructionPointerForIndex: theIP method: theMethod].
  	page baseFP: page headFP.
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: rcvr.
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	stackPages longAt: (pointer := pointer - objectMemory wordSize) put: theIP.
  	page headSP: pointer.
  	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: (self validStackPageBaseFrame: page).
  	^page!

Item was changed:
  VMStructType subclass: #CogBlockMethod
+ 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCaseOrCMIsFullBlock cmUsageCount cmUsesPenultimateLit cbUsesInstVars cmUnusedFlags stackCheckOffset'
- 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCase cmUsageCount cmUsesPenultimateLit cbUsesInstVars cmUnusedFlags stackCheckOffset'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogMethodConstants VMBasicConstants VMBytecodeConstants'
- 	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
+ !CogBlockMethod commentStamp: 'eem 4/14/2016 10:39' prior: 0!
- !CogBlockMethod commentStamp: 'eem 6/4/2015 09:06' prior: 0!
  I am the rump method header for a block method embedded in a full CogMethod.  I am the superclass of CogMethod, which is a Cog method header proper.  Instances of both classes have the same second word.  The homeOffset and startpc fields are overlaid on the objectHeader in a CogMethod.  See Cogit class>>structureOfACogMethod for more information.  In C I look like
  
  	typedef struct {
+ 		union {
+ 			struct {
+ 				unsigned short	homeOffset;
+ 				unsigned short	startpc;
- 		unsigned short	homeOffset;
- 		unsigned short	startpc;
  	#if SpurVM
+ 				unsigned int	padToWord;
- 		unsigned int	padToWord;
  	#endif
+ 			};
+ 			sqInt/sqLong	objectHeader;
+ 		};
  		unsigned		cmNumArgs : 8;
  		unsigned		cmType : 3;
  		unsigned		cmRefersToYoung : 1;
+ 		unsigned		cpicHasMNUCaseOrCMIsFullBlock : 1;
- 		unsigned		cpicHasMNUCase : 1;
  		unsigned		cmUsageCount : 3;
  		unsigned		cmUsesPenultimateLit : 1;
  		unsigned		cbUsesInstVars : 1;
  		unsigned		cmUnusedFlags : 2;
  		unsigned		stackCheckOffset : 12;
  	 } CogBlockMethod;
  
+ My instances are not actually used.  The methods exist only as input to Slang.  The simulator uses my surrogates (CogBlockMethodSurrogate32 and CogBlockMethodSurrogate64) to reference CogBlockMethod and CogMethod structures in the code zone.  The start of the structure is 32-bits in the V3 memory manager and 64-bits in the Spour memory manager.  In a CMMethod these bits are set to the object header of a marked bits objects, allowing code to masquerade as objects when referred to from the first field of a CompiledMethod.  In a CMBlock, they hold the homeOffset and the startpc.
- My instances are not actually used.  The methods exist only as input to Slang.  The simulator uses my surrogates (CogBlockMethodSurrogate32 and CogBlockMethodSurrogate64) to reference CogBlockMethod and CogMethod structures in the code zone.
  
  cbUsesInstVars
  	- a flag set to true in blocks that refer to instance variables.
  
  cmNumArgs
  	- the byte containing the block or method arg count
  
  cmRefersToYoung
  	- a flag set to true in methods which contain a reference to an object in new space
  
  cmType
  	- one of CMFree, CMMethod, CMBlock, CMClosedPIC, CMOpenPIC
  
  cmUnusedFlags
  	- as yet unused bits
  
  cmUsageCount
  	- a count used to identify older methods in code compaction.  The count decays over time, and compaction frees methods with lower usage counts
  
  cmUsesPenultimateLit
  	- a flag that states whether the penultimate literal in the corresponding bytecode method is used.  This in turn is used to check that a become of a method does not alter its bytecode.
  
+ cpicHasMNUCaseOrCMIsFullBlock
+ 	- a flag that states whether a CMClosedPIC contains one or more MNU cases which are PIC dispatches used to speed-up MNU processing,
+ 	  or states whether a CMMethod is for a full block instead of for a compiled method.
- cpicHasMNUCase
- 	- a flag that states whether a CMClosedPIC contains one or more MNU cases which are PIC dispatches used to speed-up MNU processing
  
  homeOffset
  	- the distance a CMBlock header is away from its enclosing CMMethod header
  
  objectHeader
  	- an object header used to fool the garbage collector into thinking that a CMMethod is a normal bits object, so that the first field (the header word) of a bytecoded method can refer directly to a CMMethod without special casing the garbage collector's method scanning code more than it already is.
  
  padToWord
  	- a pad that may be necessary to make the homeOffset, startpc, padToWord triple as large as a CMMethod's objectHeader field
  
  stackCheckOffset
  	- the distance from the header to the stack limit check in a frame building method or block, used to reenter execution in methods or blocks that have checked for events at what is effectively the first bytecode
  
  startpc
  	- the bytecode pc of the start of a CMBlock's bytecode in the bytecode method!

Item was changed:
  ----- Method: CogBlockMethod class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the
  	 inst vars to include in a CogMethod or CogBlockMethod struct."
  
  	self allInstVarNames do:
  		[:ivn|
  		"Notionally objectHeader is in a union with homeOffset and startpc but
  		 we don't have any convenient support for unions.  So hack, hack, hack, hack."
  		((self == CogBlockMethod
  			ifTrue: [#('objectHeader')]
  			ifFalse: [#('homeOffset' 'startpc' 'padToWord')]) includes: ivn) ifFalse:
  				[aBinaryBlock
  					value: ivn
  					value: (ivn caseOf: {
  								['objectHeader']			-> [self objectMemoryClass baseHeaderSize = 8
  																ifTrue: [#sqLong]
  																ifFalse: [#sqInt]].
  								['cmNumArgs']				-> [#(unsigned ' : 8')].		"SqueakV3 needs only 5 bits"
  								['cmType']					-> [#(unsigned ' : 3')].
  								['cmRefersToYoung']		-> [#(unsigned #Boolean ' : 1')].
+ 								['cpicHasMNUCaseOrCMIsFullBlock']
+ 															-> [#(unsigned #Boolean ' : 1')].
- 								['cpicHasMNUCase']		-> [#(unsigned #Boolean ' : 1')].
  								['cmUsageCount']			-> [#(unsigned ' : 3')].		"See CMMaxUsageCount in initialize"
  								['cmUsesPenultimateLit']	-> [#(unsigned #Boolean ' : 1')].
  								['cbUsesInstVars']			-> [#(unsigned #Boolean ' : 1')].
  								['cmUnusedFlags']			-> [#(unsigned ' : 2')].
  								['stackCheckOffset']		-> [#(unsigned ' : 12')].		"See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
  								['blockSize']				-> [#'unsigned short'].		"See MaxMethodSize in initialize"
  								['blockEntryOffset']			-> [#'unsigned short'].
  								['homeOffset']				-> [#'unsigned short'].
  								['startpc']					-> [#'unsigned short'].
  								['padToWord']				-> [#(#BaseHeaderSize 8 'unsigned int')].
  								['nextMethod']				-> ['struct _CogMethod *'].	"See NewspeakCogMethod"
  								['counters']					-> [#usqInt]}				"See SistaCogMethod"
  							otherwise:
  								[#sqInt])]]!

Item was changed:
  ----- Method: CogBlockMethod>>cmHomeMethod (in category 'accessing') -----
  cmHomeMethod
+ 	^SistaV1BytecodeSet
+ 		ifTrue: [self cmIsFullBlock
+ 					ifTrue: [self cCoerceSimple: self to: #'CogMethod *']
+ 					ifFalse: [self cCoerceSimple: self asUnsignedInteger - self homeOffset to: #'CogMethod *']]
+ 		ifFalse: [self cCoerceSimple: self asUnsignedInteger - self homeOffset to: #'CogMethod *']!
- 	^self cCoerceSimple: self asUnsignedInteger - self homeOffset to: #'CogMethod *'!

Item was added:
+ ----- Method: CogBlockMethod>>cmIsFullBlock (in category 'accessing') -----
+ cmIsFullBlock
+ 	"Answer the value of cpicHasMNUCaseOrCMIsFullBlock"
+ 
+ 	^SistaV1BytecodeSet
+ 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock]
+ 		ifFalse: [false]!

Item was changed:
  ----- Method: CogBlockMethod>>cpicHasMNUCase (in category 'accessing') -----
  cpicHasMNUCase
+ 	"Answer if the receiver has an MNU case."
+ 	<inline: true>
- 	"Answer the value of cpicHasMNUCase"
  
+ 	^SistaV1BytecodeSet
+ 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock and: [self cmType = CMClosedPIC]]
+ 		ifFalse: [cpicHasMNUCaseOrCMIsFullBlock]!
- 	^cpicHasMNUCase!

Item was changed:
  ----- Method: CogBlockMethod>>cpicHasMNUCase: (in category 'accessing') -----
  cpicHasMNUCase: anObject
+ 	"Set if the receiver has an MNU case."
+ 	<inline: true>
+ 	^cpicHasMNUCaseOrCMIsFullBlock := anObject!
- 	"Set the value of cpicHasMNUCase"
- 
- 	^cpicHasMNUCase := anObject!

Item was added:
+ ----- Method: CogBlockMethod>>cpicHasMNUCaseOrCMIsFullBlock (in category 'accessing') -----
+ cpicHasMNUCaseOrCMIsFullBlock
+ 	"Answer the value of cpicHasMNUCaseOrCMIsFullBlock"
+ 
+ 	^cpicHasMNUCaseOrCMIsFullBlock!

Item was added:
+ ----- Method: CogBlockMethod>>cpicHasMNUCaseOrCMIsFullBlock: (in category 'accessing') -----
+ cpicHasMNUCaseOrCMIsFullBlock: anObject
+ 	"Set the value of cpicHasMNUCaseOrCMIsFullBlock"
+ 
+ 	^cpicHasMNUCaseOrCMIsFullBlock := anObject!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cmHomeMethod (in category 'accessing') -----
- cmHomeMethod
- 	^cogit cogMethodSurrogateAt: address - self homeOffset!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cpicHasMNUCase (in category 'accessing') -----
- cpicHasMNUCase
- 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was removed:
- ----- Method: CogBlockMethodSurrogate32>>cpicHasMNUCase: (in category 'accessing') -----
- cpicHasMNUCase: aValue
- 	memory
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
- 	^aValue!

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cpicHasMNUCaseOrCMIsFullBlock (in category 'accessing') -----
+ cpicHasMNUCaseOrCMIsFullBlock
+ 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cpicHasMNUCaseOrCMIsFullBlock: (in category 'accessing') -----
+ cpicHasMNUCaseOrCMIsFullBlock: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
+ 	^aValue!

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cmHomeMethod (in category 'accessing') -----
- cmHomeMethod
- 	^cogit cogMethodSurrogateAt: address - self homeOffset!

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cpicHasMNUCase (in category 'accessing') -----
- cpicHasMNUCase
- 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was removed:
- ----- Method: CogBlockMethodSurrogate64>>cpicHasMNUCase: (in category 'accessing') -----
- cpicHasMNUCase: aValue
- 	memory
- 		unsignedByteAt: address + baseHeaderSize + 2
- 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
- 	^aValue!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cpicHasMNUCaseOrCMIsFullBlock (in category 'accessing') -----
+ cpicHasMNUCaseOrCMIsFullBlock
+ 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cpicHasMNUCaseOrCMIsFullBlock: (in category 'accessing') -----
+ cpicHasMNUCaseOrCMIsFullBlock: aValue
+ 	memory
+ 		unsignedByteAt: address + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
+ 	^aValue!

Item was changed:
  VMClass subclass: #CogMethodSurrogate
  	instanceVariableNames: 'address memory baseHeaderSize cogit'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogMethodConstants VMBytecodeConstants'
- 	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: CogMethodSurrogate>>cmHomeMethod (in category 'accessing') -----
+ cmHomeMethod
+ 	^cogit cogMethodSurrogateAt: ((SistaV1BytecodeSet and: [self cmIsFullBlock])
+ 										ifTrue: [address]
+ 										ifFalse: [address - self homeOffset])!

Item was added:
+ ----- Method: CogMethodSurrogate>>cmIsFullBlock (in category 'accessing') -----
+ cmIsFullBlock
+ 	"Answer the value of cpicHasMNUCaseOrCMIsFullBlock"
+ 
+ 	^SistaV1BytecodeSet
+ 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock]
+ 		ifFalse: [false]!

Item was added:
+ ----- Method: CogMethodSurrogate>>cpicHasMNUCase (in category 'accessing') -----
+ cpicHasMNUCase
+ 	"Answer if the receiver has an MNU case."
+ 	<inline: true>
+ 
+ 	^SistaV1BytecodeSet
+ 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock and: [self cmType = CMClosedPIC]]
+ 		ifFalse: [self cpicHasMNUCaseOrCMIsFullBlock]!

Item was added:
+ ----- Method: CogMethodSurrogate>>cpicHasMNUCase: (in category 'accessing') -----
+ cpicHasMNUCase: anObject
+ 	"Set if the receiver has an MNU case."
+ 
+ 	^self cpicHasMNUCaseOrCMIsFullBlock: anObject!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>maybeGenerateSelectorIndexDereferenceRoutine (in category 'initialization') -----
  maybeGenerateSelectorIndexDereferenceRoutine
  	"Generate the routine that converts selector indices into selector objects.
  	 It is called from the send trampolines.
  	 If the selector index is negative, convert it into a positive index into the
  	 special selectors array and index that.  Otherwise, index the current method."
  	| jumpNegative jumpNotBlock |
  	<var: 'jumpNegative' type: #'AbstractInstruction *'>
  	<var: 'jumpNotBlock' type: #'AbstractInstruction *'>
  	cogit zeroOpcodeIndex.
  	cogit CmpCq: 0 R: ClassReg.
  	jumpNegative := cogit JumpLess: 0.
+ 	self halt: 'Add handling of full blocks!!!!'.
  	cogit
  		MoveMw: FoxMethod r: FPReg R: Scratch0Reg;
  		AddCq: 2 R: ClassReg; "Change selector index to 1-relative, skipping the method header"
  		TstCq: MFMethodFlagIsBlockFlag R: Scratch0Reg.
  	jumpNotBlock := cogit JumpZero: 0.
  	cogit "If in a block, need to find the home method..."
  		AndCq: methodZone alignment negated R: Scratch0Reg;
  		MoveM16: 0 r: Scratch0Reg R: Scratch1Reg;
  		SubR: Scratch1Reg R: Scratch0Reg.
  	jumpNotBlock jmpTarget: cogit Label.
  	cogit "Now fetch the method object and index with the literal index to retrieve the selector"
  		AndCq: methodZone alignment negated R: Scratch0Reg;
  		MoveMw: (cogit offset: CogMethod of: #methodObject) r: Scratch0Reg R: Scratch1Reg;
  		MoveXwr: ClassReg R: Scratch1Reg R: ClassReg;
  		RetN: 0.
  	jumpNegative jmpTarget: cogit Label.
  	cogit
  		NegateR: ClassReg;
  		LogicalShiftLeftCq: 1 R: ClassReg;
  		MoveAw: objectMemory specialObjectsArrayAddress R: Scratch0Reg;
  		SubCq: 1 R: ClassReg;
  		MoveMw: SpecialSelectors + 1 * objectMemory wordSize r: Scratch0Reg R: Scratch1Reg; "Index, including header size"
  		MoveXwr: ClassReg R: Scratch1Reg R: ClassReg;
  		RetN: 0.
  	ceDereferenceSelectorIndex := cogit methodZoneBase.
  	cogit
  		outputInstructionsForGeneratedRuntimeAt: ceDereferenceSelectorIndex;
  		recordGeneratedRunTime: 'ceDereferenceSelectorIndex' address: ceDereferenceSelectorIndex;
  		recordRunTimeObjectReferences!

Item was changed:
  ----- Method: Cogit>>compileEntireFullBlockMethod: (in category 'compile abstract instructions') -----
  compileEntireFullBlockMethod: numCopied
  	"Compile the abstract instructions for the entire method, including blocks."
+ 	| result |
+ 	self preenMethodLabel.
- 	| result |	
  	self compileFullBlockEntry.
  
  	"Frame build"
  	self compileFullBlockMethodFrameBuild: numCopied.
  	"Method body"
  	(result := self compileMethodBody) < 0 ifTrue:
  		[^result].
  	self assert: blockCount = 0.
  	^0!

Item was changed:
  ----- Method: Cogit>>compileEntireMethod (in category 'compile abstract instructions') -----
  compileEntireMethod
  	"Compile the abstract instructions for the entire method, including blocks."
  	| result |
+ 	self preenMethodLabel.
  	self compileAbort.
  	self compileEntry.
  	(result := self compilePrimitive) < 0 ifTrue:
  		[^result].
  	self compileFrameBuild.
  	(result := self compileMethodBody) < 0 ifTrue:
  		[^result].
  	blockCount = 0 ifTrue:
  		[^0].
  	(result := self compileBlockBodies) < 0 ifTrue:
  		[^result].
  	^self compileBlockDispatch!

Item was changed:
  ----- Method: Cogit>>generateCogFullBlock (in category 'compile abstract instructions') -----
  generateCogFullBlock
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	<returnTypeC: #'CogMethod *'>
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: methodZone freeStart.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: nil start: methodLabel address + cbNoSwitchEntryOffset.
  .
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	totalSize > MaxMethodSize ifTrue:
  		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cbEntryOffset = fullBlockEntry address.
  	self assert: startAddress + cbNoSwitchEntryOffset = fullBlockNoContextSwitchEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithStopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cbNoSwitchEntryOffset.
  	self flag: #TOCHECK. "It's not clear we want the same header than regular methods. 
  	It could be of the same size, but maybe the cmType could be different and the selector could be ignored." 
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: objectMemory nilObject.
+ 	method cpicHasMNUCaseOrCMIsFullBlock: true.
  	postCompileHook ifNotNil:
  		[self perform: postCompileHook with: method.
  		 postCompileHook := nil].
  	^method!

Item was added:
+ ----- Method: Cogit>>preenMethodLabel (in category 'compile abstract instructions') -----
+ preenMethodLabel
+ 	"The methodLabel serves as the reference to the start of the current code object
+ 	 being produced (CMMethod, CMClosedPIC etc), but it also carries type flags for
+ 	 the frame method field, set via the labelOffset.  So we must clean the flags on each
+ 	 compilation to avoid stale lags being left behind from previous compilations."
+ 	methodLabel setLabelOffset: 0!

Item was changed:
  ----- Method: Cogit>>printMethodHeader:on: (in category 'disassembly') -----
  printMethodHeader: cogMethod on: aStream
  	<doNotGenerate>
  	self cCode: ''
  		inSmalltalk:
  			[cogMethod isInteger ifTrue:
  				[^self printMethodHeader: (self cogMethodOrBlockSurrogateAt: cogMethod) on: aStream]].
  	aStream ensureCr.
  	cogMethod asInteger printOn: aStream base: 16.
  	cogMethod cmType = CMMethod ifTrue:
  		[aStream crtab; nextPutAll: 'objhdr: '.
  		cogMethod objectHeader printOn: aStream base: 16].
  	cogMethod cmType = CMBlock ifTrue:
  		[aStream crtab; nextPutAll: 'homemth: '.
  		cogMethod cmHomeMethod asUnsignedInteger printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'startpc: '; print: cogMethod startpc].
  	aStream
  		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
  		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
  	(cogMethod cmType ~= 0 and: [cogMethod cmType ~= CMBlock]) ifTrue:
  		[aStream crtab; nextPutAll: 'blksiz: '.
  		cogMethod blockSize printOn: aStream base: 16.
  		cogMethod cmType = CMMethod ifTrue:
  			[aStream crtab; nextPutAll: 'method: '.
  			 cogMethod methodObject printOn: aStream base: 16.
  			 aStream crtab; nextPutAll: 'mthhdr: '.
  			 cogMethod methodHeader printOn: aStream base: 16].
  		aStream crtab; nextPutAll: 'selctr: '.
  		cogMethod selector printOn: aStream base: 16.
  		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
  			[:string| aStream nextPut: $=; nextPutAll: string].
  		cogMethod cmType = CMMethod ifTrue:
  			[aStream crtab; nextPutAll: 'blkentry: '.
  			 cogMethod blockEntryOffset printOn: aStream base: 16.
  			 cogMethod blockEntryOffset ~= 0 ifTrue:
  				[aStream nextPutAll: ' => '.
  				 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]]].
  	cogMethod cmType = CMClosedPIC
  		ifTrue:
  			[aStream crtab; nextPutAll: 'cPICNumCases: '.
+ 			 cogMethod cPICNumCases printOn: aStream base: 16;
+ 			 tab; nextPutAll: 'cpicHasMNUCase: ';
+ 			 nextPutAll: (cogMethod cpicHasMNUCase ifTrue: ['yes'] ifFalse: ['no'])]
- 			 cogMethod cPICNumCases printOn: aStream base: 16.]
  		ifFalse:
  			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
  			 cogMethod stackCheckOffset printOn: aStream base: 16.
  			 cogMethod stackCheckOffset > 0 ifTrue:
  				[aStream nextPut: $/.
  				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16].
  			cogMethod cmType = CMBlock
  				ifTrue:
  					[aStream
  						crtab;
  						nextPutAll: 'cbUsesInstVars ';
  						nextPutAll: (cogMethod cbUsesInstVars ifTrue: ['yes'] ifFalse: ['no'])]
  				ifFalse:
  					[aStream
  						crtab;
  						nextPutAll: 'cmRefersToYoung: ';
+ 						nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no']);
+ 						tab;
+ 						nextPutAll: 'cmIsFullBlock: ';
+ 						nextPutAll: (cogMethod cmIsFullBlock ifTrue: ['yes'] ifFalse: ['no'])].
- 						nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no'])].
  			cogMethod cmType = CMMethod ifTrue:
  				[([cogMethod nextMethodOrIRCs] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:nmoircs| aStream crtab; nextPutAll: 'nextMethodOrIRCs: '.
  						nmoircs = 0 ifTrue: [aStream print: nmoircs] ifFalse: [coInterpreter printHex: nmoircs]].
  				 ([cogMethod counters] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:cntrs| aStream crtab; nextPutAll: 'counters: '.
  						cntrs = 0 ifTrue: [aStream print: cntrs] ifFalse: [coInterpreter printHex: cntrs]]]].
  	aStream cr; flush!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileOpenPIC:numArgs: (in category 'in-line cacheing') -----
  compileOpenPIC: selector numArgs: numArgs
  	"Compile the code for an open PIC.  Perform a probe of the first-level method
  	 lookup cache followed by a call of ceSendFromInLineCacheMiss: if the probe fails."
  	| cacheBaseReg jumpSelectorMiss jumpClassMiss itsAHit jumpBCMethod |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
+ 	self preenMethodLabel.
  	self compilePICAbort: numArgs.
  	entry := objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  	self MoveR: ClassReg R: SendNumArgsReg.
  
  	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
  
  	cacheBaseReg := NoReg.
  	(backEnd isWithinMwOffsetRange: coInterpreter methodCacheAddress) ifFalse:
  		[self MoveCq: coInterpreter methodCacheAddress R: (cacheBaseReg := Scratch0Reg)].
  
  	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
  	jumpSelectorMiss := self compileOpenPICMethodCacheProbeFor: selector withShift: 0 baseRegOrNone: cacheBaseReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	"Fetch the method.  The interpret trampoline requires the bytecoded method in SendNumArgsReg"
  	itsAHit := self MoveMw: (cacheBaseReg = NoReg
  								ifTrue: [coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << objectMemory shiftForWord)]
  								ifFalse: [MethodCacheMethod << objectMemory shiftForWord])
  					r: ClassReg
  					R: SendNumArgsReg.
  			.
  	"If the method is compiled jump to its unchecked entry-point, otherwise interpret it."
  	objectRepresentation genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpImmediate: ClassReg.
  	jumpBCMethod jmpTarget: picInterpretAbort.
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	jumpSelectorMiss := self compileOpenPICMethodCacheProbeFor: selector withShift: 1 baseRegOrNone: cacheBaseReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	jumpSelectorMiss := self compileOpenPICMethodCacheProbeFor: selector withShift: 2 baseRegOrNone: cacheBaseReg.
  	self JumpZero: itsAHit.
  
  	"Last probe missed.  Call ceSendFromInLineCacheMiss: to do the full lookup."
  	jumpSelectorMiss jmpTarget: self Label.
  	self numRegArgs > 0 ifTrue:
  		[backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: SendNumArgsReg].
  	self genSmalltalkToCStackSwitch: true.
  	methodLabel addDependent: (self annotateAbsolutePCRef: (self MoveCw: methodLabel asInteger R: SendNumArgsReg)).
  	self 
  		compileCallFor: #ceSendFromInLineCacheMiss:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: NoReg
  		regsToSave: self emptyRegisterMask
  	"Note that this call does not return."!

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

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForNewspeakV4 (in category 'initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackInterpreter initializeBytecodeTableForNewspeakV4"
  	"Note: This table will be used to generate a C switch statement."
  
+ 	initializationOptions at: #NewsqueakV4BytecodeSet put: (NewsqueakV4BytecodeSet := true).
- 	initializationOptions at: #NewsqueakV4BytecodeSet put: true.
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForNewsqueakV4.
  	LongStoreBytecode := 234.
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 extPushPseudoVariableOrOuterBytecode)
  		( 78	 pushConstantZeroBytecode)
  		( 79	 pushConstantOneBytecode)
  
  		( 80	 bytecodePrimAdd)
  		( 81	 bytecodePrimSubtract)
  		( 82	 bytecodePrimLessThanV4) "for booleanCheatV4:"
  		( 83	 bytecodePrimGreaterThanV4) "for booleanCheatV4:"
  		( 84	 bytecodePrimLessOrEqualV4) "for booleanCheatV4:"
  		( 85	 bytecodePrimGreaterOrEqualV4) "for booleanCheatV4:"
  		( 86	 bytecodePrimEqualV4) "for booleanCheatV4:"
  		( 87	 bytecodePrimNotEqualV4) "for booleanCheatV4:"
  		( 88	 bytecodePrimMultiply)
  		( 89	 bytecodePrimDivide)
  		( 90	 bytecodePrimMod)
  		( 91	 bytecodePrimMakePoint)
  		( 92	 bytecodePrimBitShift)
  		( 93	 bytecodePrimDiv)
  		( 94	 bytecodePrimBitAnd)
  		( 95	 bytecodePrimBitOr)
  
  		( 96	 bytecodePrimAt)
  		( 97	 bytecodePrimAtPut)
  		( 98	 bytecodePrimSize)
  		( 99	 bytecodePrimNext)
  		(100	 bytecodePrimNextPut)
  		(101	 bytecodePrimAtEnd)
  		(102	 bytecodePrimIdenticalV4) "for booleanCheatV4:"
  		(103	 bytecodePrimClass)
  		(104	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(105	 bytecodePrimValue)
  		(106	 bytecodePrimValueWithArg)
  		(107	 bytecodePrimDo)
  		(108	 bytecodePrimNew)
  		(109	 bytecodePrimNewWithArg)
  		(110	 bytecodePrimPointX)
  		(111	 bytecodePrimPointY)
  
  		(112 127	sendLiteralSelector0ArgsBytecode)
  		(128 143	sendLiteralSelector1ArgBytecode)
  		(144 159	sendLiteralSelector2ArgsBytecode)
  		(160 175	sendAbsentImplicit0ArgsBytecode)
  
  		(176 183	storeAndPopReceiverVariableBytecode)
  		(184 191	storeAndPopTemporaryVariableBytecode)
  
  		(192 199	shortUnconditionalJump)
  		(200 207	shortConditionalJumpTrue)
  		(208 215	shortConditionalJumpFalse)
  
  		(216		returnReceiver)
  		(217		returnTopFromMethod)
  		(218		extReturnTopFromBlock)
  
  		(219		duplicateTopBytecode)
  		(220		popStackBytecode)
  		(221		extNopBytecode)
  		(222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		extPushIntegerBytecode)
  		(230		longPushTemporaryVariableBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extStoreReceiverVariableBytecode)
  		(233		extStoreLiteralVariableBytecode)
  		(234		longStoreTemporaryVariableBytecode)
  		(235		extStoreAndPopReceiverVariableBytecode)
  		(236		extStoreAndPopLiteralVariableBytecode)
  		(237		longStoreAndPopTemporaryVariableBytecode)
  
  		(238		extSendBytecode)
  		(239		extSendSuperBytecode)
  		(240		extSendAbsentImplicitBytecode)
  		(241		extSendAbsentDynamicSuperBytecode)
  
  		(242		extUnconditionalJump)
  		(243		extJumpIfTrue)
  		(244		extJumpIfFalse)
  
  		(245		extSendAbsentSelfBytecode)
  
  		(246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(249		callPrimitiveBytecode)
  
  		(250		pushRemoteTempLongBytecode)
  		(251		storeRemoteTempLongBytecode)
  		(252		storeAndPopRemoteTempLongBytecode)
  		(253		extPushClosureBytecode)
  		(254		extSendAbsentOuterBytecode)
  
  		(255		unknownBytecode)
  	)!

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

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"StackInterpreter initializeBytecodeTableForSqueakV3PlusClosures"
  	"Note: This table will be used to generate a C switch statement."
  
+ 	initializationOptions at: #SqueakV3PlusClosuresBytecodeSet put: (SqueakV3PlusClosuresBytecodeSet := true).
- 	initializationOptions at: #SqueakV3PlusClosuresBytecodeSet put: true.
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForV3PlusClosures.
  	LongStoreBytecode := 129.
  	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)
  
  		(126 127 unknownBytecode)
  
  		(128 extendedPushBytecode)
  		(129 extendedStoreBytecode)
  		(130 extendedStoreAndPopBytecode)
  		(131 singleExtendedSendBytecode)
  		(132 doubleExtendedDoAnythingBytecode)
  		(133 singleExtendedSuperBytecode)
  		(134 secondExtendedSendBytecode)
  		(135 popStackBytecode)
  		(136 duplicateTopBytecode)
  
  		(137 pushActiveContextBytecode)
  		(138 pushNewArrayBytecode)),
  
  	((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  		ifTrue: [#((139 callPrimitiveBytecode))]	"V3PlusClosures on Spur"
  		ifFalse: [#((139 unknownBytecode))]),	"V3PlusClosures on V3"
  
  	  #(
  		(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>>isVanillaBlockClosure: (in category 'internal interpreter access') -----
+ isVanillaBlockClosure: aClosure
+ 	"Answer if aClosure is a vanilla BlockClosure as in the first Cog release, BlockClosure laid out as 
+ 	 'outerContext, startpc, numArgs.  FullBlockClosure is laid out as  outerContext, method, numArgs, receiver.
+ 	 So either answer true if we're not supporting FullBlockClosure, or test the startpc/method field."
+ 	<inline: true>
+ 	^SistaV1BytecodeSet
+ 		ifTrue: [objectMemory isIntegerObject: (objectMemory fetchPointer: ClosureStartPCIndex ofObject: aClosure)]
+ 		ifFalse: [true]!

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

Item was added:
+ ----- Method: VMBytecodeConstants class>>falsifyBytecodeSetFlags (in category 'simulator initialization') -----
+ falsifyBytecodeSetFlags
+ 	SqueakV3PlusClosuresBytecodeSet.
+ 	NewsqueakV4BytecodeSet.
+ 	SistaV1BytecodeSet.
+ 	classPool keys do:
+ 		[:k|
+ 		(k endsWith: 'BytecodeSet') ifTrue:
+ 			[classPool at: k put: false]]
+ 
+ 	"classPool keys select: [:k| k endsWith: 'BytecodeSet']"!



More information about the Vm-dev mailing list