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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 21 04:34:25 UTC 2016


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

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

Name: VMMaker.oscog-eem.1660
Author: eem
Time: 21 January 2016, 8:32:44.580527 pm
UUID: 372f5635-366a-462d-8979-ae86dee05577
Ancestors: VMMaker.oscog-cb.1659

Immutability:
Add the immutability info to the bytecode tables in SimpleStackBasedCogit

Use isObjImmutable: externally to SpurMemoryManager and hence get rid of the cppIf:ifrue: around the failure.

Make the married context inst var assign methods deny immutability for their contexts.

Streamline primitiveSetImmutability to use booleanObjectOf:.

Cogit:
Move debugBytecodePointers up into Cogit to help debugging code generation in SimpleStackBasedCogit.

Plugins:
Fix the FilePlugin's unnecessary fullGC on Spur.

Slang vs simulation:
Get rid of the hacks for variables defined on the C command line or in headers such as IMMUTABILITY or VMBIGENDIAN.  Introduce VMBasicConstants class>>namesDefinedAtCompileTime to define these names and
- have dead code elimination check for these names and not eliminate
- have emitCConstants:on: query them to decide which variables are to be output as #if !defined(... forms.
Eliminate the !defined hacks from various declareCVars:.
Make sure that IMMUTABILITY et al /are/ defaulted to appropriate values for simulation if not defined.
Nuke the now incomprehensible copyOptionsBackTo:.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstants:on: (in category 'C code generator') -----
  emitCConstants: constList on: aStream
  	"Store the global variable declarations on the given stream."
  	constList isEmpty ifTrue: [^self].
  	aStream cr; nextPutAll: '/*** Constants ***/'; cr.
  	(self sortStrings: constList) do:
+ 		[:varName| | node default value conditional |
- 		[:varName| | node default value |
  		node := constants at: varName.
  		node name isEmpty ifFalse:
  			["If the definition includes a C comment, take it as is, otherwise convert the value from Smalltalk to C.
  			  Allow the class to provide an alternative definition, either of just the value or the whole shebang."
  			default := (node value isString and: [node value includesSubString: '/*'])
  							ifTrue: [node value]
  							ifFalse: [self cLiteralFor: node value name: varName].
  			default = #undefined
  				ifTrue: [aStream nextPutAll: '#undef '; nextPutAll: node name; cr]
  				ifFalse:
+ 					[conditional := VMBasicConstants namesDefinedAtCompileTime includes: node name.
+ 					 conditional ifTrue:
+ 						[aStream nextPutAll: '#if !!defined('; nextPutAll: node name; nextPutAll: ') /* Allow this to be overridden on the compiler command line */'; cr].
+ 					 value := vmClass
- 					[value := vmClass
  								ifNotNil:
  									[(vmClass specialValueForConstant: node name default: default)
  										ifNotNil: [:specialDef| specialDef]
  										ifNil: [default]]
  								ifNil: [default].
  					value first ~= $# ifTrue:
  						[aStream nextPutAll: '#define '; nextPutAll: node name; space].
+ 					aStream nextPutAll: value; cr.
+ 					conditional ifTrue:
+ 						[aStream nextPutAll: '#endif'; cr]]]].
- 					aStream nextPutAll: value; cr]]].
  	aStream cr!

Item was changed:
  ----- Method: CCodeGenerator>>isConstantNode:valueInto: (in category 'utilities') -----
  isConstantNode: aNode valueInto: aBlock
  	"Answer if aNode evaluates to a constant, and if so, evaluate aBlock with the value of that constant."
  
  	aNode isConstant ifTrue:
