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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 8 03:53:46 UTC 2017


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

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

Name: VMMaker.oscog-eem.2289
Author: eem
Time: 7 December 2017, 7:53:17.487328 pm
UUID: 2cc5ca31-b578-409a-81c2-4502a4cb0732
Ancestors: VMMaker.oscog-eem.2288

Add support for conveying os/library error codes through a special primitive failure code object.  The error code is a signed 64-bit value (so that e.g. answering -1 is not expensive).  Specific image-level clients can map that value to unsigned as appropriate.

Make sure ceReapAndResetErrorCodeFor: is exported to the Cogit.

Document that primitive 255 ius reserved for use as a failure flag by the R/Squeak VM.

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

Item was changed:
  ----- Method: CoInterpreter>>ceReapAndResetErrorCodeFor: (in category 'trampolines') -----
  ceReapAndResetErrorCodeFor: cogMethod
+ 	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	self break.
  	self assert: primFailCode ~= 0.
  	newMethod := cogMethod methodObject.
  	self reapAndResetErrorCodeTo: stackPointer header: cogMethod methodHeader!

Item was removed:
- ----- Method: CoInterpreter>>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."
- 	^super getErrorObjectFromPrimFailCode!

Item was changed:
  VMClass subclass: #InterpreterPrimitives
+ 	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn'
- 	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn'
  	classVariableNames: 'CrossedX EndOfRun MillisecondClockMask'
  	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
+ !InterpreterPrimitives commentStamp: 'eem 12/7/2017 18:44' prior: 0!
- !InterpreterPrimitives commentStamp: 'eem 12/7/2017 11:21' prior: 0!
  InterpreterPrimitives implements most of the VM's core primitives.  It is the root of the interpreter hierarchy so as to share the core primitives amongst the varioius interpreters.
  
  Instance Variables
  	argumentCount:			<Integer>
  	messageSelector:			<Integer>
  	newMethod:				<Integer>
  	nextProfileTick:				<Integer>
  	objectMemory:				<ObjectMemory> (simulation only)
  	preemptionYields:			<Boolean>
  	primFailCode:				<Integer>
+ 	osErrorCode:				<Integer>
  	profileMethod:				<Integer>
  	profileProcess:				<Integer>
  	profileSemaphore:			<Integer>
  	secHasEnvironmentAccess <Integer>
  
  argumentCount
  	- the number of arguments of the current message
  
  messageSelector
  	- the oop of the selector of the current message
  
  newMethod
  	- the oop of the result of looking up the current message
  
  nextProfileTick
  	- the millisecond clock value of the next profile tick (if profiling is in effect)
  
  objectMemory
  	- the memory manager and garbage collector that manages the heap
  
  preemptionYields
  	- a boolean controlling the process primitives.  If true (old, incorrect, blue-book semantics) a preempted process is sent to the back of its run-queue.  If false, a process preempted by a higher-priority process is put back at the head of its run queue, hence preserving cooperative scheduling within priorities.
  
  primFailCode
+ 	- primitive success/failure flag, 0 for success, otherwise the reason code for failure
- 	- primtiive success/failure flag, 0 for success, otherwise the reason code for failure
  
+ osErrorCode
+ 	- a 64-bit value settable by external primitives conveying arbitrary error codes from the operating system and/or system libraries
+ 
  profileMethod
  	- the oop of the method at the time nextProfileTick was reached
  
  profileProcess
  	- the oop of the activeProcess at the time nextProfileTick was reached
  
  profileSemaphore
  	- the oop of the semaphore to signal when nextProfileTick is reached
  
  secHasEnvironmentAccess
  	- the function to call to check if access to the envronment should be granted to primitiveGetenv
  !

Item was changed:
  ----- Method: InterpreterPrimitives class>>declareCVarsIn: (in category 'C translation') -----
  declareCVarsIn: aCCodeGen
+ 	aCCodeGen
+ 		var: 'osErrorCode' type: #sqLong;
+ 		var: 'sHEAFn' declareC: 'int (*sHEAFn)() = 0' "the hasEnvironmentAccess function"!
- 	aCCodeGen var: 'sHEAFn' declareC: 'int (*sHEAFn)() = 0' "the hasEnvironmentAccess function"!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveFailForOSError: (in category 'primitive support') -----
+ primitiveFailForOSError: osError
+ 	<var: 'osError' type: #sqLong>
+ 	"Set PrimErrOSError primitive failure and associated osErrorCode."
+ 	<api>
+ 	osErrorCode := osError.
+ 	^primFailCode := PrimErrOSError!

Item was changed:
  Object subclass: #InterpreterProxy
+ 	instanceVariableNames: 'primFailCode remapBuffer stack method argumentCount bb thisSessionID osErrorCode'
- 	instanceVariableNames: 'primFailCode remapBuffer stack method argumentCount bb thisSessionID'
  	classVariableNames: ''
