[Vm-dev] VM Maker Inbox: VMMaker.oscog-dtl.2711.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Feb 9 22:47:40 UTC 2020


A new version of VMMaker was added to project VM Maker Inbox:
http://source.squeak.org/VMMakerInbox/VMMaker.oscog-dtl.2711.mcz

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

Name: VMMaker.oscog-dtl.2711
Author: dtl
Time: 9 February 2020, 5:47:29.014712 pm
UUID: a5d389c6-2be9-46d7-bb69-789785b782eb
Ancestors: VMMaker.oscog-nice.2709

Let the image inform the interpreter that alternate bytecodes either are or are not in use, and remember that setting when writing or reading the image format number in a shapshot file header.

For background and image side accessor examples see http://lists.squeakfoundation.org/pipermail/vm-dev/2020-January/032441.html

Backward compatibie, there is no change to existing VM or image behavior.

=============== Diff against VMMaker.oscog-nice.2709 ===============

Item was changed:
  VMClass subclass: #InterpreterPrimitives
+ 	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode exceptionPC inFFIFlags profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn ffiExceptionResponse multipleBytecodeSetsActive'
- 	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode osErrorCode exceptionPC inFFIFlags profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields newFinalization sHEAFn ffiExceptionResponse'
  	classVariableNames: 'CrossedX EndOfRun MillisecondClockMask'
  	poolDictionaries: 'VMBasicConstants VMBytecodeConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !InterpreterPrimitives commentStamp: 'eem 8/24/2018 11:05' 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>
  	ffiExceptionResponse		<Integer>
  	inFFIFlags					<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
  
  ffiExceptionResponse
  	- controls system response to exceptions during FFI calls.  See primitiveFailForFFIException:at:
  
  inFFIFlags
  	- flags recording currently only whether the system is in an FFI call
  
  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
  
  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 added:
+ ----- Method: InterpreterPrimitives>>primitiveMultipleBytecodeSetsActive (in category 'other primitives') -----
+ primitiveMultipleBytecodeSetsActive
+ 	"Set the value of multipleBytecodeSetsActive based on the boolean
+ 	argument if supplied. Fail if multiple bytecode sets are not supported.
+ 	Answer the current value of multipleBytecodeSetsActive."
+ 
+ 	<export: true>
+ 	argumentCount >1 ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadNumArgs].
+ 	argumentCount = 1
+ 		ifTrue: [self stackTop = objectMemory trueObject
+ 			ifTrue: [self cppIf: MULTIPLEBYTECODESETS
+ 				ifTrue: [multipleBytecodeSetsActive := true]
+ 				ifFalse: [^self primitiveFailFor: PrimErrUnsupported]]
+ 			ifFalse: [self stackTop = objectMemory falseObject
+ 				ifTrue: [multipleBytecodeSetsActive := false]
+ 				ifFalse:[^self primitiveFailFor: PrimErrBadArgument]]].
+ 	multipleBytecodeSetsActive
+ 		ifTrue: [self pop: argumentCount + 1 thenPush: objectMemory trueObject]
+ 		ifFalse: [self pop: argumentCount + 1 thenPush: objectMemory falseObject].
+ !

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
(excessive size, no diff calculated)

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].
  
  	ReturnToInterpreter := 1. "setjmp/longjmp code."
  
  	"N.B. some of these DisownFlags are replicated in platforms/Cross/vm/sqVirtualMachine.h.
  	 Hence they should always be initialized.  Because of a hack with callbacks in the non-threaded
  	 VM they must not conflct with the VM's tag bits."
  	DisownVMLockOutFullGC := 8.
  	DisownVMForFFICall := 16.
+ 	DisownVMForThreading := 32.
+ 	
+ 	"The Sista bit in the interpreter image format version number"
+ 	MultipleBytecodeSetsBitmask := 512.
- 	DisownVMForThreading := 32
  !

Item was changed:
  ----- Method: StackInterpreter>>readableFormat: (in category 'image save/restore') -----
  readableFormat: imageVersion
  	"Anwer true if images of the given format are readable by this interpreter.
  	 Allows a virtual machine to accept selected older image formats."
  	<api>
+ 	| imageVersionWithoutSistaBit |
+ 	imageVersionWithoutSistaBit := imageVersion bitAnd: ( -1 - MultipleBytecodeSetsBitmask). "Ignore multiple bytecode support identifier"
+ 	[imageVersionWithoutSistaBit = self imageFormatVersion "Float words in platform-order"
- 	^imageVersion = self imageFormatVersion "Float words in platform-order"
  	   or: [objectMemory hasSpurMemoryManagerAPI not "No compatibility version for Spur as yet"
+ 			and: [imageVersionWithoutSistaBit = self imageFormatCompatibilityVersion]]] "Float words in BigEndian order"
+ 		ifTrue: [multipleBytecodeSetsActive := imageVersion bitAnd: MultipleBytecodeSetsBitmask. "Remember the Sista bit"
+ 			^ true].
+ 	^ false
+ !
- 			and: [imageVersion = self imageFormatCompatibilityVersion]] "Float words in BigEndian order"!