+ 		[(aNode isDefine
+ 		 and: [VMBasicConstants namesDefinedAtCompileTime includes: aNode name]) ifTrue:
+ 			[^false].
+ 		 aBlock value: aNode value.
- 		[aBlock value: aNode value.
  		 ^true].
  	(aNode isVariable
  	 and: [aNode name = #nil]) ifTrue:
  		[aBlock value: nil.
  		 ^true].
  	aNode isSend ifFalse:
  		[^false].
  	(self anyMethodNamed: aNode selector)
  		ifNil:
  			[(VMBasicConstants valueOfBasicSelector: aNode selector) ifNotNil:
  				[:value|
  				 aBlock value: value.
  				 ^true]]
  		ifNotNil:
  			[:m|
  			(m statements size = 1
  			 and: [m statements last isReturn]) ifTrue:
  				[^self isConstantNode: m statements last expression valueInto: aBlock]].
  	^false!

Item was changed:
  ----- Method: CCodeGenerator>>vmClass: (in category 'accessing') -----
  vmClass: aClass
  	"Set the main translation class if any.  This is nil other than for the core VM.
  	 It may be an interpreter or a cogit"
  	vmClass := aClass.
  	vmClass ifNotNil:
+ 		[generateDeadCode := vmClass shouldGenerateDeadCode]!
- 		[generateDeadCode := vmClass shouldGenerateDeadCode.
- 		 vmClass copyOptionsBackTo: optionsDictionary]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveObjectAtPut (in category 'object access primitives') -----
  primitiveObjectAtPut
  	"Store a literal into a CompiledMethod at the given index. Defined for CompiledMethods only."
  	| thisReceiver rawHeader realHeader index newValue |
  	newValue := self stackValue: 0.
  	index := self stackValue: 1.
  	(objectMemory isNonIntegerObject: index) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	thisReceiver := self stackValue: 2.
+ 	(objectMemory isObjImmutable: thisReceiver) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	self cppIf: IMMUTABILITY
- 		ifTrue: [ (objectMemory isImmutable: thisReceiver) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
  	rawHeader := self rawHeaderOf: thisReceiver.
  	realHeader := (self isCogMethodReference: rawHeader)
  					ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader]
  					ifFalse: [rawHeader].
  	(index > 0
  	 and: [index <= ((objectMemory literalCountOfMethodHeader: realHeader) + LiteralStart)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	index = 1
  		ifTrue:
  			[((objectMemory isNonIntegerObject: newValue)
  			 or: [(objectMemory literalCountOfMethodHeader: newValue) ~= (objectMemory literalCountOfMethodHeader: realHeader)]) ifTrue:
  				[^self primitiveFailFor: PrimErrBadArgument].
  			 (self isCogMethodReference: rawHeader)
  				ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader: newValue]
  				ifFalse: [objectMemory storePointerUnchecked: 0 ofObject: thisReceiver withValue: newValue]]
  		ifFalse:
  			[objectMemory storePointer: index - 1 ofObject: thisReceiver withValue: newValue].
  	self pop: 3 thenPush: newValue!

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

Item was changed:
  ----- Method: Cogit>>compileAbstractInstructionsFrom:through: (in category 'compile abstract instructions') -----
  compileAbstractInstructionsFrom: start through: end
  	"Loop over bytecodes, dispatching to the generator for each bytecode, handling fixups in due course."
  	| nextOpcodeIndex descriptor fixup result nExts |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	bytecodePC := start.
+ 	nExts := result := 0.
+ 	[self cCode: '' inSmalltalk:
+ 		[(debugBytecodePointers includes: bytecodePC) ifTrue: [self halt]].
+ 	 byte0 := (objectMemory fetchByte: bytecodePC ofObject: methodObj)  + bytecodeSetOffset.
- 	nExts := 0.
- 	[byte0 := (objectMemory fetchByte: bytecodePC ofObject: methodObj)  + bytecodeSetOffset.
  	 descriptor := self generatorAt: byte0.
  	 self loadSubsequentBytesForDescriptor: descriptor at: bytecodePC.
  	 nextOpcodeIndex := opcodeIndex.
  	 result := self perform: descriptor generator.
  	 descriptor isExtension ifFalse: "extended bytecodes must consume their extensions"
  		[self assert: (extA = 0 and: [extB = 0])].
  	 fixup := self fixupAt: bytecodePC - initialPC.
  	 fixup targetInstruction ~= 0 ifTrue:
  		["There is a fixup for this bytecode.  It must point to the first generated
  		   instruction for this bytecode.  If there isn't one we need to add a label."
  		 opcodeIndex = nextOpcodeIndex ifTrue:
  			[self Label].
  		 fixup targetInstruction: (self abstractInstructionAt: nextOpcodeIndex)].
  	 self maybeDumpLiterals: descriptor.
  	 bytecodePC := self nextBytecodePCFor: descriptor at: bytecodePC exts: nExts in: methodObj.
  	 result = 0 and: [bytecodePC <= end]]
  		whileTrue:
  			[nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  	self checkEnoughOpcodes.
  	^result!

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

Item was changed:
  ----- Method: FilePlugin class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  
  	self declareC:  #('sCCPfn' 'sCDFfn' 'sCDPfn' 'sCGFTfn' 'sCLPfn' 'sCOFfn' 'sCRFfn' 'sCSFTfn' 'sDFAfn' 'sHFAfn')
  		as: #'void *'
  		in: aCCodeGenerator.
- 	aCCodeGenerator
- 		const: #PharoVM
- 		declareC: ('#if !!defined(PharoVM) /* Allow PharoVM to be overridden on the compiler command line */\# define PharoVM 0\#endif') withCRs.
  	aCCodeGenerator addHeaderFile: '"FilePlugin.h"'!

Item was changed:
  ----- Method: FilePlugin>>primitiveFileStdioHandles (in category 'file primitives') -----
  primitiveFileStdioHandles
  	"Answer an Array of file handles for standard in, standard out and standard error,
  	 with nil in entries that are unvailable, e.g. because the platform does not provide
  	 standard error, etc.  Fail if there are no standard i/o facilities on the platform or
  	 if the security plugin denies access or if memory runs out."
  	| fileRecords result validMask |
  	<export: true>
  	<var: 'fileRecords' declareC: 'SQFile fileRecords[3]'>
  	sHFAfn ~= 0 ifTrue:
  		[(self cCode: ' ((sqInt (*)(void))sHFAfn)()' inSmalltalk: [true]) ifFalse:
  			[^interpreterProxy primitiveFailFor: PrimErrUnsupported]].
  	self cCode: '' inSmalltalk: [fileRecords := Array new: 3].
  	validMask := self sqFileStdioHandlesInto: fileRecords.
  	validMask = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrUnsupported].
  	result := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 3.
  	result = nil ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  	interpreterProxy pushRemappableOop: result.
  	0 to: 2 do:
  		[:index|
  		(validMask bitAnd: (1 << index)) ~= 0 ifTrue:
  			[result := interpreterProxy instantiateClass: interpreterProxy classByteArray indexableSize: self fileRecordSize.
  			 result = nil ifTrue:
  				[interpreterProxy popRemappableOop.
  				^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  			 interpreterProxy storePointer: index ofObject: interpreterProxy topRemappableOop withValue: result.
  			 self
  				cCode:
  					[self mem: (interpreterProxy firstIndexableField: result)
  						cp: (self addressOf: (fileRecords at: index))
  						y: self fileRecordSize]
  				inSmalltalk:
  					[(interpreterProxy firstIndexableField: result)
  						unitSize: interpreterProxy wordSize;
  						at: 0 put: (fileRecords at: index + 1)]]].
+ 	 "In the non-Spur threaded VM ensure the handles are old, so that sqFileReadIntoAt is unaffected
+ 	  by incremental GCs.  See platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c.  The Spur
+ 	  VM uses pinning, so it doesn't need the GC."
- 	 "In the threaded VM ensure the handles are old, so that sqFileReadIntoAt is unaffected
- 	  by incremental GCs.  See platforms/Cross/plugins/FilePlugin/sqFilePluginBasicPrims.c."
  	self cppIf: COGMTVM
+ 		ifTrue: [self cppIf: SPURVM
+ 					ifTrue: []
+ 					ifFalse: [interpreterProxy fullGC]].
- 		ifTrue: [interpreterProxy fullGC].
  	result := interpreterProxy popRemappableOop.
  	interpreterProxy pop: 1 thenPush: result!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFloatAtPut (in category 'indexing primitives') -----
  primitiveFloatAtPut
  	"Provide platform-independent access to 32-bit words comprising
  	 a Float.  Map index 1 onto the most significant word and index 2
  	 onto the least significant word."
  	| rcvr index oopToStore valueToStore |
  	<var: #valueToStore type: #usqInt>
  	oopToStore := self stackTop.
  	valueToStore := self positive32BitValueOf: oopToStore.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackValue: 2.
  	index := self stackValue: 1.
  	(objectMemory isImmediateFloat: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
+ 	(objectMemory isObjImmutable: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	self cppIf: IMMUTABILITY
- 		ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [^self primitiveFailFor: PrimErrNoModification] ].
  	index = ConstOne ifTrue:
  		[objectMemory storeLong32: (VMBIGENDIAN ifTrue: [0] ifFalse: [1])
  			ofObject: rcvr
  			withValue: valueToStore.
  		^self pop: 3 thenPush: oopToStore].
  	index = ConstTwo ifTrue:
  		[objectMemory storeLong32: (VMBIGENDIAN ifTrue: [1] ifFalse: [0])
  			ofObject: rcvr
  			withValue: valueToStore.
  		^self pop: 3 thenPush: oopToStore].
  	self primitiveFailFor: ((objectMemory isIntegerObject: index)
  							ifTrue: [PrimErrBadIndex]
  							ifFalse: [PrimErrBadArgument])!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIntegerAtPut (in category 'sound primitives') -----
  primitiveIntegerAtPut
  	"Return the 32bit signed integer contents of a words receiver"
  	| index rcvr sz addr value valueOop |
  	<var: 'value' type: 'int'>
  	valueOop := self stackValue: 0.
  	index := self stackIntegerValue: 1.
  	value := self signed32BitValueOf: valueOop.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackValue: 2.
  	(objectMemory isWords: rcvr) ifFalse:
  		[^self primitiveFailFor: PrimErrInappropriate].
+ 	(objectMemory isObjImmutable: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	self cppIf: IMMUTABILITY "isWords: ensure non immediate"
- 		ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
  	sz := objectMemory lengthOf: rcvr.  "number of fields"
  	(index >= 1 and: [index <= sz]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	"4 = 32 bits / 8"
  	addr := rcvr + objectMemory baseHeaderSize + (index - 1 * 4). "for zero indexing"
  	value := objectMemory intAt: addr put: value.
  	self pop: 3 thenPush: valueOop "pop all; return value"
  !

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveObjectAtPut (in category 'object access primitives') -----
  primitiveObjectAtPut
  	"Store a literal into a CompiledMethod at the given index. Defined for CompiledMethods only."
  	| thisReceiver index newValue |
  	newValue := self stackValue: 0.
  	index := self stackValue: 1.
  	((objectMemory isNonIntegerObject: index)
  	 or: [index = ConstOne and: [(objectMemory isNonIntegerObject: newValue)]]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	thisReceiver := self stackValue: 2.
+ 	(objectMemory isObjImmutable: thisReceiver) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	self cppIf: IMMUTABILITY
- 		ifTrue: [ (objectMemory isImmutable: thisReceiver) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
  	(index > 0 and: [index <= ((objectMemory literalCountOf: thisReceiver) + LiteralStart)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	objectMemory storePointer: index - 1 ofObject: thisReceiver withValue: newValue.
  	self pop: 3 thenPush: newValue!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSetImmutability (in category 'object access primitives') -----
  primitiveSetImmutability
  	<option: #IMMUTABILITY>
  	| rcvr boolean wasImmutable |
  	rcvr := self stackValue: 1.
+ 	(objectMemory isImmediate: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadReceiver].
- 	(objectMemory isImmediate: rcvr) ifTrue: [ ^ self primitiveFailFor: PrimErrInappropriate ].
  	boolean := self booleanValueOf: self stackTop.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	boolean ifTrue: 
+ 		[(self canBeImmutable: rcvr) ifFalse:
+ 			[^self primitiveFailFor: PrimErrInappropriate]]. 
+ 	wasImmutable := objectMemory booleanObjectOf: (objectMemory isOopImmutable: rcvr).
- 		[ (self canBeImmutable: rcvr) ifFalse: [ ^ self primitiveFailFor: PrimErrInappropriate ] ]. 
- 	wasImmutable := (objectMemory isOopImmutable: rcvr)
- 		ifTrue: [ TrueObject ]
- 		ifFalse: [ FalseObject ].
  	objectMemory setIsImmutableOf: rcvr to: boolean.
+ 	self pop: argumentCount + 1 thenPush: wasImmutable!
- 	self pop: argumentCount + 1 thenPush: (objectMemory splObj: wasImmutable)!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveShortAtPut (in category 'sound primitives') -----
  primitiveShortAtPut
  	"Treat the receiver, which can be indexible by either bytes or words, as an array
  	 of signed 16-bit values. Set the contents of the given index to the given value.
  	 Note that the index specifies the i-th 16-bit entry, not the i-th byte or word."
  
  	| index rcvr value |
  	value := self stackTop.
  	index := self stackValue: 1.
  	((objectMemory isIntegerObject: value)
  	 and: [(objectMemory isIntegerObject: index)
  	 and: [value := objectMemory integerValueOf: value.
  		  (value >= -32768) and: [value <= 32767]]]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackValue: 2.
  	(objectMemory isWordsOrBytes: rcvr) ifFalse:
  		[^self primitiveFailFor: PrimErrInappropriate].
+ 	(objectMemory isObjImmutable: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	self cppIf: IMMUTABILITY "isWordsOrBytes ensure non immediate"
- 		ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^self primitiveFailFor: PrimErrNoModification ] ].
  	index := objectMemory integerValueOf: index.
  	(index >= 1 and: [index <= (objectMemory num16BitUnitsOf: rcvr)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	objectMemory storeShort16: index - 1 ofObject: rcvr withValue: value.
  	self pop: 3 thenPush: (objectMemory integerObjectOf: value)!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveStringReplace (in category 'indexing primitives') -----
  primitiveStringReplace
  	" 
  	<array> primReplaceFrom: start to: stop with: replacement 
  	startingAt: repStart  
  	<primitive: 105>
  	"
  	| array start stop repl replStart hdr arrayFmt totalLength arrayInstSize replFmt replInstSize srcIndex |
  	array := self stackValue: 4.
  	start := self stackIntegerValue: 3.
  	stop := self stackIntegerValue: 2.
  	repl := self stackValue: 1.
  	replStart := self stackIntegerValue: 0.
  
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	(objectMemory isImmediate: repl) ifTrue: "can happen in LgInt copy"
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	(objectMemory isObjImmutable: array) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	self cppIf: IMMUTABILITY ifTrue:
- 			[(objectMemory isImmutable: array) ifTrue:
- 				[^self primitiveFailFor: PrimErrNoModification]].
  
  	hdr := objectMemory baseHeader: array.
  	arrayFmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: array baseHeader: hdr format: arrayFmt.
  	arrayInstSize := objectMemory fixedFieldsOf: array format: arrayFmt length: totalLength.
  	(start >= 1 and: [start - 1 <= stop and: [stop + arrayInstSize <= totalLength]]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  
  	hdr := objectMemory baseHeader: repl.
  	replFmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: repl baseHeader: hdr format: replFmt.
  	replInstSize := objectMemory fixedFieldsOf: repl format: replFmt length: totalLength.
  	(replStart >= 1 and: [stop - start + replStart + replInstSize <= totalLength]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  
  	"Still to do: rewrite the below to accomodate short & long access"
  	(objectMemory hasSpurMemoryManagerAPI
  	 and: [(arrayFmt between: objectMemory firstShortFormat and: objectMemory firstLongFormat - 1)
  		or: [arrayFmt = objectMemory sixtyFourBitIndexableFormat]]) ifTrue:
  		[^self primitiveFailFor: PrimErrUnsupported].
  
  	"Array formats (without byteSize bits, if bytes array) must be the same"
  	arrayFmt < objectMemory firstByteFormat
  		ifTrue: [arrayFmt = replFmt ifFalse:
  					[^self primitiveFailFor: PrimErrInappropriate]]
  		ifFalse: [(arrayFmt bitAnd: objectMemory byteFormatMask) = (replFmt bitAnd: objectMemory byteFormatMask) ifFalse:
  					[^self primitiveFailFor: PrimErrInappropriate]].
  
  	srcIndex := replStart + replInstSize - 1.
  	"- 1 for 0-based access"
  
  	arrayFmt <= objectMemory lastPointerFormat
  		ifTrue:
  			[start + arrayInstSize - 1 to: stop + arrayInstSize - 1 do:
  				[:i |
  				objectMemory storePointer: i ofObject: array withValue: (objectMemory fetchPointer: srcIndex ofObject: repl).
  				srcIndex := srcIndex + 1]]
  		ifFalse:
  			[arrayFmt < objectMemory firstByteFormat
  				ifTrue: "32-bit-word type objects"
  					[start + arrayInstSize - 1 to: stop + arrayInstSize - 1 do:
  						[:i |
  						objectMemory storeLong32: i ofObject: array withValue: (objectMemory fetchLong32: srcIndex ofObject: repl).
  						srcIndex := srcIndex + 1]]
  				ifFalse: "byte-type objects"
  					[start + arrayInstSize - 1 to: stop + arrayInstSize - 1 do:
  						[:i |
  						objectMemory storeByte: i ofObject: array withValue: (objectMemory fetchByte: srcIndex ofObject: repl).
  						srcIndex := srcIndex + 1]]].
  	"We might consider comparing stop - start to some value here and using forceInterruptCheck"
  
  	self pop: argumentCount "leave rcvr on stack"!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV4"
  
  	NSSendIsPCAnnotated := false. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	NumSpecialSelectors := 32.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode)
  		(1  78   78 genPushConstantZeroBytecode)
  		(1  79   79 genPushConstantOneBytecode)
  
  		(1   80 101 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
+ 		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability needsFrameIfImmutability: -1)
+ 
- 		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
+ 		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
+ 		(2 233 233 genExtStoreLiteralVariableBytecode isMappedIfImmutability)
- 		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef)
- 		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
+ 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
+ 		(2 236 236 genExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
- 		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef)
- 		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
  		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped hasIRC)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		(2 245 245 genExtSendAbsentSelfBytecode isMapped hasIRC)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 genCallPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 254 254 genExtSendAbsentOuterBytecode isMapped hasIRC)
  
  		(3 255 255	unknownBytecode))!

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

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"SimpleStackBasedCogit initializeBytecodeTableForSqueakV3PlusClosures"
  
  	FirstSpecialSelector := 176.
  	NumSpecialSelectors := 32.
  	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 isInstVarRef)
  		(1  16   31 genPushTemporaryVariableBytecode)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
+ 		(1  96 103 genStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability needsFrameIfImmutability: -1)
- 		(1  96 103 genStoreAndPopReceiverVariableBytecode isInstVarRef 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)
  
  		(1 126 127 unknownBytecode)
  
  		(2 128 128 extendedPushBytecode isInstVarRef) "well, maybe inst var ref"
+ 		(2 129 129 extendedStoreBytecode isInstVarRef isMappedIfImmutability) "well, maybe inst var ref"
+ 		(2 130 130 extendedStoreAndPopBytecode isInstVarRef isMappedIfImmutability) "well, maybe inst var ref"
- 		(2 129 129 extendedStoreBytecode isInstVarRef) "well, maybe inst var ref"
- 		(2 130 130 extendedStoreAndPopBytecode isInstVarRef) "well, maybe inst var ref"
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isInstVarRef isMapped) "well, maybe inst var ref"
  		(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)),
  
  		((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  			ifTrue: [#((3 139 139 genCallPrimitiveBytecode))]
  			ifFalse: [#((1 139 139 unknownBytecode))]),
  
  	  #(
  		(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: Spur32BitMemoryManager>>changeClassOf:to: (in category 'interpreter access') -----
  changeClassOf: rcvr to: argClass
  	"Attempt to change the class of the receiver to the argument given that the
  	 format of the receiver matches the format of the argument.  If successful,
  	 answer 0, otherwise answer an error code indicating the reason for failure. 
  	 Fail if the format of the receiver is incompatible with the format of the argument,
  	 or if the argument is a fixed class and the receiver's size differs from the size
  	 that an instance of the argument should have."
  	<inline: false>
  	| classFormat fixedFields instFormat normalizedInstFormat newFormat classIndex |
+ 	(self isObjImmutable: rcvr) ifTrue:
+ 		[^PrimErrNoModification].
- 	self cppIf: IMMUTABILITY ifTrue:
- 			[(self isImmutable: rcvr) ifTrue: [ ^PrimErrNoModification]].
  	classFormat := self formatOfClass: argClass.
  	fixedFields := self fixedFieldsOfClassFormat: classFormat.
  	classFormat := self instSpecOfClassFormat: classFormat.
  	instFormat := self formatOf: rcvr.
  	normalizedInstFormat := self classFormatForInstanceFormat: instFormat.
  
  	(normalizedInstFormat > self lastPointerFormat
  	 and: [normalizedInstFormat = classFormat])
  		ifTrue: [newFormat := instFormat]
  		ifFalse:
  			[normalizedInstFormat <= self lastPointerFormat
  				ifTrue:
  					[classFormat > self lastPointerFormat ifTrue:
  						[^PrimErrInappropriate].
  					 (self numSlotsOf: rcvr) < fixedFields ifTrue:
  						[^PrimErrBadReceiver].
  					 newFormat := classFormat]
  				ifFalse:
  					[| instBytes |
  					instBytes := self numBytesOf: rcvr.
  					normalizedInstFormat caseOf: {
  						[self sixtyFourBitIndexableFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := classFormat].
  						[self firstLongFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 (classFormat = self sixtyFourBitIndexableFormat and: [instBytes anyMask: 1]) ifTrue:
  								[^PrimErrBadReceiver].
  							 newFormat := classFormat].
  						[self firstShortFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 1) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstByteFormat] 		
  									-> [newFormat := classFormat + (4 - instBytes bitAnd: 3)] }].
  						[self firstByteFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 7) ifTrue: [^PrimErrBadReceiver]].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver]].
  								[self firstShortFormat] 		
  									-> [(instBytes anyMask: 1) ifTrue: [^PrimErrBadReceiver]] }.
  							 newFormat := classFormat].
  						[self firstCompiledMethodFormat] ->
  							[classFormat ~= self firstCompiledMethodFormat ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := instFormat] }]].
  
  	(classIndex := self ensureBehaviorHash: argClass) < 0 ifTrue:
  		[^classIndex negated].
  	self set: rcvr classIndexTo: classIndex formatTo: newFormat.
  	"ok"
  	^0!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>changeClassOf:to: (in category 'interpreter access') -----
  changeClassOf: rcvr to: argClass
  	"Attempt to change the class of the receiver to the argument given that the
  	 format of the receiver matches the format of the argument.  If successful,
  	 answer 0, otherwise answer an error code indicating the reason for failure. 
  	 Fail if the format of the receiver is incompatible with the format of the argument,
  	 or if the argument is a fixed class and the receiver's size differs from the size
  	 that an instance of the argument should have."
  	<inline: false>
  	| classFormat fixedFields instFormat normalizedInstFormat newFormat classIndex |
+ 	(self isObjImmutable: rcvr) ifTrue:
+ 		[^PrimErrNoModification].
- 	self cppIf: IMMUTABILITY ifTrue:
- 			[(self isImmutable: rcvr) ifTrue: [ ^PrimErrNoModification]].
  	classFormat := self formatOfClass: argClass.
  	fixedFields := self fixedFieldsOfClassFormat: classFormat.
  	classFormat := self instSpecOfClassFormat: classFormat.
  	instFormat := self formatOf: rcvr.
  	normalizedInstFormat := self classFormatForInstanceFormat: instFormat.
  
  	(normalizedInstFormat > self lastPointerFormat
  	 and: [normalizedInstFormat = classFormat])
  		ifTrue: [newFormat := instFormat]
  		ifFalse:
  			[normalizedInstFormat <= self lastPointerFormat
  				ifTrue:
  					[classFormat > self lastPointerFormat ifTrue:
  						[^PrimErrInappropriate].
  					 (self numSlotsOf: rcvr) < fixedFields ifTrue:
  						[^PrimErrBadReceiver].
  					 newFormat := classFormat]
  				ifFalse:
  					[| instBytes |
  					instBytes := self numBytesOf: rcvr.
  					normalizedInstFormat caseOf: {
  						[self sixtyFourBitIndexableFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := classFormat].
  						[self firstLongFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 (classFormat = self sixtyFourBitIndexableFormat and: [instBytes anyMask: 1]) ifTrue:
  								[^PrimErrBadReceiver].
  							 newFormat := classFormat].
  						[self firstShortFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 7) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat + (2 - instBytes bitAnd: 1)].
  								[self firstByteFormat] 		
  									-> [newFormat := classFormat + (8 - instBytes bitAnd: 7)] }].
  						[self firstByteFormat] ->
  							[(classFormat < self sixtyFourBitIndexableFormat
  							  or: [classFormat >= self firstCompiledMethodFormat]) ifTrue:
  								[^PrimErrInappropriate].
  							 classFormat caseOf: {
  								[self sixtyFourBitIndexableFormat]
  									-> [(instBytes anyMask: 7) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat].
  								[self firstLongFormat] 		
  									-> [(instBytes anyMask: 3) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat + (2 - instBytes bitAnd: 1)].
  								[self firstShortFormat] 		
  									-> [(instBytes anyMask: 1) ifTrue: [^PrimErrBadReceiver].
  										newFormat := classFormat + (4 - instBytes bitAnd: 3)] }.
  							 newFormat := classFormat].
  						[self firstCompiledMethodFormat] ->
  							[classFormat ~= self firstCompiledMethodFormat ifTrue:
  								[^PrimErrInappropriate].
  							 newFormat := instFormat] }]].
  
  	(classIndex := self ensureBehaviorHash: argClass) < 0 ifTrue:
  		[^classIndex negated].
  	self set: rcvr classIndexTo: classIndex formatTo: newFormat.
  	"ok"
  	^0!

Item was added:
+ ----- Method: SpurMemoryManager>>isObjImmutable: (in category 'header access') -----
+ isObjImmutable: anOop
+ 	<inline: true>
+ 	^self cppIf: IMMUTABILITY
+ 		ifTrue: [self isImmutable: anOop]
+ 		ifFalse: [false]!

Item was changed:
  ----- Method: SpurMemoryManager>>isOopValidBecome: (in category 'become implementation') -----
  isOopValidBecome: oop
  	"Answers 0 if the oop can be become.
  	Answers an error code in the other case"
  	(self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
  	(self isPinned: oop) ifTrue: [^PrimErrObjectIsPinned].
+ 	(self isObjImmutable: oop) ifTrue: [^PrimErrNoModification].
+ 	^0!
- 	self 
- 		cppIf: IMMUTABILITY
- 		ifTrue: [ (self isImmutable: oop) ifTrue: [^PrimErrNoModification] ].
- 	^ 0!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointerImmutabilityCheck:ofObject:withValue: (in category 'object access') -----
  storePointerImmutabilityCheck: fieldIndex ofObject: objOop withValue: valuePointer
  	"Note must check here for stores of young objects into old ones."
+ 	<inline: true> "Must be inlined for the normal send in cannotAssign:to:withIndex:"
- 	<inline: true> "normal send in cannotAssign"
  
  	self cppIf: IMMUTABILITY ifTrue: 
+ 		[self deny: (self isImmediate: objOop).
+ 		 (self isImmutable: objOop) ifTrue: 
+ 			[^coInterpreter cannotAssign: valuePointer to: objOop withIndex: fieldIndex]].
- 		[ self assert: (self isImmediate: objOop) not.
- 		(self isImmutable: objOop) ifTrue: 
- 			[ ^ coInterpreter cannotAssign: valuePointer to: objOop withIndex: fieldIndex ] ].
  	
+ 	^self storePointer: fieldIndex ofObject: objOop withValue: valuePointer!
- 	^ self storePointer: fieldIndex ofObject: objOop withValue: valuePointer!

Item was changed:
  ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| vmClass |
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	vmClass := aCCodeGenerator vmClass. "Generate primitiveTable etc based on vmClass, not just StackInterpreter"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h> /* for e.g. alloca */';
  		addHeaderFile:'<setjmp.h>';
  		addHeaderFile:'<wchar.h> /* for wint_t */';
  		addHeaderFile:'"vmCallback.h"';
  		addHeaderFile:'"sqMemoryFence.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	vmClass declareInterpreterVersionIn: aCCodeGenerator defaultName: 'Stack'.
  	aCCodeGenerator
  		var: #interpreterProxy  type: #'struct VirtualMachine*'.
  	aCCodeGenerator
  		declareVar: #sendTrace type: 'volatile int';
  		declareVar: #byteCount type: 'unsigned long'.
  	"These need to be pointers or unsigned."
  	self declareC: #(instructionPointer method newMethod)
  		as: #usqInt
  		in: aCCodeGenerator.
  	"These are all pointers; char * because Slang has no support for C pointer arithmetic."
  	self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit stackMemory breakSelector)
  		as: #'char *'
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #breakSelectorLength
  		declareC: 'sqInt breakSelectorLength = MinSmallInteger'.
  	self declareC: #(stackPage overflowedPage)
  		as: #'StackPage *'
  		in: aCCodeGenerator.
  	aCCodeGenerator removeVariable: 'stackPages'.  "this is an implicit receiver in the translated code."
+ 	NewspeakVM ifFalse:
+ 		[aCCodeGenerator
+ 			removeVariable: 'localAbsentReceiver';
+ 			removeVariable: 'localAbsentReceiverOrZero';
+ 			removeVariable: 'nsMethodCache'].
- 	NewspeakVM
- 		ifTrue:
- 			[aCCodeGenerator
- 				const: #EnforceAccessControl
- 				declareC: ('#if !!defined(EnforceAccessControl) /* Allow EnforceAccessControl to be overridden on the compiler command line */\# define EnforceAccessControl ', (aCCodeGenerator cLiteralFor: EnforceAccessControl),'\#endif') withCRs]
- 		ifFalse:
- 			[aCCodeGenerator
- 				removeVariable: 'localAbsentReceiver';
- 				removeVariable: 'localAbsentReceiverOrZero';
- 				removeVariable: 'nsMethodCache'].
  	"This defines bytecodeSetSelector as 0 if MULTIPLEBYTECODESETS
  	 is not defined, for the benefit of the interpreter on slow machines."
  	aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS).
  	MULTIPLEBYTECODESETS == false ifTrue:
  		[aCCodeGenerator
  			removeVariable: 'extA';
  			removeVariable: 'extB';
  			removeVariable: 'bytecodeSetSelector'].
  	aCCodeGenerator
  		var: #methodCache
  		declareC: 'long methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #nsMethodCache
  		declareC: 'long nsMethodCache[NSMethodCacheSize + 1 /* ', (NSMethodCacheSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #atCache
  		declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #primitiveTable
  		declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', vmClass primitiveTableString.
  	vmClass primitiveTable do:
  		[:symbolOrNot|
  		(symbolOrNot isSymbol
  		 and: [symbolOrNot ~~ #primitiveFail]) ifTrue:
  			[(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil:
  				[:tMethod| tMethod returnType: #void]]].
  	vmClass objectMemoryClass hasSpurMemoryManagerAPI
  		ifTrue:
  			[aCCodeGenerator
  				var: #primitiveAccessorDepthTable
  				type: 'signed char'
  				sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */'
  				array: vmClass primitiveAccessorDepthTable]
  		ifFalse:
  			[aCCodeGenerator removeVariable: #primitiveAccessorDepthTable].
  	aCCodeGenerator
  		var: #primitiveFunctionPointer
  		declareC: 'void (*primitiveFunctionPointer)()'.
  	aCCodeGenerator
  		var: #externalPrimitiveTable
  		declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)'.
  	aCCodeGenerator var: #showSurfaceFn type: #'void *'.
  	aCCodeGenerator
  		var: #jmpBuf
  		declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedCallbacks
  		declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #suspendedMethods
  		declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #interruptCheckChain
  		declareC: 'void (*interruptCheckChain)(void) = 0'.
  
  	self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs
  								longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
  								"these are high-frequency enough that they're overflowing quite quickly on modern hardware"
  								statProcessSwitch statIOProcessEvents statForceInterruptCheck
  								statCheckForEvents statStackOverflow statStackPageDivorce)
  		in: aCCodeGenerator.
  	aCCodeGenerator var: #nextProfileTick type: #sqLong!

Item was changed:
  ----- Method: StackInterpreter class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	STACKVM := true.
  
  	"These flags function to identify a GC operation, or
  	 to specify what operations the leak checker should be run for."
  	GCModeFull := 1.				"stop-the-world global GC"
  	GCModeNewSpace := 2.		"Spur's scavenge, or V3's incremental"
  	GCModeIncremental := 4.		"incremental global gc (Dijkstra tri-colour marking); as yet unimplemented"
  	GCModeBecome := 8.			"v3 post-become sweeping"
  	GCModeImageSegment := 16.	"just a flag for leak checking image segments"
  
  	StackPageTraceInvalid := -1.
  	StackPageUnreached := 0.
  	StackPageReachedButUntraced := 1.
  	StackPageTraced := 2.
  
  	DumpStackOnLowSpace := 0.
  	PrimitiveExternalCallIndex := 117. "Primitive index for #primitiveExternalCall"
  	MillisecondClockMask := 16r1FFFFFFF.
  	"Note: The external primitive table should actually be dynamically sized but for the sake of inferior platforms (e.g., Mac :-) who cannot allocate memory in any reasonable way, we keep it static (and cross our fingers...)"
  	MaxExternalPrimitiveTableSize := 4096. "entries"
  
  	MaxJumpBuf := 32. "max. callback depth"
  	FailImbalancedPrimitives := initializationOptions at: #FailImbalancedPrimitives ifAbsentPut: [true].
+ 	EnforceAccessControl := initializationOptions at: #EnforceAccessControl ifAbsent: [true]!
- 
- 	EnforceAccessControl := initializationOptions at: #EnforceAccessControl ifAbsentPut: [false]!

Item was changed:
  ----- Method: StackInterpreter>>commonAtPut: (in category 'indexing primitive support') -----
  commonAtPut: stringy
  	"This code is called if the receiver responds primitively to at:Put:.
  	 N.B. this does *not* use the at cache, instead inlining stObject:at:put:.
  	 Using the at cache here would require that callers set messageSelector
  	 and lkupClass and that is onerous and error-prone, and in any case,
  	 inlining produces much better performance than using the at cache here."
  	| value index rcvr |
  	<inline: true> "to get it inlined in primitiveAtPut and primitiveStringAtPut"
  	self initPrimCall.
  	rcvr := self stackValue: 2.
  	index := self stackValue: 1.
  	value := self stackTop.
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
  	"No need to test for large positive integers here.  No object has 1g elements"
  	((objectMemory isNonIntegerObject: index)
  	 or: [argumentCount > 2 "e.g. object:basicAt:put:"
  		 and: [objectMemory isForwarded: rcvr]]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	(objectMemory isObjImmutable: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	self cppIf: IMMUTABILITY ifTrue:
- 		[(objectMemory isImmutable: rcvr) ifTrue:
- 			[^self primitiveFailFor: PrimErrNoModification]].
  	index := objectMemory integerValueOf: index.
  	stringy
  		ifTrue: [self stObject: rcvr at: index put: (self asciiOfCharacter: value)]
  		ifFalse: [self stObject: rcvr at: index put: value].
  	self successful ifTrue:
  		[self pop: argumentCount+1 thenPush: value]!

Item was changed:
  ----- Method: StackInterpreter>>externalInstVar:ofContext:put: (in category 'frame access') -----
  externalInstVar: index ofContext: maybeMarriedContext put: anOop
  	| theFP thePage onCurrentPage |
  	<var: #theFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	self assert: (objectMemory isContext: maybeMarriedContext).
  	self externalWriteBackHeadFramePointers.
  	"Assign the field of a married context."
+ 	self deny: (objectMemory isObjImmutable: maybeMarriedContext).
  	(self isStillMarriedContext: maybeMarriedContext) ifFalse:
  		[objectMemory storePointer: index ofObject: maybeMarriedContext withValue: anOop.
  		 index = StackPointerIndex ifTrue:
  			[self ensureContextIsExecutionSafeAfterAssignToStackPointer: maybeMarriedContext].
  		 ^nil].
  	theFP := self frameOfMarriedContext: maybeMarriedContext.
  	thePage := stackPages stackPageFor: theFP.
  	self assert: stackPage = stackPages mostRecentlyUsedPage.
  	onCurrentPage := thePage = stackPage.
  	index == SenderIndex
  		ifTrue:
  			[self storeSenderOfFrame: theFP withValue: anOop]
  		ifFalse:
  			[self externalDivorceFrame: theFP andContext: maybeMarriedContext.
  			 objectMemory storePointer: index ofObject: maybeMarriedContext withValue: anOop.
  			 index = StackPointerIndex ifTrue:
  				[self ensureContextIsExecutionSafeAfterAssignToStackPointer: maybeMarriedContext]].
  	onCurrentPage
  		ifTrue:
  			[framePointer := stackPage headFP.
  			 stackPointer := stackPage headSP]
  		ifFalse:
  			[stackPages markStackPageMostRecentlyUsed: stackPage].
  	stackPages assert: stackPage = stackPages mostRecentlyUsedPage.
  	stackPages assert: stackPages pageListIsWellFormed.
  	stackPages assert: self validStackPageBaseFrames!

Item was changed:
  ----- Method: StackInterpreter>>instVar:ofContext:put: (in category 'frame access') -----
  instVar: index ofContext: aMarriedContext put: anOop
  	| theFP |
  	"Assign the field of a married context.  The important case to optimize is
  	 assigning the sender.  We could also consider optimizing assigning the IP but
  	 typically that is followed by an assignment to the stack pointer and we can't
  	 efficiently assign the stack pointer because it involves moving frames around."
  	<inline: true>
  	self assert: (self isMarriedOrWidowedContext: aMarriedContext).
+ 	self deny: (objectMemory isObjImmutable: aMarriedContext).
  	self writeBackHeadFramePointers.
  	(self isStillMarriedContext: aMarriedContext) ifFalse:
  		[objectMemory storePointer: index ofObject: aMarriedContext withValue: anOop.
  		 index = StackPointerIndex ifTrue:
  			[self ensureContextIsExecutionSafeAfterAssignToStackPointer: aMarriedContext].
  		 ^nil].
  	theFP := self frameOfMarriedContext: aMarriedContext.
  	index == SenderIndex ifTrue:
  		[| thePage onCurrentPage |
  		 thePage := stackPages stackPageFor: theFP.
  		 self assert: stackPage = stackPages mostRecentlyUsedPage.
  		 onCurrentPage := thePage = stackPage.
  		 self storeSenderOfFrame: theFP withValue: anOop.
  		 onCurrentPage
  			ifTrue:
  				[localFP := stackPage headFP.
  				 localSP := stackPage headSP]
  			ifFalse:
  				[stackPages markStackPageMostRecentlyUsed: stackPage].
  		 ^nil].
  	self externalizeIPandSP.
  	self externalDivorceFrame: theFP andContext: aMarriedContext.
  	objectMemory storePointer: index ofObject: aMarriedContext withValue: anOop.
  	index = StackPointerIndex ifTrue:
  		[self ensureContextIsExecutionSafeAfterAssignToStackPointer: aMarriedContext].
  	self internalizeIPandSP.
  	"Assigning various fields can force a divorce which can change the stackPage."
  	stackPages markStackPageMostRecentlyUsed: stackPage.
  	self assertValidExecutionPointe: localIP asUnsignedInteger r: localFP s: localSP imbar: true line: #'__LINE__'!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveInstVarAtPut (in category 'object access primitives') -----
  primitiveInstVarAtPut
  	| newValue index rcvr hdr fmt totalLength fixedFields |
  	newValue := self stackTop.
  	index := self stackValue: 1.
  	rcvr := self stackValue: 2.
  	((objectMemory isNonIntegerObject: index)
  	 or: [argumentCount > 2 "e.g. object:instVarAt:put:"
  		and: [objectMemory isOopForwarded: rcvr]]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	(objectMemory isImmediate: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadReceiver].
+ 	(objectMemory isObjImmutable: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrNoModification].
- 	(objectMemory isImmediate: rcvr) ifTrue: [ ^ self primitiveFailFor: PrimErrInappropriate].
- 	self 
- 		cppIf: IMMUTABILITY 
- 		ifTrue: [ (objectMemory isImmutable: rcvr) ifTrue: [ ^ self primitiveFailFor: PrimErrNoModification] ].
  	index := objectMemory integerValueOf: index.
  	hdr := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
  	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
  	(index >= 1 and: [index <= fixedFields]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	(fmt = objectMemory indexablePointersFormat
  	 and: [objectMemory isContextHeader: hdr])
  		ifTrue: [self externalInstVar: index - 1 ofContext: rcvr put: newValue]
  		ifFalse: [self subscript: rcvr with: index storing: newValue format: fmt].
  	self pop: argumentCount + 1 thenPush: newValue!

Item was changed:
  SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
+ 	instanceVariableNames: 'prevBCDescriptor numPushNilsFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode'
- 	instanceVariableNames: 'prevBCDescriptor numPushNilsFunction pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC debugStackPointers debugFixupBreaks debugBytecodePointers realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs deadCode'
  	classVariableNames: ''
  	poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!
  
  !StackToRegisterMappingCogit commentStamp: 'eem 12/19/2010 18:12' prior: 0!
  StackToRegisterMappingCogit is an optimizing code generator that eliminates a lot of stack operations and inlines some special selector arithmetic.  It does so by a simple stack-to-register mapping scheme based on deferring the generation of code to produce operands until operand-consuming operations.  The operations that consume operands are sends, stores and returns.
  
  See methods in the class-side documentation protocol for more detail.
  
  Instance Variables
  	callerSavedRegMask:							<Integer>
  	ceEnter0ArgsPIC:								<Integer>
  	ceEnter1ArgsPIC:								<Integer>
  	ceEnter2ArgsPIC:								<Integer>
  	ceEnterCogCodePopReceiverArg0Regs:		<Integer>
  	ceEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	debugBytecodePointers:						<Set of Integer>
  	debugFixupBreaks:								<Set of Integer>
  	debugStackPointers:							<CArrayAccessor of (Integer|nil)>
  	methodAbortTrampolines:						<CArrayAccessor of Integer>
  	methodOrBlockNumTemps:						<Integer>
  	optStatus:										<Integer>
  	picAbortTrampolines:							<CArrayAccessor of Integer>
  	picMissTrampolines:							<CArrayAccessor of Integer>
  	realCEEnterCogCodePopReceiverArg0Regs:		<Integer>
  	realCEEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
  	regArgsHaveBeenPushed:						<Boolean>
  	simSelf:											<CogSimStackEntry>
  	simSpillBase:									<Integer>
  	simStack:										<CArrayAccessor of CogSimStackEntry>
  	simStackPtr:									<Integer>
  	traceSimStack:									<Integer>
  
  callerSavedRegMask
  	- the bitmask of the ABI's caller-saved registers
  
  ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
  	- the trampoline for entering an N-arg PIC
  
  ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
  	- teh trampoline for entering a method with N register args
  	
  debugBytecodePointers
  	- a Set of bytecode pcs for setting breakpoints (simulation only)
  
  debugFixupBreaks
  	- a Set of fixup indices for setting breakpoints (simulation only)
  
  debugStackPointers
  	- an Array of stack depths for each bytecode for code verification
  
  methodAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  methodOrBlockNumTemps
  	- the number of method or block temps (including args) in the current compilation unit (method or block)
  
  optStatus
  	- the variable used to track the status of ReceiverResultReg for avoiding reloading that register with self between adjacent inst var accesses
  
  picAbortTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  picMissTrampolines
  	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
  
  realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs
  	- the real trampolines for ebtering machine code with N reg args when in the Debug regime
  
  regArgsHaveBeenPushed
  	- whether the register args have been pushed before frame build (e.g. when an interpreter primitive is called)
  
  simSelf
  	- the simulation stack entry representing self in the current compilation unit
  
  simSpillBase
  	- the variable tracking how much of the simulation stack has been spilled to the real stack
  
  simStack
  	- the simulation stack itself
  
  simStackPtr
  	- the pointer to the top of the simulation stack
  !
  StackToRegisterMappingCogit class
  	instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV4"
  
  	numPushNilsFunction := #v4:Num:Push:Nils:.
  	pushNilSizeFunction := #v4PushNilSize:numInitialNils:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by SendAbsentImplicit"
  	FirstSpecialSelector := 80.
  	NumSpecialSelectors := 32.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode isInstVarRef needsFrameNever: 1)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode needsFrameNever: 1)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode needsFrameIfExtBGT2: 1)
  		(1  78   78 genPushConstantZeroBytecode needsFrameNever: 1)
  		(1  79   79 genPushConstantOneBytecode needsFrameNever: 1)
  
  		(1   80   80 genSpecialSelectorArithmetic isMapped AddRR)
  		(1   81   81 genSpecialSelectorArithmetic isMapped SubRR)
  		(1   82   82 genSpecialSelectorComparison isMapped JumpLess)
  		(1   83   83 genSpecialSelectorComparison isMapped JumpGreater)
  		(1   84   84 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1   85   85 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1   86   86 genSpecialSelectorComparison isMapped JumpZero)
  		(1   87   87 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1   88   93 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1   94   94 genSpecialSelectorArithmetic isMapped AndRR)
  		(1   95   95 genSpecialSelectorArithmetic isMapped OrRR)
  		(1   96 101 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  			
  		(1 176 183 genStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability needsFrameIfImmutability: -1)
  			
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension					needsFrameNever: 0)
  		(2 225 225 extBBytecode extension					needsFrameNever: 0)
  		(2 226 226 genExtPushReceiverVariableBytecode isInstVarRef)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
+ 		(2 233 233 genExtStoreLiteralVariableBytecode isMappedIfImmutability)
- 		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
+ 		(2 236 236 genExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
- 		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
  		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped hasIRC)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		(2 245 245	genExtSendAbsentSelfBytecode isMapped hasIRC)
  
  		(2 246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 genCallPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 254 254	genExtSendAbsentOuterBytecode isMapped hasIRC)
  
  		(3 255 255	unknownBytecode))!

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

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	super setInterpreter: aCoInterpreter.
  
  	methodAbortTrampolines := CArrayAccessor on: (Array new: self numRegArgs + 2).
  	picAbortTrampolines := CArrayAccessor on: (Array new: self numRegArgs + 2).
  	picMissTrampolines := CArrayAccessor on: (Array new: self numRegArgs + 2).
  
  	simStack := CArrayAccessor on: ((1 to: 256) collect: [:i| CogSimStackEntry new cogit: self]).
  	simSelf := CogSimStackEntry new cogit: self.
  	optStatus := CogSSOptStatus new.
  
  	debugFixupBreaks := self class initializationOptions at: #debugFixupBreaks ifAbsent: [Set new].
- 	debugBytecodePointers := self class initializationOptions at: #debugBytecodePointers ifAbsent: [Set new].
  
  	numPushNilsFunction := self class numPushNilsFunction.
  	pushNilSizeFunction := self class pushNilSizeFunction!

Item was added:
+ ----- Method: TDefineNode>>isDefine (in category 'testing') -----
+ isDefine
+ 
+ 	^true!

Item was added:
+ ----- Method: TParseNode>>isDefine (in category 'testing') -----
+ isDefine
+ 
+ 	^false!

Item was changed:
  SharedPool subclass: #VMBasicConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BaseHeaderSize Byte0Mask Byte0Shift Byte1Mask Byte1Shift Byte1ShiftNegated Byte2Mask Byte2Shift Byte3Mask Byte3Shift Byte3ShiftNegated Byte4Mask Byte4Shift Byte4ShiftNegated Byte5Mask Byte5Shift Byte5ShiftNegated Byte6Mask Byte6Shift Byte7Mask Byte7Shift Byte7ShiftNegated Bytes3to0Mask Bytes7to4Mask BytesPerOop BytesPerWord COGMTVM COGVM DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCModeBecome GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace IMMUTABILITY MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrUnsupported PrimErrWritePastObject PrimNoErr SPURVM STACKVM SistaVM VMBIGENDIAN'
- 	classVariableNames: 'BaseHeaderSize Byte0Mask Byte0Shift Byte1Mask Byte1Shift Byte1ShiftNegated Byte2Mask Byte2Shift Byte3Mask Byte3Shift Byte3ShiftNegated Byte4Mask Byte4Shift Byte4ShiftNegated Byte5Mask Byte5Shift Byte5ShiftNegated Byte6Mask Byte6Shift Byte7Mask Byte7Shift Byte7ShiftNegated Bytes3to0Mask Bytes7to4Mask BytesPerOop BytesPerWord COGMTVM COGVM DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCModeBecome GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace IMMUTABILITY MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrUnsupported PrimErrWritePastObject PrimNoErr STACKVM SistaVM VMBIGENDIAN'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMBasicConstants commentStamp: '<historical>' prior: 0!
  I am a shared pool for basic constants upon which the VM as a whole depends.
  
  self ensureClassPool.
  self classPool declare: #BytesPerWord from: VMSqueakV3ObjectRepresentationConstants classPool.
  self classPool declare: #BaseHeaderSize from: VMSqueakV3ObjectRepresentationConstants classPool
  (ObjectMemory classPool keys select: [:k| k beginsWith: 'Byte']) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!

Item was added:
+ ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
+ namesDefinedAtCompileTime
+ 	"Answer the set of names for variables that should be defined at compile time.
+ 	 Some of these get default values during simulation, and hence get defaulted in
+ 	 the various initializeMiscConstants methods.  But that they have values should
+ 	 /not/ cause the code generator to do dead code elimination based on their
+ 	 default values."
+ 	^#(	VMBIGENDIAN
+ 		IMMUTABILITY
+ 		STACKVM COGVM COGMTVM SPURVM
+ 		"Pharo vs Squeak" PharoVM
+ 		"Newspeak" EnforceAccessControl)!

Item was removed:
- ----- Method: VMClass class>>copyOptionsBackTo: (in category 'initialization') -----
- copyOptionsBackTo: optionsDictionary
- 	"Ugh.  Copy back those options that the CCodeGenerator will do
- 	 dead-code elimination for that are not yet set in optionsDictionary.
- 	 This lets the CCodeGenerator see defaults for the options below."
- 
- 	optionsDictionary ifNil: [^self].
- 	initializationOptions ifNil: [^self].
- 	#(MULTIPLEBYTECODESETS IMMUTABILITY) do:
- 		[:option|
- 		((initializationOptions includesKey: option)
- 		 and: [(optionsDictionary includesKey: option) not]) ifTrue:
- 			[optionsDictionary at: option put: (initializationOptions at: option)]]!

Item was changed:
  ----- Method: VMClass class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
+ 	"Falsify the `what type of VM is this?' flags that are defined in the various interp.h files.
- 	"Falsify the `what type of VM is this?' flags that are defined in the various interp.h files,
- 	 or in the case of VMBIGENDIAN the various sqConfig.h files.
  	 Subclass implementations need to include a super initializeMiscConstants"
  
  	| omc |
- 	"VMBIGENDIAN & IMMUTABILITY are intended to be defined on the C compiler command line/in an include file, etc.
- 	 Don't inline them."
  	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
+ 	SPURVM := STACKVM := COGVM := COGMTVM := false.
- 	IMMUTABILITY class.
  
- 	self isInterpreterClass ifTrue:
- 		[STACKVM := COGVM := COGMTVM := false].
- 
  	initializationOptions ifNil: [self initializationOptions: Dictionary new].
  	omc := initializationOptions at: #ObjectMemory ifAbsent: nil.
  	(omc isNil and: [self defaultObjectMemoryClass notNil]) ifTrue:
  		[omc := initializationOptions at: #ObjectMemory put: self defaultObjectMemoryClass name].
  	initializationOptions
  		at: #SqueakV3ObjectMemory	"the good ole default"
  			ifAbsentPut: (omc
  					ifNil: [true]
  					ifNotNil: [(Smalltalk at: omc) includesBehavior: ObjectMemory]);
  		at: #SpurObjectMemory		"the new contender"
  			ifAbsentPut: (omc
  					ifNil: [false]
  					ifNotNil: [(Smalltalk at: omc) includesBehavior: SpurMemoryManager]).
  
  	"Use ifAbsentPut: so that they will get copied back to the
  	 VMMaker's options and dead code will likely be eliminated."
  	PharoVM := initializationOptions at: #PharoVM ifAbsentPut: [false].
  	NewspeakVM := initializationOptions at: #NewspeakVM ifAbsentPut: [false].
  	SistaVM := initializationOptions at: #SistaVM ifAbsentPut: [false].
+ 	"But not these; they're compile-time"
+ 	MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsent: [false].
+ 	IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsent: [false].
- 	MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false].
  
+ 	"These must be set only if specified, not defaulted, because they are set on the command line or in include files."
+ 	initializationOptions
+ 		at: #VMBIGENDIAN	ifPresent: [:value| VMBIGENDIAN := value];
+ 		at: #STACKVM		ifPresent: [:value| STACKVM := value];
+ 		at: #COGVM		ifPresent: [:value| COGVM := initializationOptions at: #COGVM];
+ 		at: #COGMTVM		ifPresent: [:value| COGMTVM := initializationOptions at: #COGMTVM]!
- 	"These for scripts etc... Usually they should get set by an Interpreter class's initializeMiscConstantsWith:"
- 	(initializationOptions includesKey: #STACKVM) ifTrue:
- 		[STACKVM := initializationOptions at: #STACKVM].
- 	(initializationOptions includesKey: #COGVM) ifTrue:
- 		[COGVM := initializationOptions at: #COGVM].
- 	(initializationOptions includesKey: #COGMTVM) ifTrue:
- 		[COGMTVM := initializationOptions at: #COGMTVM]!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCog64VM (in category 'configurations') -----
  generateNewspeakSpurCog64VM
  	"No primitives since we can use those for the Spur Cog Newspeak VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur64BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
+ 				NewspeakVM true)
- 				NewspeakVM true
- 				EnforceAccessControl true)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspur64src') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including:#()
  !

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCogVM (in category 'configurations') -----
  generateNewspeakSpurCogVM
  	"This tree also includes the Newspeak plugins.  But once the Alien plugins are harmonised
  	 (which can be done now immutability support is being added to Spur) all VMs can share a
  	 single set of plugin sources."
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
+ 				NewspeakVM true)
- 				NewspeakVM true
- 				EnforceAccessControl true)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspursrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation
  					DeflatePlugin DSAPlugin DropPlugin FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin
  					ImmX11Plugin JPEGReadWriter2Plugin JPEGReaderPlugin LargeIntegersPlugin
  					Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin RePlugin
  					SecurityPlugin SocketPlugin SoundPlugin SqueakSSLPlugin SurfacePlugin
  					UUIDPlugin UnixOSProcessPlugin UnixAioPlugin
  					VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)
  !

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStack64VM (in category 'configurations') -----
  generateNewspeakSpurStack64VM
  	"No primitives since we can use those from the Spur Cog Newspeak VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #( ObjectMemory Spur64BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
+ 				FailImbalancedPrimitives false)
- 				FailImbalancedPrimitives false
- 				EnforceAccessControl true)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspurstack64src') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStackVM (in category 'configurations') -----
  generateNewspeakSpurStackVM
  	"No primitives since we can use those from the Spur Cog Newspeak VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(	ObjectMemory Spur32BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
+ 				FailImbalancedPrimitives false)
- 				FailImbalancedPrimitives false
- 				EnforceAccessControl true)
  		to: (FileDirectory default directoryNamed: self sourceTree, '/nsspurstacksrc') fullName
  		platformDir: (FileDirectory default directoryNamed: self sourceTree, '/platforms') fullName
  		including: #()!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForCogit:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForCogit: cogitClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  	"Answer the code generator for translating the cogit."
  
  	| cg cogitClasses |
  	cg := self createCogitCodeGenerator.
  
  	cg vmClass: cogitClass.
  	initializeClasses ifTrue:
  		[{ cogitClass. self interpreterClass. self interpreterClass objectMemoryClass } do:
  			[:cgc|
  			(cgc respondsTo: #initializeWithOptions:)
  				ifTrue: [cgc initializeWithOptions: optionsDictionary]
  				ifFalse: [cgc initialize]]].
  
  	cogitClasses := OrderedCollection withAll: (cogitClass withAllSuperclasses copyUpThrough: VMClass) reverse.
  	cogitClasses addAllLast: ((cogitClass ancilliaryClasses: optionsDictionary) reject: [:class| class isStructClass]).
  	cogitClasses do: [:cgc| cg addClass: cgc].
  	cg addStructClasses: (cg structClassesForTranslationClasses: cogitClasses).
  
  	getAPIMethods ifTrue:
  		[cg includeAPIFrom: (self
  								buildCodeGeneratorForInterpreter: self interpreterClass
  								includeAPIMethods: false
  								initializeClasses: false)].
  
- 	cg
- 		removeConstant: #VMBIGENDIAN; "this should be defined in platforms/??/vm/sqConfig.h"
- 		const: #IMMUTABILITY "this can be defined on the C compiler command line."
- 			declareC: ('#if !!defined(IMMUTABILITY)\/* Allow IMMUTABILITY to be overridden on the compiler command line */\# define IMMUTABILITY ', (cg cLiteralFor: false),'\#endif') withCRs.
- 
  	^cg!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForInterpreter:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForInterpreter: interpreterClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  	"Answer the code generator for translating the interpreter."
  
  	| cg interpreterClasses |
  	initializeClasses ifTrue:
  		[interpreterClass initializeWithOptions: optionsDictionary.
  		 interpreterClass hasCogit ifTrue:
  			[interpreterClass cogitClass initializeWithOptions: optionsDictionary]].
  
  	(cg := self createCodeGenerator) vmClass: interpreterClass.
  
  	"Construct interpreterClasses as all classes from interpreterClass &
  	 objectMemoryClass up to VMClass in superclass to subclass order."
  	interpreterClasses := OrderedCollection new.
  	{interpreterClass. interpreterClass objectMemoryClass} do:
  		[:vmClass| | theClass |
  		 theClass := vmClass.
  		 [theClass ~~ VMClass] whileTrue:
  			[interpreterClasses addFirst: theClass.
  			 theClass := theClass superclass]].
  	interpreterClasses
  		addFirst: VMClass;
  		addAllLast: (cg nonStructClassesForTranslationClasses: interpreterClasses).
  
  	initializeClasses ifTrue:
  		[interpreterClasses do:
  			[:ic|
  			(ic respondsTo: #initializeWithOptions:)
  				ifTrue: [ic initializeWithOptions: optionsDictionary]
  				ifFalse: [ic initialize]].
  		 (cg structClassesForTranslationClasses: interpreterClasses) do:
  			[:structClass| structClass initialize]].
  
  	cg addStructClasses: (cg structClassesForTranslationClasses: interpreterClasses).
  
  	interpreterClasses do: [:ic| cg addClass: ic].
  
  	getAPIMethods ifTrue:
  		[interpreterClass cogitClass ifNotNil:
  			[:cogitClass|
  			 cg includeAPIFrom: (self
  									buildCodeGeneratorForCogit: cogitClass
  									includeAPIMethods: false
  									initializeClasses: false)]].
  
- 	cg removeConstant: #VMBIGENDIAN; "this should be defined in platforms/??/vm/sqConfig.h"
- 		const: #IMMUTABILITY "this can be defined on the C compiler command line."
- 			declareC: ('#if !!defined(IMMUTABILITY)\/* Allow IMMUTABILITY to be overridden on the compiler command line */\# define IMMUTABILITY ', (cg cLiteralFor: false),'\#endif') withCRs.
- 
  	^cg!



More information about the Vm-dev mailing list