+ 	poolDictionaries: 'VMBasicConstants'
- 	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
+ !InterpreterProxy commentStamp: 'eem 12/7/2017 19:37' prior: 0!
+ This class should provide the definition of what interpreter support plugins need and can have access to. Note that the proxy related files platforms - Cross - vm - sqVirtualMachine.[ch] are kept under the git tree at http://www.github.com/opensmalltalk/vm.
- !InterpreterProxy commentStamp: '<historical>' prior: 0!
- This class should provide the definition of what interpreter support plugins need and can have access to. Note that the proxy related files platforms - Cross - vm - sqVirtualMachine.[ch] are kept under the SVN tree at www.squeakvm.org .
  The main use of the class is to support the vm simulator!

Item was added:
+ ----- Method: InterpreterProxy>>primitiveFailForOSError: (in category 'other') -----
+ primitiveFailForOSError: osError
+ 	<var: 'osError' type: #sqLong>
+ 	"Set PrimErrOSError primitive failure and associated osErrorCode.
+ 	 Primitive 255 is called to indicate that we are currently simulating a primitive that should fail and the VM should handle that case appropriately (if supported by the VM)."
+ 	<primitive: 255>
+ 	osErrorCode := osError.
+ 	^primFailCode := PrimErrOSError!

Item was added:
+ ----- Method: ObjectMemory>>nonIndexablePointerFormat (in category 'header formats') -----
+ nonIndexablePointerFormat
+ 	^1!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter class>>vmProxyMinorVersion (in category 'api version') -----
  vmProxyMinorVersion
  	"Define the  VM_PROXY_MINOR version for this VM as used to
  	 define the api in platforms/Cross/vm/sqVirtualMachine.[ch]"
+ 	^14 "primitiveFailForOSError: added"!
- 	^14 "statNumGCs added"!

Item was added:
+ ----- Method: StackInterpreter>>cloneOSErrorObj:numSlots: (in category 'message sending') -----
+ cloneOSErrorObj: errObj numSlots: numSlots
+ 	"If errObj is a pointer object with at least two slots, then answer a clone
+ 	  of the error object with the second slot set to the value of osErrorCode."
+ 	| clone |
+ 	<inline: true>
+ 	clone := objectMemory hasSpurMemoryManagerAPI
+ 				ifTrue: [objectMemory
+ 							eeInstantiateSmallClassIndex: (objectMemory classIndexOf: errObj)
+ 							format: objectMemory nonIndexablePointerFormat
+ 							numSlots: numSlots]
+ 				ifFalse: [objectMemory
+ 							eeInstantiateSmallClass: (objectMemory fetchClassOfNonImm: errObj)
+ 							numSlots: numSlots].
+ 	0 to: numSlots - 1 do:
+ 		[:i| objectMemory
+ 				storePointerUnchecked: i
+ 				ofObject: clone
+ 				withValue: (objectMemory fetchPointer: i ofObject: errObj)].
+ 	objectMemory
+ 		storePointerUnchecked: 1
+ 		ofObject: clone
+ 		withValue: (self signed64BitIntegerFor: osErrorCode).
+ 	^clone!

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 numSlots |
- 	| table |
  	primFailCode > 0 ifTrue:
  		[table := objectMemory splObj: PrimErrTableIndex.
  		 primFailCode <= (objectMemory numSlotsOf: table) ifTrue:
+ 			[errObj := objectMemory followField: primFailCode - 1 ofObject: table.
+ 			 "If this is a PrimErrOSError and 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 osErrorCode."
+ 			 (primFailCode = PrimErrOSError
+ 			  and: [(objectMemory formatOf: errObj) = objectMemory nonIndexablePointerFormat
+ 			  and: [(numSlots := objectMemory numSlotsOf: errObj) >= 2]]) ifTrue:
+ 				[errObj := self cloneOSErrorObj: errObj numSlots: numSlots].
+ 			 ^errObj]].
- 			[^objectMemory fetchPointer: primFailCode - 1 ofObject: table]].
  	^objectMemory integerObjectOf: primFailCode!

Item was changed:
  SharedPool subclass: #VMBasicConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCCheckPrimCall GCModeBecome GCModeFreeSpace GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrUnsupported PrimErrWritePastObject PrimNoErr SPURVM STACKVM SistaVM VMBIGENDIAN'
- 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCCheckPrimCall GCModeBecome GCModeFreeSpace GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrUnsupported PrimErrWritePastObject PrimNoErr SPURVM STACKVM SistaVM VMBIGENDIAN'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMBasicConstants commentStamp: '<historical>' prior: 0!
  I am a shared pool for basic constants upon which the VM as a whole depends.
  
  self ensureClassPool.
  self classPool declare: #BytesPerWord from: VMSqueakV3ObjectRepresentationConstants classPool.
  self classPool declare: #BaseHeaderSize from: VMSqueakV3ObjectRepresentationConstants classPool
  (ObjectMemory classPool keys select: [:k| k beginsWith: 'Byte']) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!

Item was 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 |
  	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: 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!
- 	PrimErrCallbackError		:= pet indexOf: #'error in callback' ifAbsent: 20!



More information about the Vm-dev mailing list