Item was changed:
  ----- Method: StackInterpreter>>writeImageFileIO (in category 'image save/restore') -----
  writeImageFileIO
  	"Write the image header and heap contents to imageFile for snapshot. c.f. writeImageFileIOSimulation.
  	 The game below is to maintain 64-bit alignment for all putLong:toFile: occurrences."
  	<inline: #never>
  	| imageName headerStart headerSize f imageBytes bytesWritten sCWIfn okToWrite |
  	<var: #f type: #sqImageFile>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #sCWIfn type: #'void *'>
  	<var: #imageName declareC: 'extern char imageName[]'>
  
  	self cCode: [] inSmalltalk: [imageName := 'sooth compiler'. ^self writeImageFileIOSimulation].
  
  	"If the security plugin can be loaded, use it to check for write permission.
  	 If not, assume it's ok"
  	sCWIfn := self ioLoadFunction: 'secCanWriteImage' From: 'SecurityPlugin'.
  	sCWIfn ~= 0 ifTrue:
  		[okToWrite := self cCode: '((sqInt (*)(void))sCWIfn)()'.
  		 okToWrite ifFalse:[^self primitiveFail]].
  	
  	"local constants"
  	headerStart := 0.  
  	headerSize := objectMemory wordSize = 4 ifTrue: [64] ifFalse: [128].  "header size in bytes; do not change!!"
  
  	f := self sqImageFile: imageName Open: 'wb'.
  	f = nil ifTrue: "could not open the image file for writing"
  		[^self primitiveFail].
  
  	imageBytes := objectMemory imageSizeToWrite.
  	headerStart := self sqImage: f File: imageName StartLocation: headerSize + imageBytes.
  	self cCode: '/* Note: on Unix systems one could put an exec command here, padded to 512 bytes */'.
  	"position file to start of header"
  	self sqImageFile: f Seek: headerStart.
+ 	multipleBytecodeSetsActive
+ 		ifTrue: [self putWord32: (self imageFormatVersion bitOr: MultipleBytecodeSetsBitmask) toFile: f]
+ 		ifFalse: [self putWord32: self imageFormatVersion toFile: f].
- 
- 	self putWord32: self imageFormatVersion toFile: f.
  	self putWord32: headerSize toFile: f.
  	self putLong: imageBytes toFile: f.
  	self putLong: objectMemory baseAddressOfImage toFile: f.
  	self putLong: objectMemory specialObjectsOop toFile: f.
  	self putLong: objectMemory newObjectHash toFile: f.
  	self putLong: self getSnapshotScreenSize toFile: f.
  	self putLong: self getImageHeaderFlags toFile: f.
  	self putWord32: extraVMMemory toFile: f.
  	self putShort: desiredNumStackPages toFile: f.
  	self putShort: self unknownShortOrCodeSizeInKs toFile: f.
  	self putWord32: desiredEdenBytes toFile: f.
  	self putShort: (maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]) toFile: f.
  	self putShort: the2ndUnknownShort toFile: f.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[self putLong: objectMemory firstSegmentBytes toFile: f.
  			 self putLong: objectMemory bytesLeftInOldSpace toFile: f.
  			 2 timesRepeat: [self putLong: 0 toFile: f]	"Pad the rest of the header."]
  		ifFalse:
  			[4 timesRepeat: [self putLong: 0 toFile: f]].  "Pad the rest of the header."
  
  	 objectMemory wordSize = 8 ifTrue:
  		[3 timesRepeat: [self putLong: 0 toFile: f]]. "Pad the rest of the header."
  
  	self assert: headerStart + headerSize = (self sqImageFilePosition: f).
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	self successful ifFalse: "file write or seek failure"
  		[self sqImageFileClose: f.
  		 ^nil].
  
  	"write the image data"
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[bytesWritten := objectMemory writeImageSegmentsToFile: f]
  		ifFalse:
  			[bytesWritten := self sq: (self pointerForOop: objectMemory baseAddressOfImage)
  								Image: (self sizeof: #char)
  								File: imageBytes
  								Write: f].
  	self success: bytesWritten = imageBytes.
  	self sqImageFileClose: f!



More information about the Vm-dev mailing list