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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 7 22:52:20 UTC 2018


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

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

Name: VMMaker.oscog-eem.2408
Author: eem
Time: 7 June 2018, 3:51:43.72542 pm
UUID: a22d7480-0ba1-4f23-9116-32abed9941cd
Ancestors: VMMaker.oscog-cb.2407

Initialization:
Nuke the insane initializationOptions inst var in VMClass class and replace it by a simple class variable InitializationOptions.  This avoids stale initializationOptions dictionaries during initialization.  The exact symptom was the validation of options in VMClass class>>initializeMiscConstants; it wanted to check SpurmemoryManager's compactorClass, but since SpurMemoryManager's initialationOptions was stale it answered a bogus class.  Grasshopper, enlightenment comes slowly to some.

Consequently refactor ancilliaryClasses: to ancilliaryClasses (returning to an older style).

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

Item was changed:
  ----- Method: CCodeGenerator>>initializerForInstVar:inStartClass: (in category 'inlining') -----
  initializerForInstVar: varName inStartClass: aClass
  	| allClasses sizeBefore |
  	(aClass inheritsFrom: VMClass) ifFalse:
  		[^false].
  	allClasses := (aClass withAllSuperclasses copyUpTo: VMClass) asSet.
  	[sizeBefore := allClasses size.
  	 allClasses copy do:
  		[:class|
+ 		class ancilliaryClasses do:
- 		(class ancilliaryClasses: optionsDictionary) do:
  			[:ancilliary|
  			allClasses addAll: (ancilliary withAllSuperclasses copyUpTo: VMClass)]].
  	 sizeBefore ~= allClasses size] whileTrue.
  	allClasses do:
  		[:class|
  		(self initializerForInstVar: varName in: class) ifNotNil:
  			[:initializer| ^initializer]].
  	^nil!

