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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 30 20:27:24 UTC 2013


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

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

Name: VMMaker.oscog-eem.420
Author: eem
Time: 30 September 2013, 1:24:21.885 pm
UUID: 1453e450-7e86-4412-81a9-a20e91c5fc44
Ancestors: VMMaker.oscog-eem.419

Move the initialization optionsDictionary into the initializationOptions
class variable of VMClass.  Rewrite the initialization routines that
access options to take them from the inst var.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstantsOn: (in category 'C code generator') -----
  emitCConstantsOn: aStream 
  	"Store the global variable declarations on the given stream."
  	| unused constList |
  	unused := constants keys asSet.
  	"Don't generate any defines for the externally defined constants,
  	 STACKVM, COGVM, COGMTVM et al, unless they're actually used."
+ 	(VMClass class>>#initializeMiscConstants) literalsDo:
- 	(VMClass class>>#initializeMiscConstantsWith:) literalsDo:
  		[:lit|
  		(lit isVariableBinding and: [lit key isString]) ifTrue:
  			[unused add: lit key]].
  	methods do:
  		[:meth|
  		meth declarations keysDo:
  			[:v|
  			(meth typeFor: v in: self) ifNotNil:
  				[:type| unused remove: type ifAbsent: []]].
  		unused remove: meth returnType ifAbsent: [].
  		meth parseTree nodesDo:
  			[:n| n isConstant ifTrue: [unused remove: n name ifAbsent: []]]].
  	unused copy do:
  		[:const|
  		(variableDeclarations anySatisfy: [:value| value includesSubString: const]) ifTrue:
  			[unused remove: const ifAbsent: []]].
  	unused remove: #BytesPerWord ifAbsent: []. "force inclusion of BytesPerWord declaration"
  	constList := constants keys reject: [:any| unused includes: any].
  	aStream cr; nextPutAll: '/*** Constants ***/'; cr.
  	(self sortStrings: constList) do:
  		[: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].
  			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]].
  	aStream cr!

Item was added:
+ ----- Method: CoInterpreter class>>defaultObjectMemoryClass (in category 'accessing class hierarchy') -----
+ defaultObjectMemoryClass
+ 	^NewCoObjectMemory!

Item was added:
+ ----- Method: CoInterpreter class>>initializeMiscConstants (in category 'initialization') -----
+ initializeMiscConstants
+ 
+ 	super initializeMiscConstants.
+ 	COGVM := true.
+ 
+ 	MinBackwardJumpCountForCompile := 10.
+ 
+ 	MaxNumArgs := 15.
+ 	PrimCallNeedsNewMethod := 1.
+ 	PrimCallNeedsPrimitiveFunction := 2.
+ 	PrimCallMayCallBack := 4.
+ 	PrimCallCollectsProfileSamples := 8.
+ 
+ 	ReturnToInterpreter := 1. "setjmp/longjmp code."
+ 
+ 	GCModeFull := 1.
+ 	GCModeIncr := 2.
+ 	GCModeBecome := 3.
+ 
+ 	PrimTraceLogSize := 256. "Room for 256 selectors.  Must be 256 because we use a byte to hold the index"
+ 	TraceBufferSize := 256 * 3. "Room for 256 events"
+ 	TraceContextSwitch := self objectMemoryClass basicNew integerObjectOf: 1.
+ 	TraceBlockActivation := self objectMemoryClass basicNew integerObjectOf: 2.
+ 	TraceBlockCreation := self objectMemoryClass basicNew integerObjectOf: 3.
+ 	TraceIncrementalGC := self objectMemoryClass basicNew integerObjectOf: 4.
+ 	TraceFullGC := self objectMemoryClass basicNew integerObjectOf: 5.
+ 	TraceCodeCompaction := self objectMemoryClass basicNew integerObjectOf: 6.
+ 	TraceOwnVM := self objectMemoryClass basicNew integerObjectOf: 7.
+ 	TraceDisownVM := self objectMemoryClass basicNew integerObjectOf: 8.
+ 	TraceThreadSwitch := self objectMemoryClass basicNew integerObjectOf: 9.
+ 	TracePreemptDisowningThread := self objectMemoryClass basicNew integerObjectOf: 10.
+ 	TraceVMCallback := self objectMemoryClass basicNew integerObjectOf: 11.
+ 	TraceVMCallbackReturn := self objectMemoryClass basicNew integerObjectOf: 12.
+ 	TraceStackOverflow := self objectMemoryClass basicNew integerObjectOf: 13.
+ 
+ 	TraceIsFromMachineCode := 1.
+ 	TraceIsFromInterpreter := 2.
+ 	CSCallbackEnter := 3.
+ 	CSCallbackLeave := 4.
+ 	CSEnterCriticalSection := 5.
+ 	CSExitCriticalSection := 6.
+ 	CSResume := 7.
+ 	CSSignal := 8.
+ 	CSSuspend := 9.
+ 	CSWait := 10.
+ 	CSYield := 11.
+ 	CSCheckEvents := 12.
+ 	CSThreadSchedulingLoop := 13.
+ 	CSOwnVM := 14.
+ 	CSThreadBind := 15.
+ 	CSSwitchIfNeccessary := 16.
+ 
+ 	TraceSources := CArrayAccessor on: #('?' 'm' 'i' 'callbackEnter' 'callbackLeave' 'enterCritical' 'exitCritical' 'resume' 'signal'  'suspend' 'wait' 'yield' 'eventcheck' 'threadsched' 'ownVM' 'bindToThread' 'switchIfNecessary').
+ 
+ 	"this is simulation only"
+ 	RumpCStackSize := 4096!

