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

commits at source.squeak.org commits at source.squeak.org
Fri Feb 18 20:05:50 UTC 2022


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

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

Name: VMMaker.oscog-eem.3159
Author: eem
Time: 18 February 2022, 11:59:34.550592 am
UUID: c1612d06-f1b4-4bb1-8528-43aac645fa70
Ancestors: VMMaker.oscog-eem.3158

CoInterpreter: fix a serious bug with post-become processing in Spur where the instruction pointer could be updated incorrectly if it was in machine code (CoInterpreter>>followForwardingPointersInStackZone:).  Nuke the unused primErrTable.

Slang: Add shared pool variables to cointerp.h so tat phase errors are caught.  Rename PrimErrTableIndex to PrimitiveErrorTableIndex so it is not confused with the PrimErrXXX values.  Fix a bug with VMMakerTool when changing the source directory; VMMaker held onto the old directory objects.

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

Item was changed:
  ----- Method: CCodeGenerator>>commonSharedPoolVariableNames (in category 'C code generator') -----
  commonSharedPoolVariableNames
  	"Answer the names of pool variables (potentially) shared between the Cogit and the CoInterpreter, but not defined in interp.h"
  	| commonConstants cointerpPools cogitPools |
  	commonConstants := Set new.
  	cointerpPools := vmClass withAllSuperclasses
  						inject: Set new
  						into: [:them :class| them addAll: class poolDictionaryNames. them].
  	cogitPools := vmClass cogitClass withAllSuperclasses
  						inject: Set new
  						into: [:them :class| them addAll: class poolDictionaryNames. them].
  	(cointerpPools intersection: cogitPools) do:
  		[:poolName|
  		(Smalltalk at: poolName) classPool associationsDo:
  			[:binding|
  			 (self isCLiteral: binding value) ifTrue:
  				[commonConstants add: binding key]]].
  	#(initializeMiscConstants initializePrimitiveErrorCodes) do:
  		[:selector|
  		(VMClass class>>selector) literalsDo:
  			[:lit|
+ 			(lit isVariableBinding and: [lit key isString and: [lit key ~~ #PrimitiveErrorTableIndex]]) ifTrue:
- 			(lit isVariableBinding and: [lit key isString]) ifTrue:
  				[commonConstants remove: lit key ifAbsent: []]]].
  	VMBasicConstants mostBasicConstantNames do:
  		[:mbcn| commonConstants remove: mbcn ifAbsent: []].
  	^commonConstants!

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstantsOn: (in category 'C code generator') -----
  emitCConstantsOn: aStream 
  	"Store the global variable declarations on the given stream."
  	| unused |
  	unused := constants keys asSet.
+ 	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: []]]].
  	"Don't generate any defines for the externally defined constants,
  	 STACKVM, COGVM, COGMTVM et al, unless they're actually used.
  	 Also don't generate the PrimErr defines; these must be taken from interp.h"
  	#(initializeMiscConstants initializePrimitiveErrorCodes) do:
  		[:selector|
  		(VMClass class>>selector) literalsDo:
  			[:lit|
+ 			(lit isVariableBinding and: [lit key isString and: [lit key ~~ #PrimitiveErrorTableIndex]]) ifTrue:
- 			(lit isVariableBinding and: [lit key isString]) ifTrue:
  				[unused add: lit key]]].
  	"and VMBasicConstants mostBasicConstantNames must be taken from interp.h"
  	unused addAll: VMBasicConstants mostBasicConstantNames.
- 	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: []]].
+ 	self emitCConstants: (constants keys reject: [:any| unused includes: any]) on: aStream!
- 		self emitCConstants: (constants keys reject: [:any| unused includes: any]) on: aStream!

Item was changed:
  ----- Method: CoInterpreter class>>metadataFlagsForPrimitive: (in category 'spur compilation support') -----
  metadataFlagsForPrimitive: aPrimitiveMethodOrNil
+ 	"Primitive methods may decorate themselves with 8 flags (FastCPrimitiveFlag FastCPrimitiveAlignForFloatsFlag et al)
+ 	 that alter how the Cogit dispatches primitives. These flags are supplied by the primitiveMetadata: pragma.
+ 	 Primitive methods that access newMethod (e.g. primitiveExternalCall), or may experience a code compaction (e.g.
+ 	 they may callback), are required to decorate themselves with the PrimCallMayEndureCodeCompaction &
+ 	 PrimCallNeedsNewMethod flags. This information is used by the JIT to generate correct and efficient dispatch code."
- 	"We allow methods to decorate themselves with 8 flags (FastCPrimitiveFlag FastCPrimitiveAlignForFloatsFlag et al)
- 	 that alter how the Cogit dispatches primitives. These flags are supplied by the primitiveMetadata: pragma."
  	aPrimitiveMethodOrNil ifNil: [^0].
  	^(aPrimitiveMethodOrNil pragmaAt: #primitiveMetadata:)
  		ifNil: [0]
  		ifNotNil:
  			[:pragma| | flags |
  			flags := (flags := pragma arguments first) isInteger
  						ifTrue: [flags]
  						ifFalse: [self valueOfMetadataFlag: flags].
  			"PrimCallMayEndureCodeCompaction & PrimCallOnSmalltalkStack[Align2x] are mutually exclusive..."
+ 			self assert: ((flags noMask: PrimCallMayEndureCodeCompaction) or: [flags noMask: PrimCallOnSmalltalkStack + PrimCallOnSmalltalkStackAlign2x]).
+ 			"And because ceActivateFailingPrimitiveMethod: needs newMethod to be up-to-date,
+ 			 PrimCallMayEndureCodeCompaction implies PrimCallNeedsNewMethod."
+ 			self assert: ((flags noMask: PrimCallMayEndureCodeCompaction) or: [flags allMask: PrimCallNeedsNewMethod]).
- 			self assert: ((flags anyMask: PrimCallMayEndureCodeCompaction) & (flags anyMask: PrimCallOnSmalltalkStack + PrimCallOnSmalltalkStackAlign2x)) not.
  			flags]!

Item was changed:
  ----- Method: CoInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  
  	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become.
  
  	 Override to handle machine code frames"
  	| theIPPtr |
  	<inline: false>
- 	<var: #theSP type: #'char *'>
- 	<var: #theFP type: #'char *'>
- 	<var: #theIPPtr type: #usqInt>
- 	<var: #callerFP type: #'char *'>
- 	<var: #thePage type: #'StackPage *'>
  
- 	self externalWriteBackHeadFramePointers.
- 
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
+ 			[theIPPtr := instructionPointer > method ifTrue: [instructionPointer - method].
- 			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
+ 			 theIPPtr ifNotNil: [instructionPointer := method + theIPPtr]].
- 			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
+ 	stackPage = 0 ifTrue: "the system must be snapshotting; nothing to do..."
+ 		[self assert: (stackPages mostRecentlyUsedPage isNil or: [stackPages mostRecentlyUsedPage isFree]).
+ 		 self cCode: [] inSmalltalk: [self assert: stackPages allPagesFree].
+ 		 ^self].
+ 
+ 	self externalWriteBackHeadFramePointers.
+ 
- 	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  			 theFP := thePage headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
+ 			 theIPPtr := thePage = stackPage ifFalse: [thePage headSP asUnsignedInteger].
- 			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
+ 			  self assert: (theIPPtr isNil or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
- 			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[oop := stackPages longAt: theFP + FoxMFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxMFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 self assert: (objectMemory isForwarded: (self mframeHomeMethod: theFP) methodObject) not]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := self iframeMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
  						[| newOop |
  						 newOop := objectMemory followForwarded: oop.
  						 offset := newOop - oop.
+ 						 (theIPPtr notNil
- 						 (theIPPtr ~= 0
  						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + offset].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + offset.
  						stackPages
  							longAt: theFP + FoxMethod
  							put: (oop := newOop)]].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the saved context and the caller context."
  			 theSP := thePage baseAddress - objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isForwarded: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory followForwarded: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was removed:
- ----- Method: CoInterpreter>>primErrTable (in category 'cog jit support') -----
- primErrTable
- 	<api>
- 	^objectMemory splObj: PrimErrTableIndex!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFlushExternalPrimitives (in category 'plugin primitives') -----
  primitiveFlushExternalPrimitives
  	"Primitive. Flush all the existing external primitives in the image thus forcing a reload on next invocation."
+ 	<primitiveMetadata: #(PrimCallMayEndureCodeCompaction PrimCallNeedsNewMethod)>
- 	<primitiveMetadata: #PrimCallMayEndureCodeCompaction>
  	self flushExternalPrimitives!

Item was changed:
  ----- Method: ObjectMemory>>primitiveErrorTable (in category 'interpreter access') -----
  primitiveErrorTable
  	<api>
+ 	^self splObj: PrimitiveErrorTableIndex!
- 	^self splObj: PrimErrTableIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>primitiveErrorTable (in category 'accessing') -----
  primitiveErrorTable
  	<api>
+ 	^self splObj: PrimitiveErrorTableIndex!
- 	^self splObj: PrimErrTableIndex!

Item was changed:
  ----- Method: StackInterpreter class>>metadataFlagsForPrimitive: (in category 'spur compilation support') -----
  metadataFlagsForPrimitive: aPrimitiveMethod
+ 	"Primitive methods may decorate themselves with 8 flags (FastCPrimitiveFlag FastCPrimitiveAlignForFloatsFlag et al)
- 	"We allow methods to decorate themselves with 8 flags (FastCPrimitiveFlag FastCPrimitiveAlignForFloatsFlag et al)
  	 that alter how the Cogit dispatches primitives. These flags are supplied by the primitiveMetadata: pragma.
+ 	 Primitive methods that access newMethod (e.g. primitiveExternalCall), or may experience a code compaction (e.g.
+ 	 they may callback), are required to decorate themselves with the PrimCallMayEndureCodeCompaction &
+ 	 PrimCallNeedsNewMethod flags. This information is used by the JIT to generate correct and efficient dispatch code.
  	 But this is not relevant to the StackInterpreter."
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  
  	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
- 	<var: #theFP type: #'char *'>
- 	<var: #theIPPtr type: #usqInt>
- 	<var: #callerFP type: #'char *'>
- 	<var: #thePage type: #'StackPage *'>
  
- 	stackPage = 0 ifTrue: "the system must be snapshotting; nothing to do..."
- 		[self assert: (stackPages mostRecentlyUsedPage isNil or: [stackPages mostRecentlyUsedPage isFree]).
- 		 self cCode: [] inSmalltalk: [self assert: stackPages allPagesFree].
- 		 ^self].
- 
- 	self externalWriteBackHeadFramePointers.
- 
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
+ 	stackPage = 0 ifTrue: "the system must be snapshotting; nothing to do..."
+ 		[self assert: (stackPages mostRecentlyUsedPage isNil or: [stackPages mostRecentlyUsedPage isFree]).
+ 		 self cCode: [] inSmalltalk: [self assert: stackPages allPagesFree].
+ 		 ^self].
+ 
+ 	self externalWriteBackHeadFramePointers.
+ 
- 	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theFP callerFP offset oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
+ 			 theFP := thePage headFP.
- 			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
+ 			 theIPPtr := thePage = stackPage ifFalse: [thePage headSP asUnsignedInteger].
- 			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
+ 			  self assert: (theIPPtr isNil or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
- 			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  oop := self frameMethod: theFP.
  			  (objectMemory isForwarded: oop) ifTrue:
  				[| newOop delta |
  				 newOop := objectMemory followForwarded: oop.
+ 				 theIPPtr ifNotNil:
- 				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 delta := newOop - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
  					put: (oop := newOop)].
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the caller context."
  			 self assert: theFP = thePage baseFP.
  			 oop := self frameCallerContext: theFP.
  			 (objectMemory isForwarded: oop) ifTrue:
  				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was changed:
  ----- Method: StackInterpreter>>getErrorObjectFromPrimFailCode (in category 'message sending') -----
  getErrorObjectFromPrimFailCode
  	"Answer the errorCode object to supply to a failing primitive method that accepts one.
  	 If there is a primitive error table and the primFailCode is a valid index there-in answer
  	 the corresponding entry in the table, otherwise simply answer the code as an integer."
  	| table errObj |
  	primFailCode > 0 ifTrue:
+ 		[table := objectMemory splObj: PrimitiveErrorTableIndex.
- 		[table := objectMemory splObj: PrimErrTableIndex.
  		 primFailCode <= (objectMemory numSlotsOf: table) ifTrue:
  			[errObj := objectMemory followField: primFailCode - 1 ofObject: table.
  			 "If there's a clonable object in the table at that index,
  			 answer a clone of the error object with the second slot set to the value of secondaryErrorCode."
  			 (objectMemory formatOf: errObj) = objectMemory nonIndexablePointerFormat ifTrue:
  				[errObj := self cloneErrorObj: errObj].
  			 ^errObj]].
  	^objectMemory integerObjectOf: primFailCode!

Item was changed:
  ----- Method: VMClass class>>initializePrimitiveErrorCodes (in category 'initialization') -----
  initializePrimitiveErrorCodes
  	"Define the VM's primitive error codes.  N.B. these are
  	 replicated in platforms/Cross/vm/sqVirtualMachine.h."
  	"VMClass initializePrimitiveErrorCodes"
  	| pet |
+ 	PrimitiveErrorTableIndex := 51. "Zero-relative"
- 	PrimErrTableIndex := 51. "Zero-relative"
  	"See SmalltalkImage>>recreateSpecialObjectsArray for the table definition.
  	 If the table exists and is large enough the corresponding entry is returned as
  	 the primitive error, otherwise the error is answered numerically."
+ 	pet := Smalltalk specialObjectsArray at: PrimitiveErrorTableIndex + 1 ifAbsent: [#()].
- 	pet := Smalltalk specialObjectsArray at: PrimErrTableIndex + 1 ifAbsent: [#()].
  	pet isArray ifFalse: [pet := #()].
  	PrimNoErr := 0. "for helper methods that need to answer success or an error code."
  	PrimErrGenericFailure		:= pet indexOf: nil ifAbsent: 1.
  	PrimErrBadReceiver			:= pet indexOf: #'bad receiver' ifAbsent: 2.
  	PrimErrBadArgument		:= pet indexOf: #'bad argument' ifAbsent: 3.
  	PrimErrBadIndex			:= pet indexOf: #'bad index' ifAbsent: 4.
  	PrimErrBadNumArgs		:= pet indexOf: #'bad number of arguments' ifAbsent: 5.
  	PrimErrInappropriate		:= pet indexOf: #'inappropriate operation' ifAbsent: 6.
  	PrimErrUnsupported		:= pet indexOf: #'unsupported operation' ifAbsent: 7.
  	PrimErrNoModification		:= pet indexOf: #'no modification' ifAbsent: 8.
  	PrimErrNoMemory			:= pet indexOf: #'insufficient object memory' ifAbsent: 9.
  	PrimErrNoCMemory			:= pet indexOf: #'insufficient C memory' ifAbsent: 10.
  	PrimErrNotFound			:= pet indexOf: #'not found' ifAbsent: 11.
  	PrimErrBadMethod			:= pet indexOf: #'bad method' ifAbsent: 12.
  	PrimErrNamedInternal		:= pet indexOf: #'internal error in named primitive machinery' ifAbsent: 13.
  	PrimErrObjectMayMove		:= pet indexOf: #'object may move' ifAbsent: 14.
  	PrimErrLimitExceeded		:= pet indexOf: #'resource limit exceeded' ifAbsent: 15.
  	PrimErrObjectIsPinned		:= pet indexOf: #'object is pinned' ifAbsent: 16.
  	PrimErrWritePastObject		:= pet indexOf: #'primitive write beyond end of object' ifAbsent: 17.
  	PrimErrObjectMoved		:= pet indexOf: #'object moved' ifAbsent: 18.
  	PrimErrObjectNotPinned	:= pet indexOf: #'object not pinned' ifAbsent: 19.
  	PrimErrCallbackError		:= pet indexOf: #'error in callback' ifAbsent: 20.
  	PrimErrOSError				:= pet indexOf: #'operating system error' ifAbsent: 21.
  	PrimErrFFIException		:= pet indexOf: #'ffi call exception' ifAbsent: 22.
  	PrimErrNeedCompaction	:= pet indexOf: #'heap compaction needed' ifAbsent: 23. "N.B. This is currently an internal error in Spur image segment saving."
  	PrimErrOperationFailed		:= pet indexOf: #'operation failed' ifAbsent: 24.
  	PrimErrInternalError		:= pet indexOf: #'internal error' ifAbsent: 25.
  	PrimErrUninitialized			:= pet indexOf: #'uninitialized' ifAbsent: 26.
  	PrimErrFFIMarshallingError	:= pet indexOf: #'ffi marshalling error' ifAbsent: 27!

Item was changed:
  ----- Method: VMMaker>>sourceDirectoryName: (in category 'target directories') -----
  sourceDirectoryName: aString
  	"Sanity check really ought to be added, This is the root directory for where the sources will be WRITTEN"
  	sourceDirName := aString.
+ 	coreVMDirectory := sourceDirectory := nil.
  	(aString first == $.
  		ifTrue: [FileDirectory default directoryNamed: aString]
  		ifFalse: [FileDirectory on: aString]) assureExistence.
  	self changed: #sourceDirectory.
  	^true!

Item was changed:
  SharedPool subclass: #VMObjectIndices
  	instanceVariableNames: ''
+ 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassDoubleByteArray ClassDoubleWordArray ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFullBlockClosure ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClassWordArray ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess FullClosureCompiledBlockIndex FullClosureFirstCopiedValueIndex FullClosureReceiverIndex HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex Liter
 alStart LowcodeContextMark LowcodeNativeContextClass MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimitiveErrorTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorSistaTrap SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
- 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassDoubleByteArray ClassDoubleWordArray ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFullBlockClosure ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClassWordArray ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess FullClosureCompiledBlockIndex FullClosureFirstCopiedValueIndex FullClosureReceiverIndex HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex Liter
 alStart LowcodeContextMark LowcodeNativeContextClass MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorSistaTrap SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMObjectIndices commentStamp: '<historical>' prior: 0!
  I am a shared pool for the constants that define object layout and well-known objects shared between the object memories (e.g. ObjectMemory, NewObjectMemory), the interpreters (e.g. StackInterpreter, CoInterpreter) and the object representations (e.g. ObjectRepresentationForSqueakV3).
  
  self classPool declare: #Foo from: StackInterpreter classPool
  
  (ObjectMemory classPool keys select: [:k| (k beginsWith: 'Class') and: [(k endsWith: 'Index') not]]) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list