Item was changed:
  ----- Method: CCodeGenerator>>nonStructClassesForTranslationClasses: (in category 'utilities') -----
  nonStructClassesForTranslationClasses: classes
  	"Answer in superclass order (any superclass precedes any subclass)
  	 the ancilliaryClasses that are not struct classes for all the given classes."
  	| nonStructClasses |
  	nonStructClasses := OrderedCollection new.
  	classes do:
  		[:aTranslationClass|
+ 		([aTranslationClass ancilliaryClasses]
- 		([aTranslationClass ancilliaryClasses: self options]
  				on: MessageNotUnderstood
  				do: [:ex|
+ 					ex message selector == #ancilliaryClasses
- 					ex message selector == #ancilliaryClasses:
  						ifTrue: [#()]
  						ifFalse: [ex pass]]) do:
  			[:class|
  			(vmClass isNil or: [vmClass isAcceptableAncilliaryClass: class]) ifTrue:
  				[(class isStructClass
  				 or: [(nonStructClasses includes: class)
  				 or: [classes includes: class]]) ifFalse:
  					[nonStructClasses addLast: class]]]].
  	^ChangeSet superclassOrder: nonStructClasses!

Item was changed:
  ----- Method: CCodeGenerator>>structClassesForTranslationClasses: (in category 'utilities') -----
  structClassesForTranslationClasses: classes
  	"Answer in superclass order (any superclass precedes any subclass)
  	 the ancilliaryClasses that are struct classes for all the given classes."
  	| theStructClasses |
  	theStructClasses := OrderedCollection new.
  	classes do:
  		[:aTranslationClass|
+ 		([aTranslationClass ancilliaryClasses]
- 		([aTranslationClass ancilliaryClasses: self options]
  				on: MessageNotUnderstood
  				do: [:ex|
+ 					ex message selector == #ancilliaryClasses
- 					ex message selector == #ancilliaryClasses:
  						ifTrue: [#()]
  						ifFalse: [ex pass]]) do:
  			[:class|
  			(class isStructClass
  			 and: [(vmClass isNil or: [vmClass isAcceptableAncilliaryClass: class])
  			 and: [(theStructClasses includes: class) not]]) ifTrue:
  				[theStructClasses addLast: class]]].
  	^ChangeSet superclassOrder: theStructClasses!

Item was added:
+ ----- Method: CoInterpreter class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^(super ancilliaryClasses copyWithout: InterpreterStackPages),
+ 	   {	CoInterpreterStackPages.
+ 		CogBlockMethod. NSSendCache },
+ 	((Cogit ancilliaryClasses) select: [:class| class inheritsFrom: CogBlockMethod])!

Item was removed:
- ----- Method: CoInterpreter class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	"Answer any extra classes to be included in the translation."
- 	^((super ancilliaryClasses: options) copyWithout: InterpreterStackPages),
- 	   {	CoInterpreterStackPages.
- 		CogBlockMethod. NSSendCache },
- 	((Cogit ancilliaryClasses: options) select: [:class| class inheritsFrom: CogBlockMethod])!

Item was added:
+ ----- Method: CoInterpreterMT class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^super ancilliaryClasses, { CogThreadManager. CogVMThread }!

Item was removed:
- ----- Method: CoInterpreterMT class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	^(super ancilliaryClasses: options), { CogThreadManager. CogVMThread }!

Item was changed:
  ----- Method: CoInterpreterMT class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  
  	"N.B. some of these DisownFlags are replicated in platforms/Cross/vm/sqVirtualMachine.h.
  	 Hence they should always be initialized."
  	DisownVMLockOutFullGC := 1.
  	DisownVMForProcessorRelinquish := 2.
  
+ 	(InitializationOptions at: #COGMTVM ifAbsent: [false]) == false ifTrue:
- 	(initializationOptions notNil
- 	 and: [(initializationOptions at: #COGMTVM ifAbsent: [false]) == false]) ifTrue:
  		[^self].
  
  	COGMTVM := true.
  
+ 	ReturnToThreadSchedulingLoop := 2 "setjmp/longjmp code."!
- 	ReturnToThreadSchedulingLoop := 2. "setjmp/longjmp code."!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCodeGen
  	"Deal wuth the fact that the number of trampolines depends on IMMUTABILITY
  	 and that IMMUTABILITY can be defined at compile time.  Yes, this is a mess."
  	| current values |
  	self assert: (CogObjectRepresentationForSpur allSubclasses allSatisfy:
  					[:sc|
  					 CogObjectRepresentationForSpur initializationOptions == sc initializationOptions]).
+ 	current := InitializationOptions at: #IMMUTABILITY ifAbsent: nil.
- 	current := initializationOptions at: #IMMUTABILITY ifAbsent: nil.
  	values := #(true false) collect:
  				[:bool|
+ 				 InitializationOptions at: #IMMUTABILITY put: bool.
- 				 initializationOptions at: #IMMUTABILITY put: bool.
  				 self cogitClass initializeNumTrampolines.
  				 (Cogit classPool at: #NumTrampolines) printString].
  	current
+ 		ifNil: [InitializationOptions removeKey: #IMMUTABILITY]
+ 		ifNotNil: [InitializationOptions at: #IMMUTABILITY put: current].
- 		ifNil: [initializationOptions removeKey: #IMMUTABILITY]
- 		ifNotNil: [initializationOptions at: #IMMUTABILITY put: current].
  	values first ~= values last ifTrue:
  		[aCodeGen addConstantForBinding: #NumTrampolines -> ('(IMMUTABILITY ? ' , values first , ' : ' , values last , ')')].
  	aCodeGen
  		var: #ceStoreTrampolines
  		declareC: ('#if IMMUTABILITY\sqInt ceStoreTrampolines[', NumStoreTrampolines printString, '];\#endif') withCRs!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
+ 	CheckRememberedInTrampoline := InitializationOptions at: #CheckRememberedInTrampoline ifAbsent: [false]!
- 	CheckRememberedInTrampoline := initializationOptions at: #CheckRememberedInTrampoline ifAbsent: [false]!

Item was changed:
  ----- Method: CogVMSimulator class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	super initializeWithOptions: optionsDictionary.
  
+ 	ByteCountsPerMicrosecond := InitializationOptions
- 	ByteCountsPerMicrosecond := initializationOptions
  										at: #ByteCountsPerMicrosecond
  										ifAbsent: [100]!

Item was changed:
  ----- Method: CogVMSimulator class>>initializeWithOptions:objectMemoryClass: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionaryOrArray objectMemoryClass: objectMemoryClassOrNil
  	"The relevant ObjectMemory, Interpreter and Cogit classes must be initialized in order.
  	 This happens notionally every time we start the simulator,
  	 but in fact happens when ever we instantiate a simulator."
+ 	InitializationOptions := optionsDictionaryOrArray isArray
- 	initializationOptions := optionsDictionaryOrArray isArray
  							ifTrue: [Dictionary newFromPairs: optionsDictionaryOrArray]
  							ifFalse: [optionsDictionaryOrArray].
  
- 	(self allSuperclasses copyUpThrough: InterpreterPrimitives) do:
- 		[:sc| sc initializationOptions: initializationOptions].
- 
  	(objectMemoryClassOrNil ifNil: [self objectMemoryClass])
+ 		initializeWithOptions: InitializationOptions.
- 		initializeWithOptions: initializationOptions.
  
+ 	self initializeWithOptions: InitializationOptions.
- 	self initializeWithOptions: initializationOptions.
  
  	(self cogitClass withAllSuperclasses copyUpTo: Cogit) reverseDo:
+ 		[:c| c initializeWithOptions: InitializationOptions]!
- 		[:c| c initializeWithOptions: initializationOptions]!

Item was changed:
  ----- Method: CogX64Compiler class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize various x64 instruction-related constants.
  	 [1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
  
  	"CogX64Compiler initialize"
  
  	self ~~ CogX64Compiler ifTrue: [^self].
  
+ 	InitializationOptions
- 	initializationOptions ifNil: [ initializationOptions := Dictionary new ].
- 	initializationOptions
  		at: #ABI
  		ifPresent: [:abi| SysV := abi asUppercase ~= #WIN64 and: [abi asUppercase ~= #'_WIN64']]
  		ifAbsent: [SysV := true]. "Default ABI; set to true for SysV, false for WIN64/_WIN64"
  
  	RAX := 0.
  	RCX := 1.  "Were they completely mad or simply sadistic?"
  	RDX := 2.
  	RBX := 3.
  	RSP := 4.
  	RBP := 5.
  	RSI := 6.
  	RDI := 7.
  	R8 := 8.
  	R9 := 9.
  	R10 := 10.
  	R11 := 11.
  	R12 := 12.
  	R13 := 13.
  	R14 := 14.
  	R15 := 15.
  
  	XMM0L := 0.
  	XMM1L := 1.
  	XMM2L := 2.
  	XMM3L := 3.
  	XMM4L := 4.
  	XMM5L := 5.
  	XMM6L := 6.
  	XMM7L := 7.
  	XMM8L := 8.
  	XMM9L := 9.
  	XMM10L := 10.
  	XMM11L := 11.
  	XMM12L := 12.
  	XMM13L := 13.
  	XMM14L := 14.
  	XMM15L := 15.
  
  	"Mod R/M Mod fields.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-2"
  	ModRegInd := 0.
  		ModRegIndSIB := 4.
  		ModRegIndDisp32 := 5.
  	ModRegRegDisp8 := 1.
  	ModRegRegDisp32 := 2.
  	ModReg := 3.
  
  	"SIB Scaled Index modes.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-3"
  	SIB1 := 0.
  	SIB2 := 1.
  	SIB4 := 2.
  	SIB8 := 3.
  
  	"Specific instructions"
  	self
  		initializeSpecificOpcodes: #(CDQ IDIVR IMULRR CPUID LFENCE MFENCE SFENCE LOCK CMPXCHGAwR CMPXCHGMwrR XCHGAwR XCHGMwrR XCHGRR CLD REP MOVSB MOVSQ)
  		in: thisContext method!

Item was changed:
  ----- Method: CogX64Compiler class>>moduleName (in category 'translation') -----
  moduleName
  	"CogAbstractInstruction subclasses collect: [:ea| ea moduleName]"
+ 	^'cogit', self ISA, ((InitializationOptions at: #ABI ifAbsent: ['']) copyWithout: $_)!
- 	^'cogit', self ISA, ((initializationOptions at: #ABI ifAbsent: ['']) copyWithout: $_)!

Item was changed:
  ----- Method: Cogit class>>activeCompilerClass (in category 'translation') -----
  activeCompilerClass
+ 	^InitializationOptions
- 	^initializationOptions
  		at: #CogCompilerClass
  		ifPresent: [:compilerClassName| Smalltalk classNamed: compilerClassName]
  		ifAbsent:
  			[(CogAbstractInstruction subclasses detect:
  				[:compilerClass|
+ 				 compilerClass ISA == (InitializationOptions at: #ISA ifAbsent: [#IA32])]) defaultCompilerClass]!
- 				 compilerClass ISA == (initializationOptions at: #ISA ifAbsent: [#IA32])]) defaultCompilerClass]!

Item was added:
+ ----- Method: Cogit class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	ProcessorClass ifNil:
+ 		[Cogit initializeMiscConstants].
+ 	^(self activeCompilerClass withAllSuperclasses copyUpThrough: CogAbstractInstruction),
+ 	  {	CogMethodZone.
+ 		CogBlockStart.
+ 		CogBytecodeDescriptor.
+ 		CogBytecodeFixup.
+ 		CogPrimitiveDescriptor.
+ 		CogBlockMethod.
+ 		CogMethod.
+ 		self activeCompilerClass literalsManagerClass},
+ 	((InitializationOptions at: #NewspeakVM ifAbsent: [false])
+ 		ifTrue: [{NewspeakCogMethod. NSSendCache}]
+ 		ifFalse: [#()]),
+ 	((InitializationOptions at: #SistaVM ifAbsent: [false])
+ 		ifTrue: [{SistaMethodZone}]
+ 		ifFalse: [#()])!

Item was removed:
- ----- Method: Cogit class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	ProcessorClass ifNil:
- 		[Cogit initializeMiscConstants].
- 	^(self activeCompilerClass withAllSuperclasses copyUpThrough: CogAbstractInstruction),
- 	  {	CogMethodZone.
- 		CogBlockStart.
- 		CogBytecodeDescriptor.
- 		CogBytecodeFixup.
- 		CogPrimitiveDescriptor.
- 		CogBlockMethod.
- 		CogMethod.
- 		self activeCompilerClass literalsManagerClass},
- 	((options at: #NewspeakVM ifAbsent: [false])
- 		ifTrue: [{NewspeakCogMethod. NSSendCache}]
- 		ifFalse: [#()]),
- 	((options at: #SistaVM ifAbsent: [false])
- 		ifTrue: [{SistaMethodZone}]
- 		ifFalse: [#()])!

Item was changed:
  ----- Method: Cogit class>>attemptToComputeInstVarNamesFor: (in category 'in-image compilation support') -----
  attemptToComputeInstVarNamesFor: aCompiledMethod
  	(aCompiledMethod methodClass instSize > 0) ifTrue:
+ 		[InitializationOptions
- 		[initializationOptions
  			at: #instVarNames
  			put: (aCompiledMethod methodClass allInstVarNames)]!

Item was changed:
  ----- Method: Cogit class>>attemptToComputeTempNamesFor: (in category 'in-image compilation support') -----
  attemptToComputeTempNamesFor: aCompiledMethod
  	(aCompiledMethod respondsTo: #tempNames) ifTrue:
  		[| schematicTemps blocks |
  		 schematicTemps := aCompiledMethod methodNode schematicTempNamesString.
  		 blocks := aCompiledMethod embeddedBlockClosures.
+ 		 InitializationOptions
- 		 initializationOptions
  			at: #tempNames
  			put: (Dictionary withAll: {aCompiledMethod initialPC -> (self decomposeSchematicTemps: (schematicTemps copyUpTo: $[))},
  				(blocks
  					ifEmpty: [#()]
  					ifNotEmpty:
  						[aCompiledMethod embeddedBlockClosures
  							with: (schematicTemps piecesCutWhere: [:a :b| b = $[]) allButFirst
  							collect: [:c :s| c startpc -> (self decomposeSchematicTemps: (s copyWithoutAll: '[]'))]]))]!

Item was changed:
  ----- Method: Cogit class>>generateCodeStringForCogitDotC (in category 'translation') -----
  generateCodeStringForCogitDotC
  	"Generate a skeletal cogit.c that includes the relevant cogitFOO.c
  	 for the appropriate subclasses of CogAbstractInstruction.
  	 self generateCodeStringForCogitDotC"
  	 
  	| string insertPosition abis defaultDef |
  	abis := OrderedCollection new.
  	string := String streamContents:
  		[:s|
  		 s nextPutAll: '/* Automatically generated by\	' withCRs.
  		 s nextPutAll: (CCodeGenerator monticelloDescriptionFor: self).
  		 s cr; nextPutAll: ' */'.
  		 s cr; cr; nextPut: $#.
  		 insertPosition := s position.
  		 self translateableInstructionSubclassesAndInstalledOptionsDo:
  			[:class | | abi |
  			 s nextPutAll: 'if '.
+ 			 (abi := InitializationOptions at: #ABI ifAbsent: []) ifNotNil:
- 			 (abi := initializationOptions at: #ABI ifAbsent: []) ifNotNil:
  				[s nextPutAll: (abis addLast: abi); nextPutAll: ' && ('].
  			 class identifyingPredefinedMacros
  				do: [:predefinedMacro| s nextPutAll: 'defined('; nextPutAll: predefinedMacro; nextPut: $)]
  				separatedBy: [s nextPutAll: ' || '].
  			 abi ifNotNil: [s nextPut: $)].
  			 s cr; cr; nextPutAll: '#	include "'; nextPutAll: class moduleName; nextPutAll: '.c"'.
  			 s cr; cr; nextPutAll: '#el'].
  		 s nextPutAll: 'se'.
  		 #(	'As yet no Cogit implementation appears to exist for your platform.'
  			'Consider implementing it, starting by adding a subclass of CogAbstractInstruction.') do:
  			[:msg| s cr; nextPutAll: '#	error '; nextPutAll: msg].
  		 s cr; nextPutAll: '#endif'; cr].
  	abis isEmpty ifTrue:
  		[^string].
  	defaultDef := String streamContents:
  		[:s|
  		s nextPutAll: '#if !!'.
  		abis do: [:abi| s nextPutAll: abi] separatedBy: [s nextPutAll: ' && !!'].
  		s cr; nextPutAll: '# define '; nextPutAll: abis first; nextPutAll: ' 1'; cr.
  		s nextPutAll: '#endif'; cr; cr].
  	^string copyReplaceFrom: insertPosition to: insertPosition - 1 with: defaultDef!

Item was changed:
  ----- Method: Cogit class>>initializeBytecodeTable (in category 'class initialization') -----
  initializeBytecodeTable
  	"SimpleStackBasedCogit initializeBytecodeTableWith: Dictionary new"
  	"StackToRegisterMappingCogit initializeBytecodeTableWith: Dictionary new"
  
  	| initializer |
  	BytecodeSetHasDirectedSuperSend := BytecodeSetHasExtensions := false.
+ 	initializer := InitializationOptions
- 	initializer := initializationOptions
  					at: #bytecodeTableInitializer
  					ifAbsent:
  						[NewspeakVM
  							ifTrue:
  								[MULTIPLEBYTECODESETS
  									ifTrue: [#initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid]
  									ifFalse: [#initializeBytecodeTableForNewspeakV4]]
  							ifFalse:
  								[MULTIPLEBYTECODESETS
  									ifTrue: [#initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid]
  									ifFalse: [#initializeBytecodeTableForSqueakV3PlusClosures]]].
  	"Now make sure all classes in the hierarchy have initialized to the same bytecode table."
  	(self withAllSuperclasses copyUpTo: Cogit) reverseDo: "i.e. exclude Cogit"
  		[:cogitClass|
  		 cogitClass perform: initializer]!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
+ 	Debug := InitializationOptions at: #Debug ifAbsent: [false].
+ 	(InitializationOptions includesKey: #EagerInstructionDecoration)
- 	Debug := initializationOptions at: #Debug ifAbsent: [false].
- 	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
+ 			[EagerInstructionDecoration := InitializationOptions at: #EagerInstructionDecoration]
- 			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration ifNil:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
+ 	ProcessorClass := (InitializationOptions at: #ISA ifAbsentPut: [self objectMemoryClass defaultISA]) caseOf: {
- 	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [self objectMemoryClass defaultISA]) caseOf: {
  							[#X64] 		->	[BochsX64Alien].
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien].
  							[#MIPSEL]	->	[MIPSELSimulator] }.
  	CogCompilerClass := self activeCompilerClass.
  	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) reverseDo:
  		[:compilerClass| compilerClass initialize; initializeAbstractRegisters].
  	self objectMemoryClass objectRepresentationClass initializeMiscConstants.
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
+ 	MaxLiteralCountForCompile := InitializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
- 	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
  	"6 is a fine number for the max number of PCI entries.  8 is too large."
  	MaxCPICCases := 6.
  
  	"One variable defines whether in a block and whether in a vanilla or full block."
  	InVanillaBlock := 1.
  	InFullBlock := 2.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was changed:
  ----- Method: Cogit class>>initializeWithOptions: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionary
- 	{ self. CogMethodSurrogate. } , (self ancilliaryClasses: optionsDictionary) do:
- 		[:aSuperclass|
- 		 aSuperclass withAllSubclasses do:
- 			[:class| class initializationOptions: optionsDictionary]].
  	super initializeWithOptions: optionsDictionary.
  	self initializeMiscConstants. "must precede other initialization."
  	self initializeErrorCodes.
  	self initializeCogMethodConstants.
  	self initializeAnnotationConstants.
  	self initializeBytecodeTable.
  	self initializeNumTrampolines.
  	self initializePrimitiveTable!

Item was changed:
  ----- Method: Cogit class>>translateableInstructionSubclassesAndInstalledOptionsDo: (in category 'translation') -----
  translateableInstructionSubclassesAndInstalledOptionsDo: aBlock
  	"Evaluate aBlock with the translateable subclass and its options installed, being careful to clean-up afterwards."
  	CogAbstractInstruction translateableSubclassesAndOptions do:
  		[:pair|
  		[:class :options| | toRemove |
  		 toRemove := Set new.
  		 options pairsDo:
  			[:key :value|
+ 			 (InitializationOptions includesKey: key) ifFalse:
- 			 (initializationOptions includesKey: key) ifFalse:
  				[toRemove add: key].
+ 			 InitializationOptions at: key put: value].
- 			 initializationOptions at: key put: value].
  		 aBlock value: class.
+ 		 toRemove do: [:key| InitializationOptions removeKey: key]]
- 		 toRemove do: [:key| initializationOptions removeKey: key]]
  			valueWithArguments: pair]!

Item was added:
+ ----- Method: IA32ABIPlugin class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^{ VMCallbackContext. VMCallbackReturnValue }!

Item was removed:
- ----- Method: IA32ABIPlugin class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	^{ VMCallbackContext. VMCallbackReturnValue }!

Item was changed:
  ----- Method: Interpreter class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  
+ 	DoBalanceChecks := InitializationOptions at: #DoBalanceChecks ifAbsent: [false]. "generate stack balance checks"
- 	DoBalanceChecks := initializationOptions at: #DoBalanceChecks ifAbsent: [false]. "generate stack balance checks"
  	SemaphoresToSignalSize := 500.
  	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"!

Item was changed:
  ----- Method: RiscOSVMMaker>>needsToRegenerateInterpreterFile (in category 'initialize') -----
  needsToRegenerateInterpreterFile
  	"Check the timestamp for the relevant classes and then the timestamp for the main
  	 source file (e.g. interp.c) if it already exists.  Answer if the file needs regenerating."
  
  	| classes tStamp fstat |
  	classes := self interpreterClass withAllSuperclasses copyUpTo: VMClass.
  	self interpreterClass objectMemoryClass ifNotNil:
  		[:objectMemoryClass|
  		classes addAllLast: (objectMemoryClass withAllSuperclasses copyUpTo: VMClass)].
  	classes copy do:
+ 		[:class| classes addAllLast: class ancilliaryClasses].
- 		[:class| classes addAllLast: (class ancilliaryClasses: self options)].
  	tStamp := classes inject: 0 into: [:tS :cl| tS max: cl timeStamp].
  
  	"don't translate if the file is newer than my timeStamp"
  	"RiscOS keeps the interp file in a 'c' subdirectory of coreVMDirectory"
  	(self coreVMDirectory directoryExists: 'c') ifFalse:[^true].
  
  	fstat := (self coreVMDirectory directoryNamed: 'c') entryAt: self interpreterFilename ifAbsent:[nil].
  	fstat ifNotNil:[tStamp < fstat modificationTime ifTrue:[^false]].
  	^true
  !

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^super ancilliaryClasses, (self objectRepresentationClass withAllSuperclasses copyUpThrough: CogObjectRepresentation) reverse!

Item was removed:
- ----- Method: SimpleStackBasedCogit class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	initializationOptions ifNil:
- 		[initializationOptions := options].
- 	^(super ancilliaryClasses: options), (self objectRepresentationClass withAllSuperclasses copyUpThrough: CogObjectRepresentation) reverse!

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 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 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])
- 		((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 200 genSpecialSelectorNotEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 201 207 genSpecialSelectorSend isMapped)
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was added:
+ ----- Method: SistaCogit class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^super ancilliaryClasses copyWith: SistaCogMethod!

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

Item was added:
+ ----- Method: SistaCogitClone class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^super ancilliaryClasses copyWith: SistaCogMethod!

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

Item was changed:
  ----- Method: SpurCompactor class>>classesForTranslation (in category 'translation') -----
  classesForTranslation
+ 	"Usually we want to add the SpurCompactor first, followed by the subclass.
+ 	 SpurHybridCompactor is more complicated."
  	^(self withAllSuperclasses copyUpThrough: SpurCompactor) reverse!

Item was changed:
  ----- Method: SpurCompactor class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	"If subclasses are being used but are not the compactorClass itself
  	 then staticvally resolve their api selectors."
  	((self inheritsFrom: SpurCompactor)
+ 	 and: [(InitializationOptions at: #compactorClass) ~= self name]) ifTrue:
- 	 and: [(initializationOptions at: #compactorClass) ~= self name]) ifTrue:
  		[#(compact biasForGC biasForSnapshot remapObj: shouldRemapObj:) do:
  			[:selectorToStaticallyResolve|
  			 aCCodeGenerator
  				staticallyResolveMethodNamed: selectorToStaticallyResolve
  				forClass: self
  				to: (self staticallyResolvePolymorphicSelector: selectorToStaticallyResolve)]]!

Item was removed:
- ----- Method: SpurHybridCompactor class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	"Answer any extra classes to be included in the translation."
- 	^{	SpurPlanningCompactor.
- 		SpurSelectiveCompactor.
- 		SpurSweeper }!

Item was changed:
  ----- Method: SpurHybridCompactor class>>classesForTranslation (in category 'translation') -----
  classesForTranslation
+ 	^{	SpurPlanningCompactor.
+ 		SpurSelectiveCompactor.
+ 		SpurSweeper }, super classesForTranslation!
- 	^(self ancilliaryClasses: nil), super classesForTranslation!

Item was added:
+ ----- Method: SpurMemoryManager class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^{	SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo }, 
+ 		self compactorClass classesForTranslation,
+ 		SpurNewSpaceSpace withAllSubclasses
+ 		
+ 	!

Item was removed:
- ----- Method: SpurMemoryManager class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	initializationOptions ifNil: [initializationOptions := options].
- 	^{	SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo }, 
- 		self compactorClass classesForTranslation,
- 		SpurNewSpaceSpace withAllSubclasses
- 		
- 	!

Item was changed:
  ----- Method: SpurMemoryManager class>>compactorClass (in category 'accessing class hierarchy') -----
  compactorClass
  	"Answer the compaction algorithm to use."
+ 	^Smalltalk classNamed: (InitializationOptions at: #compactorClass ifAbsent: [#SpurPlanningCompactor])!
- 	^Smalltalk classNamed: (initializationOptions at: #compactorClass ifAbsent: [#SpurPlanningCompactor])!

Item was changed:
  ----- Method: SpurMemoryManager class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	self declareCAsOop: #(	memory freeStart scavengeThreshold newSpaceStart newSpaceLimit pastSpaceStart
+ 							lowSpaceThreshold freeOldSpaceStart oldSpaceStart endOfMemory)
- 							lowSpaceThreshold freeOldSpaceStart oldSpaceStart endOfMemory firstFreeChunk lastFreeChunk)
  		in: aCCodeGenerator.
  	self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs']), #(statAllocatedBytes)
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #freeListsMask type: #usqInt;
  		var: #freeLists type: #'sqInt *';
  		var: #objStackInvalidBecause type: #'char *';
  		var: #unscannedEphemerons type: #SpurContiguousObjStack;
  		var: #heapGrowthToSizeGCRatio type: #float;
  		var: #heapSizeAtPreviousGC type: #usqInt;
  		var: #totalFreeOldSpace type: #usqInt;
  		var: #maxOldSpaceSize type: #usqInt.
  	aCCodeGenerator
  		var: #oldSpaceUsePriorToScavenge type: #sqLong.
  	aCCodeGenerator
  		var: #remapBuffer
  		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #extraRoots
  		declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'!

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionary
  	"SpurMemoryManager initializeWithOptions: Dictionary new"
  
- 	{self}, (self ancilliaryClasses: optionsDictionary) do:
- 		[:aSuperclass|
- 		 aSuperclass withAllSubclasses do:
- 			[:class| class initializationOptions: optionsDictionary]].
- 
  	super initializeWithOptions: optionsDictionary.
+ 	InitializationOptions
- 	initializationOptions
  		at: #Spur32BitMemoryManager ifAbsentPut: false;
  		at: #Spur64BitMemoryManager ifAbsentPut: false.
  	self initialize.
  	self initBytesPerWord: (self == SpurMemoryManager
  								ifTrue: [optionsDictionary at: #BytesPerWord ifAbsent: [4]]
  								ifFalse: [self wordSize]).
  
  	self initializeObjectHeaderConstants. "Initializes BaseHeaderSize so do early"
  	self initializeSpurObjectRepresentationConstants.
  	self initializeSpecialObjectIndices.
  	self initializeCompactClassIndices.
  	self initializePrimitiveErrorCodes.
  
  	SpurGenerationScavenger initialize!

Item was added:
+ ----- Method: StackInterpreter class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^{	self objectMemoryClass.
+ 		VMCallbackContext.
+ 		CogStackPages.
+ 		InterpreterStackPages.
+ 		CogStackPage }!

Item was removed:
- ----- Method: StackInterpreter class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	"Answer any extra classes to be included in the translation."
- 	^{	self objectMemoryClass.
- 		VMCallbackContext.
- 		CogStackPages.
- 		InterpreterStackPages.
- 		CogStackPage }!

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

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

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

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

Item was 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/Spur forwarding"
  	GCModeImageSegment := 16.	"just a flag for leak checking image segments"
  	GCModeFreeSpace := 32.		"just a flag for leak checking free space; Spur only"
  	GCCheckPrimCall := 64.		"just a flag for leak checking external primitive calls"
  
  	StackPageTraceInvalid := -1.
  	StackPageUnreached := 0.
  	StackPageReachedButUntraced := 1.
  	StackPageTraced := 2.
  
  	DumpStackOnLowSpace := 0.
  	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]!
- 	FailImbalancedPrimitives := initializationOptions at: #FailImbalancedPrimitives ifAbsentPut: [true].
- 	EnforceAccessControl := initializationOptions at: #EnforceAccessControl ifAbsent: [true]!

Item was changed:
  ----- Method: StackInterpreter class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"StackInterpreter initializeWithOptions: Dictionary new"
  
  	super initializeWithOptions: optionsDictionary.
- 	(self primitivesClass withAllSuperclasses copyUpTo: StackInterpreter) do:
- 		[:class| class initializationOptions: initializationOptions].
  	self initializeMiscConstants. "must precede other initialization."
  	self initializeAssociationIndex.
  	self initializeBytecodeTable.
  	self initializeCaches.
  	self initializeCharacterIndex.
  	self initializeCharacterScannerIndices.
  	self initializeClassIndices.
  	self initializeContextIndices.
  	self initializeDirectoryLookupResultCodes.
  	self initializeFrameIndices.
  	self initializeMessageIndices.
  	self initializeMethodIndices.
  	self initializePointIndices.
  	self initializePrimitiveTable.
  	self initializeSchedulerIndices.
  	self initializeSmallIntegers.
  	self initializeStreamIndices!

Item was changed:
  ----- Method: StackInterpreter class>>writeVMHeaderTo:bytesPerWord:generator: (in category 'translation') -----
  writeVMHeaderTo: aStream bytesPerWord: bytesPerWord generator: aCCodeGenerator
  	super writeVMHeaderTo: aStream bytesPerWord: bytesPerWord generator: aCCodeGenerator.
  	SistaVM ifTrue:
  		[aCCodeGenerator putDefineOf: #SistaVM as: 1 on: aStream].
  	NewspeakVM ifTrue:
  		[aCCodeGenerator putDefineOf: #NewspeakVM as: 1 on: aStream].
  	MULTIPLEBYTECODESETS ifTrue:
  		[aCCodeGenerator putDefineOf: #MULTIPLEBYTECODESETS as: 1 on: aStream].
  	IMMUTABILITY ifTrue:
  		[aCCodeGenerator
  			putConditionalDefineOf: #IMMUTABILITY
  			as: 1
  			comment: 'Allow this to be overridden on the compiler command line'
  			on: aStream].
  	SistaVM | NewspeakVM | MULTIPLEBYTECODESETS | IMMUTABILITY ifTrue:
  		[aStream cr].
  	aCCodeGenerator putDefineOf: #STACKVM as: 1 on: aStream.
+ 	(InitializationOptions at: #SpurObjectMemory ifAbsent: false) ifTrue:
- 	(initializationOptions at: #SpurObjectMemory ifAbsent: false) ifTrue:
  		[aCCodeGenerator putDefineOf: #SPURVM as: 1 on: aStream]!

Item was changed:
  ----- Method: StackInterpreterSimulator class>>initializeWithOptions:objectMemoryClass: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionaryOrArray objectMemoryClass: objectMemoryClassOrNil
  	"The relevant ObjectMemory and Interpreter classes must be initialized in order.
  	 This happens notionally every time we start the simulator,
  	 but in fact happens when ever we instantiate a simulator."
+ 	InitializationOptions := optionsDictionaryOrArray isArray
- 	initializationOptions := optionsDictionaryOrArray isArray
  							ifTrue: [Dictionary newFromPairs: optionsDictionaryOrArray]
  							ifFalse: [optionsDictionaryOrArray].
  
- 	(self allSuperclasses copyUpThrough: InterpreterPrimitives) do:
- 		[:sc| sc initializationOptions: initializationOptions].
- 
  	(objectMemoryClassOrNil ifNil: [self objectMemoryClass])
+ 		initializeWithOptions: InitializationOptions.
- 		initializeWithOptions: initializationOptions.
  
+ 	self initializeWithOptions: InitializationOptions!
- 	self initializeWithOptions: initializationOptions!

Item was added:
+ ----- Method: StackToRegisterMappingCogit class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	^super ancilliaryClasses,
+ 	  { self basicNew simStackEntryClass. self basicNew bytecodeFixupClass. CogSSOptStatus } ,
+ 	(LowcodeVM ifTrue: [ { self basicNew simStackNativeEntryClass } ] ifFalse: [ #() ])!

Item was removed:
- ----- Method: StackToRegisterMappingCogit class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	^(super ancilliaryClasses: options),
- 	  { self basicNew simStackEntryClass. self basicNew bytecodeFixupClass. CogSSOptStatus } ,
- 	(LowcodeVM ifTrue: [ { self basicNew simStackNativeEntryClass } ] ifFalse: [ #() ])!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosures"
  
  	numPushNilsFunction := #v3:Num:Push:Nils:.
  	pushNilSizeFunction := #v3PushNilSize:numInitialNils:.
  	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 needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode isInstVarRef is1ByteInstVarStore isMappedIfImmutability needsFrameIfImmutability: -1)
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(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 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped) "well, maybe inst var ref"
  		(2 133 133 genExtendedSuperBytecode isInstVarRef 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])
- 		((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 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 200 genSpecialSelectorNotEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 201 207 genSpecialSelectorSend isMapped) " #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was added:
+ ----- Method: ThreadedFFIPlugin class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	^{ self calloutStateClass }!

Item was removed:
- ----- Method: ThreadedFFIPlugin class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	^{ self calloutStateClass }!

Item was added:
+ ----- Method: ThreadedX64SysVFFIPlugin class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	^{ self calloutStateClass. ThreadedFFIX64SixteenByteReturn }!

Item was removed:
- ----- Method: ThreadedX64SysVFFIPlugin class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: options
- 	^{ self calloutStateClass. ThreadedFFIX64SixteenByteReturn }!

Item was changed:
  Object subclass: #VMClass
  	instanceVariableNames: ''
+ 	classVariableNames: 'DefaultBase ExpensiveAsserts InitializationOptions'
- 	classVariableNames: 'DefaultBase ExpensiveAsserts'
  	poolDictionaries: 'VMBasicConstants VMObjectIndices'
  	category: 'VMMaker-Support'!
  VMClass class
+ 	instanceVariableNames: 'timeStamp'!
- 	instanceVariableNames: 'timeStamp initializationOptions'!
  
+ !VMClass commentStamp: 'eem 6/7/2018 15:16' prior: 0!
+ I am an abstract superclass for all classes in the VM that want to maintain a source timeStamp.  I am also the holder of the InitializationOptions class variable which holds options such as which JIT or which memory manager to use when creating or generating a VM.!
- !VMClass commentStamp: '<historical>' prior: 0!
- I am an abstract superclass for all classes in the VM that want to maintain a source timeStamp.!
  VMClass class
+ 	instanceVariableNames: 'timeStamp'!
- 	instanceVariableNames: 'timeStamp initializationOptions'!

Item was added:
+ ----- Method: VMClass class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^{}!

Item was removed:
- ----- Method: VMClass class>>ancilliaryClasses: (in category 'translation') -----
- ancilliaryClasses: optionsDictionary
- 	"Answer any extra classes to be included in the translation."
- 	^{}!

Item was changed:
  ----- Method: VMClass class>>cogitClass (in category 'accessing class hierarchy') -----
  cogitClass
  	"Answer the cogitClass in effect.  Ensure that StackInterpreter has a nil cogitClass."
  	(self isInterpreterClass and: [self hasCogit not]) ifTrue:
  		[^nil].
+ 	^Smalltalk classNamed: (InitializationOptions
+ 								at: #Cogit
+ 								ifAbsent: [#StackToRegisterMappingCogit])!
- 	^initializationOptions ifNotNil:
- 		[Smalltalk classNamed: (initializationOptions
- 									at: #Cogit
- 									ifAbsent: [#StackToRegisterMappingCogit])]!

Item was changed:
  ----- Method: VMClass class>>initializationOptions (in category 'initialization') -----
  initializationOptions
+ 	^InitializationOptions!
- 	^initializationOptions!

Item was removed:
- ----- Method: VMClass class>>initializationOptions: (in category 'initialization') -----
- initializationOptions: optionsDictionary
- 	initializationOptions := optionsDictionary!

Item was changed:
  ----- Method: VMClass class>>initialize (in category 'initialization') -----
  initialize
+ 	InitializationOptions ifNil: [InitializationOptions := Dictionary new].
  	(Utilities classPool at: #CommonRequestStrings ifAbsent: []) ifNotNil:
  		[:commonRequestStringHolder|
  		(commonRequestStringHolder contents asString includesSubstring: 'VMClass open') ifFalse:
  			[Utilities appendToCommonRequests: '-\VMMaker generateConfiguration\VMMaker generateAllConfigurationsUnderVersionControl\VMMaker generateAllSpurConfigurations\VMClass openCogMultiWindowBrowser\VMClass openObjectMemoriesInterpretersBrowser\VMClass openSpurMultiWindowBrowser\VMClass openCogSpurMultiWindowBrowser\VMClass openCogitMultiWindowBrowser' withCRs]].
  	ExpensiveAsserts := false!

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.
  	 Subclass implementations need to include a super initializeMiscConstants"
  
  	| omc |
  	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
  	SPURVM := STACKVM := COGVM := COGMTVM := false.
  
+ 	InitializationOptions ifNil: [InitializationOptions := Dictionary new].
+ 	omc := InitializationOptions at: #ObjectMemory ifAbsent: nil.
- 	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
- 		[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].
+ 	TempVectReadBarrier := InitializationOptions at: #TempVectReadBarrier ifAbsentPut: [false].
+ 	LowcodeVM := InitializationOptions at: #LowcodeVM ifAbsentPut: [false].
+ 	MULTIPLEBYTECODESETS := InitializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false].
- 	PharoVM := initializationOptions at: #PharoVM ifAbsentPut: [false].
- 	NewspeakVM := initializationOptions at: #NewspeakVM ifAbsentPut: [false].
- 	SistaVM := initializationOptions at: #SistaVM ifAbsentPut: [false].
- 	TempVectReadBarrier := initializationOptions at: #TempVectReadBarrier ifAbsentPut: [false].
- 	LowcodeVM := initializationOptions at: #LowcodeVM ifAbsentPut: [false].
- 	MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false].
  	"Simulation only; on by default..."
+ 	CloneOnGC := InitializationOptions at: #CloneOnGC ifAbsentPut: [true].
+ 	CloneOnScavenge := InitializationOptions at: #CloneOnScavenge ifAbsentPut: [true].
- 	CloneOnGC := initializationOptions at: #CloneOnGC ifAbsentPut: [true].
- 	CloneOnScavenge := initializationOptions at: #CloneOnScavenge ifAbsentPut: [true].
  
  	"These must be set only if specified, not defaulted, because they are set on the command line or in include files."
+ 	InitializationOptions
- 	initializationOptions
  		at: #VMBIGENDIAN	ifPresent: [:value| VMBIGENDIAN := value];
  		at: #ObjectMemory	ifPresent: [:value| SPURVM := value beginsWith: 'Spur'];
  		at: #STACKVM		ifPresent: [:value| STACKVM := value];
+ 		at: #COGVM		ifPresent: [:value| COGVM := InitializationOptions at: #COGVM];
+ 		at: #COGMTVM		ifPresent: [:value| COGMTVM := InitializationOptions at: #COGMTVM].
- 		at: #COGVM		ifPresent: [:value| COGVM := initializationOptions at: #COGVM];
- 		at: #COGMTVM		ifPresent: [:value| COGMTVM := initializationOptions at: #COGMTVM].
  
  	"consistency checks"
+ 	SPURVM
+ 		ifTrue:
+ 			[(TempVectReadBarrier not
+ 			  and: [{SpurMemoryManager compactorClass}, (SpurMemoryManager compactorClass ancilliaryClasses) anySatisfy:
+ 						[:c| c == SpurSelectiveCompactor]]) ifTrue:
+ 				[self error: 'Selective compactor requires read barrier']]
+ 		ifFalse:
+ 			[TempVectReadBarrier ifTrue: [self error: 'read barrier works with spur VM only...'].
+ 			 SistaVM ifTrue: [self error: 'Sista VM works with spur VM only...']].
- 	(TempVectReadBarrier and: [SPURVM not]) ifTrue: [self error: 'read barrier works with spur VM only...'].
- 	(SistaVM and: [SPURVM not]) ifTrue: [self error: 'Sista VM works with spur VM only...'].
- 	((initializationOptions at: #compactorClass ifAbsent: []) = #SpurSelectiveCompactor and: [TempVectReadBarrier not]) ifTrue: [self error: 'Selective compactor requires read barrier'].
  
  	"And not these; they're compile-time"
+ 	IMMUTABILITY := InitializationOptions at: #IMMUTABILITY ifAbsent: [SPURVM] "Default as enabled for Spur VMs"!
- 	IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsent: [SPURVM] "Default as enabled for Spur VMs"!

Item was changed:
  ----- Method: VMClass class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionaryOrArray
  	"Initialize the receiver, typically initializing class variables. Initialize any class variables
  	 whose names occur in optionsDictionary with the corresponding values there-in."
+ 	InitializationOptions := optionsDictionaryOrArray isArray
+ 								ifTrue: [Dictionary newFromPairs: optionsDictionaryOrArray]
+ 								ifFalse: [optionsDictionaryOrArray].
- 	| optionsDictionary |
- 	optionsDictionary := optionsDictionaryOrArray isArray
- 							ifTrue: [Dictionary newFromPairs: optionsDictionaryOrArray]
- 							ifFalse: [optionsDictionaryOrArray].
- 	"This is necessary.  e.g. if the receiver is CoInterpreterPrimitives,
- 	 it is still necessary to set the options in CoInterpreter.  Otherwise,
- 	 some class in the chain may have stale options, and when building
- 	 the code generator, a stale ancilliary class may be computed."
- 	(self withAllSuperclasses copyUpThrough: VMClass) do:
- 		[:class|
- 		class initializationOptions: optionsDictionary].
  
+ 	ExpensiveAsserts := InitializationOptions at: #ExpensiveAsserts ifAbsent: [false]!
- 	ExpensiveAsserts := optionsDictionary at: #ExpensiveAsserts ifAbsent: [false]!

Item was changed:
  ----- Method: VMClass class>>objectMemoryClass (in category 'accessing class hierarchy') -----
  objectMemoryClass
+ 	InitializationOptions ifNil:
- 	initializationOptions ifNil:
  		[^self defaultObjectMemoryClass].
+ 	^Smalltalk at: (InitializationOptions
- 	^Smalltalk at: (initializationOptions
  					at: #ObjectMemory
  					ifAbsent: [^self defaultObjectMemoryClass])!

Item was changed:
  ----- Method: VMClass class>>shouldIncludeMethodForSelector: (in category 'translation') -----
  shouldIncludeMethodForSelector: selector
  	"Answer whether a primitive method should be translated.  Emit a warning to the transcript if the method doesn't exist."
  	^(self whichClassIncludesSelector: selector)
  		ifNotNil:
  			[:c|
  			 (c >> selector pragmaAt: #option:)
  				ifNotNil:
  					[:pragma|
  					(VMBasicConstants defineAtCompileTime: pragma arguments first)
+ 					 or: [InitializationOptions
- 					 or: [initializationOptions
  							at: pragma arguments first
  							ifAbsent: [(self bindingOf: pragma arguments first)
  										ifNil: [false]
  										ifNotNil: [:binding| binding value ~~ #undefined]]]]
  				ifNil: [true]]
  		ifNil:
  			[Transcript nextPutAll: 'Cannot find implementation of '; nextPutAll: selector; nextPutAll: ' in hierarchy of '; print: self; cr; flush.
  			 false]!

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 reject: [:class| class isStructClass]).
- 	cogitClasses addAllLast: ((cogitClass ancilliaryClasses: optionsDictionary) reject: [:class| class isStructClass]).
  	cogitClasses do: [:cgc| cg addClass: cgc].
  	"Now make sure to add struct classes that the most specific subclasses specify.
  	 This makes sure that struct classes are ordered as the most specific cogitClass desires.
  	 This must happen for references between the struct classes to be resolved in a specific order."
  	cogitClasses := OrderedCollection with: cogitClass with: cogitClass objectRepresentationClass.
+ 	cogitClasses addAll: (cogitClass ancilliaryClasses reject:
- 	cogitClasses addAll: ((cogitClass ancilliaryClasses: optionsDictionary) reject:
  							[:class|
  							 class isStructClass
  							 or: [cogitClass objectRepresentationClass includesBehavior: class]]).
  	cg addStructClasses: (cg structClassesForTranslationClasses: cogitClasses).
  
  	getAPIMethods ifTrue:
  		[cg includeAPIFrom: (self
  								buildCodeGeneratorForInterpreter: self interpreterClass
  								includeAPIMethods: false
  								initializeClasses: false)].
  
  	^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]].
- 			[interpreterClass cogitClass initializeWithOptions: optionsDictionary].
- 		 interpreterClass objectMemoryClass initializationOptions: 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 initializationOptions: interpreterClass initializationOptions.
- 			 interpreterClasses addFirst: theClass.
  			 theClass := theClass superclass]].
  	interpreterClasses
  		addFirst: VMClass;
  		addAllLast: (cg nonStructClassesForTranslationClasses: interpreterClasses).
  
  	initializeClasses ifTrue:
  		[interpreterClasses do:
  			[:ic|
  			(ic respondsTo: #initializeWithOptions:)
  				ifTrue: [ic initializeWithOptions: interpreterClass initializationOptions]
  				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!

Item was changed:
  ----- Method: VMMaker>>needsToRegenerateCogitFile (in category 'generate sources') -----
  needsToRegenerateCogitFile
  	"Check the timestamp for the relevant classes and then the timestamp for the main source file (e.g. interp.c)
  	 file if it already exists. Answer if the file needs regenerating."
  
  	| cogitClass cogitClasses tStamp files |
  	cogitClasses := (cogitClass := self interpreterClass cogitClass) withAllSuperclasses copyUpThrough: Cogit.
+ 	cogitClasses addAllLast: cogitClass ancilliaryClasses.
- 	cogitClasses addAllLast: (cogitClass ancilliaryClasses: self options).
  	tStamp := cogitClasses inject: 0 into: [:tS :cl| tS max: cl timeStamp].
  
  	"don't translate if the file(s) is newer than my timeStamp"
  	files := (self coreVMDirectory fileNamesMatching: cogitClass activeCompilerClass moduleName, '*.c').
  	files isEmpty ifTrue:
  		[^true].
  	(files allSatisfy:
  		[:fileName|
  		(self coreVMDirectory entryAt: fileName ifAbsent: [nil])
  			ifNil: [false]
  			ifNotNil:
  				[:fstat| | mTime |
  				mTime := fstat modificationTime.
  				mTime isInteger ifFalse: [mTime := mTime asSeconds].
  				tStamp < mTime]]) ifTrue:
  		[^self confirm: ('The ', self configurationNameIfAny, cogitClass printString,
  			', ', cogitClass activeCompilerClass, '\classes have not been modified since the ',
  			cogitClass processorSpecificSourceFileName,
  			' source file\was last generated.  Do you still want to regenerate it?') withCRs].
  	^true!

Item was changed:
  ----- Method: VMMaker>>needsToRegenerateInterpreterFile (in category 'initialize') -----
  needsToRegenerateInterpreterFile
  	"Check the timestamp for the relevant classes and then the timestamp for the main
  	 source file (e.g. interp.c) if it already exists.  Answer if the file needs regenerating."
  
  	| classes tStamp |
  	classes := self interpreterClass withAllSuperclasses copyUpTo: VMClass.
  	self interpreterClass objectMemoryClass ifNotNil:
  		[:objectMemoryClass|
  		classes addAllLast: (objectMemoryClass withAllSuperclasses copyUpTo: VMClass)].
  	classes copy do:
+ 		[:class| classes addAllLast: class ancilliaryClasses].
- 		[:class| classes addAllLast: (class ancilliaryClasses: self options)].
  	tStamp := classes inject: 0 into: [:tS :cl| tS max: cl timeStamp].
  
  	"don't translate if the file is newer than my timeStamp"
  	(self coreVMDirectory entryAt: self interpreterFilename ifAbsent: [nil]) ifNotNil:
  		[:fstat| | mTime |
  		mTime := fstat modificationTime.
  		mTime isInteger ifFalse: [mTime := mTime asSeconds].
  		tStamp < mTime ifTrue:
  			[^self confirm: 'The ', self configurationNameIfAny, 'interpreter classes have not been modified since\ the interpreter file was last generated.\Do you still want to regenerate the source file?' withCRs]].
  	^true
  !



More information about the Vm-dev mailing list