Item was removed:
- ----- Method: CoInterpreter class>>initializeMiscConstantsWith: (in category 'initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 
- 	super initializeMiscConstantsWith: optionsDictionary.
- 	COGVM := true.
- 
- 	MinBackwardJumpCountForCompile := 10.
- 
- 	MaxNumArgs := 15.
- 	PrimCallNeedsNewMethod := 1.
- 	PrimCallNeedsPrimitiveFunction := 2.
- 	PrimCallMayCallBack := 4.
- 	PrimCallCollectsProfileSamples := 8.
- 
- 	ReturnToInterpreter := 1. "setjmp/longjmp code."
- 
- 	GCModeFull := 1.
- 	GCModeIncr := 2.
- 	GCModeBecome := 3.
- 
- 	PrimTraceLogSize := 256. "Room for 256 selectors.  Must be 256 because we use a byte to hold the index"
- 	TraceBufferSize := 256 * 3. "Room for 256 events"
- 	TraceContextSwitch := self objectMemoryClass basicNew integerObjectOf: 1.
- 	TraceBlockActivation := self objectMemoryClass basicNew integerObjectOf: 2.
- 	TraceBlockCreation := self objectMemoryClass basicNew integerObjectOf: 3.
- 	TraceIncrementalGC := self objectMemoryClass basicNew integerObjectOf: 4.
- 	TraceFullGC := self objectMemoryClass basicNew integerObjectOf: 5.
- 	TraceCodeCompaction := self objectMemoryClass basicNew integerObjectOf: 6.
- 	TraceOwnVM := self objectMemoryClass basicNew integerObjectOf: 7.
- 	TraceDisownVM := self objectMemoryClass basicNew integerObjectOf: 8.
- 	TraceThreadSwitch := self objectMemoryClass basicNew integerObjectOf: 9.
- 	TracePreemptDisowningThread := self objectMemoryClass basicNew integerObjectOf: 10.
- 	TraceVMCallback := self objectMemoryClass basicNew integerObjectOf: 11.
- 	TraceVMCallbackReturn := self objectMemoryClass basicNew integerObjectOf: 12.
- 	TraceStackOverflow := self objectMemoryClass basicNew integerObjectOf: 13.
- 
- 	TraceIsFromMachineCode := 1.
- 	TraceIsFromInterpreter := 2.
- 	CSCallbackEnter := 3.
- 	CSCallbackLeave := 4.
- 	CSEnterCriticalSection := 5.
- 	CSExitCriticalSection := 6.
- 	CSResume := 7.
- 	CSSignal := 8.
- 	CSSuspend := 9.
- 	CSWait := 10.
- 	CSYield := 11.
- 	CSCheckEvents := 12.
- 	CSThreadSchedulingLoop := 13.
- 	CSOwnVM := 14.
- 	CSThreadBind := 15.
- 	CSSwitchIfNeccessary := 16.
- 
- 	TraceSources := CArrayAccessor on: #('?' 'm' 'i' 'callbackEnter' 'callbackLeave' 'enterCritical' 'exitCritical' 'resume' 'signal'  'suspend' 'wait' 'yield' 'eventcheck' 'threadsched' 'ownVM' 'bindToThread' 'switchIfNecessary').
- 
- 	"this is simulation only"
- 	RumpCStackSize := 4096!

Item was removed:
- ----- Method: CoInterpreter class>>objectMemoryClass (in category 'accessing class hierarchy') -----
- objectMemoryClass
- 	^NewCoObjectMemory!

Item was added:
+ ----- Method: CoInterpreterMT class>>initializeMiscConstants (in category 'initialization') -----
+ initializeMiscConstants
+ 
+ 	super initializeMiscConstants.
+ 	COGMTVM := true.
+ 
+ 	ReturnToThreadSchedulingLoop := 2. "setjmp/longjmp code."
+ 
+ 	"N.B. some of these DisownFlags are replicated in platforms/Cross/vm/sqVirtualMachine.h"
+ 	DisownVMLockOutFullGC := 1.
+ 	DisownVMForProcessorRelinquish := 2!

Item was removed:
- ----- Method: CoInterpreterMT class>>initializeMiscConstantsWith: (in category 'initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 
- 	super initializeMiscConstantsWith: optionsDictionary.
- 	COGMTVM := true.
- 
- 	ReturnToThreadSchedulingLoop := 2. "setjmp/longjmp code."
- 
- 	"N.B. some of these DisownFlags are replicated in platforms/Cross/vm/sqVirtualMachine.h"
- 	DisownVMLockOutFullGC := 1.
- 	DisownVMForProcessorRelinquish := 2!

Item was changed:
  ----- Method: CogVMSimulator>>primitiveExecuteMethod (in category 'debugging traps') -----
  primitiveExecuteMethod
+ 	self halt: thisContext selector.
- 	self halt.
  	^super primitiveExecuteMethod!

Item was changed:
  ----- Method: CogVMSimulator>>primitiveExecuteMethodArgsArray (in category 'control primitives') -----
  primitiveExecuteMethodArgsArray
+ 	self halt: thisContext selector.
- 	self halt.
  	^super primitiveExecuteMethodArgsArray!

Item was added:
+ ----- Method: Cogit class>>initializeBytecodeTable (in category 'class initialization') -----
+ initializeBytecodeTable
+ 	"SimpleStackBasedCogit initializeBytecodeTableWith: Dictionary new"
+ 	"StackToRegisterMappingCogit initializeBytecodeTableWith: Dictionary new"
+ 
+ 	(initializationOptions at: #bytecodeTableInitializer ifAbsent: nil) ifNotNil:
+ 		[:initalizer| ^self perform: initalizer].
+ 
+ 	NewspeakVM ifTrue:
+ 		[^MULTIPLEBYTECODESETS
+ 			ifTrue: [self initializeBytecodeTableForNewspeakV3PlusClosuresNewspeakV4Hybrid]
+ 			ifFalse: [self initializeBytecodeTableForNewspeakV3PlusClosures]].
+ 	^self initializeBytecodeTableForSqueakV3PlusClosures!

Item was removed:
- ----- Method: Cogit class>>initializeBytecodeTableWith: (in category 'class initialization') -----
- initializeBytecodeTableWith: optionsDictionary
- 	"SimpleStackBasedCogit initializeBytecodeTableWith: Dictionary new"
- 	"StackToRegisterMappingCogit initializeBytecodeTableWith: Dictionary new"
- 
- 	(optionsDictionary at: #bytecodeTableInitializer ifAbsent: nil) ifNotNil:
- 		[:initalizer| ^self perform: initalizer].
- 
- 	NewspeakVM ifTrue:
- 		[^MULTIPLEBYTECODESETS
- 			ifTrue: [self initializeBytecodeTableForNewspeakV3PlusClosuresNewspeakV4Hybrid]
- 			ifFalse: [self initializeBytecodeTableForNewspeakV3PlusClosures]].
- 	^self initializeBytecodeTableForSqueakV3PlusClosures!

Item was added:
+ ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
+ initializeMiscConstants
+ 	super initializeMiscConstants.
+ 	Debug := initializationOptions at: #Debug ifAbsent: [false].
+ 	(initializationOptions includesKey: #EagerInstructionDecoration)
+ 		ifTrue:
+ 			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
+ 		ifFalse:
+ 			[EagerInstructionDecoration isNil ifTrue:
+ 				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
+ 
+ 	ProcessorClass := (initializationOptions at: #ISA ifAbsent: [#IA32]) caseOf: {
+ 							[#IA32] 	->	[BochsIA32Alien].
+ 							[#ARMv5]	->	[GdbARMAlien]. }.
+ 	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
+ 	NumSendTrampolines := 4.
+ 	"Currently only the ceImplicitReceiverTrampoline contains object references."
+ 	NumObjRefsInRuntime := 2.
+ 	"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 removed:
- ----- Method: Cogit class>>initializeMiscConstantsWith: (in category 'class initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 	super initializeMiscConstantsWith: optionsDictionary.
- 	Debug := optionsDictionary at: #Debug ifAbsent: [false].
- 	(optionsDictionary includesKey: #EagerInstructionDecoration)
- 		ifTrue:
- 			[EagerInstructionDecoration := optionsDictionary at: #EagerInstructionDecoration]
- 		ifFalse:
- 			[EagerInstructionDecoration isNil ifTrue:
- 				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
- 
- 	ProcessorClass := (optionsDictionary at: #ISA ifAbsent: [#IA32]) caseOf: {
- 							[#IA32] 	->	[BochsIA32Alien].
- 							[#ARMv5]	->	[GdbARMAlien]. }.
- 	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
- 	NumSendTrampolines := 4.
- 	"Currently only the ceImplicitReceiverTrampoline contains object references."
- 	NumObjRefsInRuntime := 2.
- 	"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
  
+ 	super initializeWithOptions: optionsDictionary.
+ 	self initializeMiscConstants. "must preceed other initialization."
- 	self initializeMiscConstantsWith: optionsDictionary. "must preceed other initialization."
  	self initializeErrorCodes.
  	self initializeCogMethodConstants.
  	self initializeAnnotationConstants.
+ 	self initializeBytecodeTable.
- 	self initializeBytecodeTableWith: optionsDictionary.
  	self initializePrimitiveTable!

Item was added:
+ ----- Method: Interpreter class>>initializeMiscConstants (in category 'initialization') -----
+ initializeMiscConstants
+ 
+ 	super initializeMiscConstants.
+ 
+ 	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 removed:
- ----- Method: Interpreter class>>initializeMiscConstantsWith: (in category 'initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 
- 	super initializeMiscConstantsWith: optionsDictionary.
- 
- 	DoBalanceChecks := optionsDictionary 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: Interpreter class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"Interpreter initializeWithOptions: Dictionary new"
  
  	super initializeWithOptions: optionsDictionary.  "initialize ObjectMemory constants"
+ 	self initializeMiscConstants. "must preceed other initialization."
- 	self initializeMiscConstantsWith: optionsDictionary. "must preceed other initialization."
  	self initializeAssociationIndex.
  	self initializeBytecodeTable.
  	self initializeCaches.
  	self initializeCharacterIndex.
  	self initializeCharacterScannerIndices.
  	self initializeClassIndices.
  	self initializeCompilerHooks.
  	self initializeContextIndices.
  	self initializeDirectoryLookupResultCodes.
  	self initializeMessageIndices.
  	self initializeMethodIndices.
  	self initializePointIndices.
  	self initializePrimitiveTable.
  	self initializeSchedulerIndices.
  	self initializeSmallIntegers.
  	self initializeStreamIndices!

Item was added:
+ ----- Method: NewspeakInterpreter class>>initializeMiscConstants (in category 'initialization') -----
+ initializeMiscConstants
+ 
+ 	super initializeMiscConstants.
+ 	NewspeakVM := true.
+ 	IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsent: [true].
+ 
+ 	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 := 1024. "entries"
+ 
+ 	FailImbalancedPrimitives ifNil: [FailImbalancedPrimitives := false].
+ 	RecordPrimTrace := false.
+ 	RecordSendTrace := false.
+ 	TraceLogSize := 256!

Item was removed:
- ----- Method: NewspeakInterpreter class>>initializeMiscConstantsWith: (in category 'initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 
- 	super initializeMiscConstantsWith: optionsDictionary.
- 	NewspeakVM := true.
- 	IMMUTABILITY := optionsDictionary at: #IMMUTABILITY ifAbsent: [true].
- 
- 	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 := 1024. "entries"
- 
- 	FailImbalancedPrimitives ifNil: [FailImbalancedPrimitives := false].
- 	RecordPrimTrace := false.
- 	RecordSendTrace := false.
- 	TraceLogSize := 256!

Item was changed:
  ----- Method: NewspeakInterpreter class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"NewspeakInterpreter initializeWithOptions: Dictionary new"
  
  	super initializeWithOptions: optionsDictionary.  "initialize ObjectMemory constants"
+ 	self initializeMiscConstants. "must preceed other initialization."
- 	self initializeMiscConstantsWith: optionsDictionary. "must preceed other initialization."
  	self initializeAssociationIndex.
  	self initializeBytecodeTable.
  	self initializeCaches.
  	self initializeCharacterIndex.
  	self initializeCharacterScannerIndices.
  	self initializeClassIndices.
  	self initializeContextIndices.
  	self initializeDirectoryLookupResultCodes.
  	self initializeMessageIndices.
  	self initializeMethodIndices.
  	self initializePointIndices.
  	self initializePrimitiveTable.
  	self initializePrimitiveErrorCodes.
  	self initializeSchedulerIndices.
  	self initializeSmallIntegers.
  	self initializeStreamIndices!

Item was added:
+ ----- Method: SimpleStackBasedCogit class>>initializeMiscConstants (in category 'class initialization') -----
+ initializeMiscConstants
+ 	super initializeMiscConstants.
+ 	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
+ 	NumTrampolines := NewspeakVM
+ 							ifTrue: [46]
+ 							ifFalse: [38]!

Item was removed:
- ----- Method: SimpleStackBasedCogit class>>initializeMiscConstantsWith: (in category 'class initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 	super initializeMiscConstantsWith: optionsDictionary.
- 	MaxLiteralCountForCompile := optionsDictionary at: #MaxLiteralCountForCompile ifAbsent: [60].
- 	NumTrampolines := NewspeakVM
- 							ifTrue: [46]
- 							ifFalse: [38]!

Item was removed:
- ----- Method: SmartSyntaxPluginTMethod class>>fromContext:primitive:parameters:receiver: (in category 'as yet unclassified') -----
- fromContext: aContext primitive: aString parameters: aClassList receiver: aClass
- 
- 	^super new 
- 		fromContext: aContext 
- 		primitive: aString 
- 		parameters: aClassList 
- 		receiver: aClass
- !

Item was removed:
- ----- Method: SmartSyntaxPluginTMethod>>replaceArraySizeMessages (in category 'transforming') -----
- replaceArraySizeMessages
- 	"Replace sends of the message 'size' with calls to sizeOfSTArrayFromCPrimitive. Specialised version for generating primitives outside a plugin"
- 
- 	super replaceSizeMessages
- !

Item was added:
+ ----- Method: Spur32BitMemoryManager class>>simulatorClass (in category 'simulation only') -----
+ simulatorClass
+ 	^Spur32BitMMLESimulator!

Item was added:
+ ----- Method: StackInterpreter class>>defaultObjectMemoryClass (in category 'accessing class hierarchy') -----
+ defaultObjectMemoryClass
+ 	^NewObjectMemory!

Item was added:
+ ----- Method: StackInterpreter class>>initializeMiscConstants (in category 'initialization') -----
+ initializeMiscConstants
+ 
+ 	super initializeMiscConstants.
+ 	STACKVM := true.
+ 
+ 	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 := true!

Item was removed:
- ----- Method: StackInterpreter class>>initializeMiscConstantsWith: (in category 'initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 
- 	super initializeMiscConstantsWith: optionsDictionary.
- 	STACKVM := true.
- 
- 	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 := true!

Item was changed:
  ----- Method: StackInterpreter class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"StackInterpreter initializeWithOptions: Dictionary new"
  
+ 	super initializeWithOptions: optionsDictionary.
+ 	self initializeMiscConstants. "must preceed other initialization."
- 	self initializeMiscConstantsWith: optionsDictionary. "must preceed 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 removed:
- ----- Method: StackInterpreter class>>objectMemoryClass (in category 'accessing class hierarchy') -----
- objectMemoryClass
- 	^NewObjectMemory!

Item was changed:
  ----- Method: StackInterpreterSimulator>>primitiveExecuteMethod (in category 'control primitives') -----
  primitiveExecuteMethod
+ 	self halt: thisContext selector.
- 	self halt.
  	^super primitiveExecuteMethod!

Item was added:
+ ----- Method: StackToRegisterMappingCogit class>>initializeMiscConstants (in category 'class initialization') -----
+ initializeMiscConstants
+ 	super initializeMiscConstants.
+ 	NumTrampolines := NewspeakVM
+ 							ifTrue: [58]
+ 							ifFalse: [50]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit class>>initializeMiscConstantsWith: (in category 'class initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 	super initializeMiscConstantsWith: optionsDictionary.
- 	NumTrampolines := NewspeakVM
- 							ifTrue: [58]
- 							ifFalse: [50]!

Item was changed:
  Object subclass: #VMClass
  	instanceVariableNames: ''
  	classVariableNames: 'DefaultBase'
  	poolDictionaries: 'VMBasicConstants VMObjectIndices'
  	category: 'VMMaker-Support'!
  VMClass class
+ 	instanceVariableNames: 'timeStamp initializationOptions'!
- 	instanceVariableNames: 'timeStamp'!
  
  !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 initializationOptions'!
- 	instanceVariableNames: 'timeStamp'!

Item was added:
+ ----- Method: VMClass class>>defaultObjectMemoryClass (in category 'accessing class hierarchy') -----
+ defaultObjectMemoryClass
+ 	"Default for all-in-one VMs where the interpreter inherits from the object memory."
+ 	^nil!

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

Item was added:
+ ----- 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,
+ 	 or in the case of VMBIGENDIAN the various sqConfig.h files.
+ 	 Subclass implementations need to include a super initializeMiscConstantsWith:."
+ 
+ 	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
+ 	self isInterpreterClass ifTrue:
+ 		[STACKVM := COGVM := COGMTVM := false].
+ 	NewspeakVM := initializationOptions at: #NewspeakVM ifAbsent: [false].
+ 	MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsent: [false].
+ 	"N.B.  Not yet implemented."
+ 	IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsent: [false].
+ 
+ 	"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 removed:
- ----- Method: VMClass class>>initializeMiscConstantsWith: (in category 'initialization') -----
- initializeMiscConstantsWith: optionsDictionary
- 	"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 initializeMiscConstantsWith:."
- 
- 	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
- 	self isInterpreterClass ifTrue:
- 		[STACKVM := COGVM := COGMTVM := false].
- 	NewspeakVM := optionsDictionary at: #NewspeakVM ifAbsent: [false].
- 	MULTIPLEBYTECODESETS := optionsDictionary at: #MULTIPLEBYTECODESETS ifAbsent: [false].
- 	"N.B.  Not yet implemented."
- 	IMMUTABILITY := optionsDictionary at: #IMMUTABILITY ifAbsent: [false].
- 
- 	"These for scripts etc... Usually they should get set by an Interpreter class's initializeMiscConstantsWith:"
- 	(optionsDictionary includesKey: #STACKVM) ifTrue:
- 		[STACKVM := optionsDictionary at: #STACKVM].
- 	(optionsDictionary includesKey: #COGVM) ifTrue:
- 		[COGVM := optionsDictionary at: #COGVM].
- 	(optionsDictionary includesKey: #COGMTVM) ifTrue:
- 		[COGMTVM := optionsDictionary at: #COGMTVM]!

Item was changed:
  ----- Method: VMClass class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"Initialize the receiver, typically initializing class variables. Initialize any class variables
+ 	 whose names occur in optionsDictionary with the corresponding values there-in."
+ 	(self withAllSuperclasses copyUpThrough: VMClass) do:
+ 		[:class|
+ 		class initializationOptions: optionsDictionary]!
- 	 whose names occur in optionsDictionary with the corresponding values there-in."!

Item was changed:
  ----- Method: VMClass class>>objectMemoryClass (in category 'accessing class hierarchy') -----
  objectMemoryClass
+ 	initializationOptions ifNil:
+ 		[^self defaultObjectMemoryClass].
+ 	^Smalltalk at: (initializationOptions
+ 					at: #ObjectMemory
+ 					ifAbsent: [^self defaultObjectMemoryClass])!
- 	"Default for all-in-one VMs where the interpreter inherits from the object memory."
- 	^nil!



More information about the Vm-dev mailing list