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

commits at source.squeak.org commits at source.squeak.org
Wed Oct 13 17:55:02 UTC 2021


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

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

Name: VMMaker.oscog-eem.3086
Author: eem
Time: 13 October 2021, 10:54:48.735388 am
UUID: 326d7993-ca3c-4987-a17d-85db2e6c85fd
Ancestors: VMMaker.oscog-eem.3085

CoInterpreterMT Work in progress towards being able to bind to any other thread than a specific thread.
Process's threadId is now organized as two bits fields.  The most significant 14 bits are the threadId; if negative, this means "bind to any thread other than the negation"; if positive, this means "bind to this thread". The least significant 14 bits are the thread the proces is affined to (temporarily bound to).  If zero, the Process is not temporarily bound.

Nuke noThreadingOfGUIThread. (hoping also to nuke activeProcessAffined & disowningVMThread).

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

Item was changed:
  CoInterpreterPrimitives subclass: #CoInterpreterMT
+ 	instanceVariableNames: 'cogThreadManager checkThreadActivation maxWaitingPriority foreignCallbackPriority deferThreadSwitch disowningVMThread disownCount foreignCallbackProcessSlot activeProcessAffined relinquishing processHasThreadId reenterThreadSchedulingLoop willNotThreadWarnCount'
+ 	classVariableNames: 'DisownFlagsShift DisownVMForProcessorRelinquish OwnVMForeignThreadFlag PrimNumberRelinquishProcessor ProcessUnaffinedOnDisown ReturnToThreadSchedulingLoop VMAlreadyOwnedHenceDoNotDisown'
- 	instanceVariableNames: 'cogThreadManager checkThreadActivation maxWaitingPriority foreignCallbackPriority deferThreadSwitch disowningVMThread disownCount foreignCallbackProcessSlot willNotThreadWarnCount activeProcessAffined relinquishing processHasThreadId noThreadingOfGUIThread reenterThreadSchedulingLoop'
- 	classVariableNames: 'DisownFlagsShift DisownVMForProcessorRelinquish LockGUIThreadFlag LockGUIThreadShift OwnVMForeignThreadFlag PrimNumberRelinquishProcessor ProcessUnaffinedOnDisown ReturnToThreadSchedulingLoop VMAlreadyOwnedHenceDoNotDisown'
  	poolDictionaries: 'VMThreadingConstants'
  	category: 'VMMaker-Multithreading'!

Item was changed:
  ----- Method: CoInterpreterMT class>>initializeSchedulerIndices (in category 'initialization') -----
  initializeSchedulerIndices
  	super initializeSchedulerIndices.
  	"Class Process"
+ 	"The thread id of a process is either nil or a SmallInteger that defines how a process binds to threads.
+ 	 If nil, the process may run on any thread.
+ 	 The least significant bit of threadId is a flag. The most significant bits are a threadId.
+ 	 If the threadId is nil the process can run on any thread.
+ 	 If the flag (least significant bit) is set then
+ 		If the threadId is positive the process can only be run on the thread with that thread Id.
+ 		If the threadId is negative the process must not be run on the thread with that thread Id.
+ 	 If the flag (least significant bit) is not set then
+ 		the thread id will not be negative and if non-zero is the id of the thread the process is currenty running on
+ 	 The flag is probably a mistake..."
+ 
+ 	"In part, what's really going on here is an attempt to deal with threading on Mac.  Events can only be delivered
+ 	 on the GUi thread. To avoid blocking and/or crashing the VM by making a blocking (e.g. FFI) call on the GUI
+ 	 thread we want a nice way of preventing a process from running on the GUI thread.  We can then use a process
+ 	 whose threadId precludes running on the GUI thread to make blocking calls.  The alternative, of arranging that
+ 	 events are delivered to a thread the VM does not run on, is problematic; it cannot support event callbacks."
+ 
+ 	"So if we simplify, and threadId is only instructive to the VM, (i.e. can say ''run on a given thread'', or ''don't run
+ 	 on a given thread'', and ''don't care; run on any thread'') and does not necessarily hold the threadId of the thread
+ 	 the process is currenty bound to, how do we locate the threadId for a process temporarily affined to a thread for
+ 	 the duration of an FFI call?  Note that a process *must* be bound to a thread for the duration of a threaded call
+ 	 (or foreign callback) so that return occurs on the correct thread.  We can use the least significant bit to mean
+ 	 ''temporarily affined'', but we need to support ''don't run on this thread''.  We could use bit fields (yuck); we
+ 	 could allocate a two field object and assign it to threadId when setting a process to not run on a given thread.
+ 
+ 	 This isn't so bad; use negative values to mean ''don't run on this thread'', and positive values to mean ''run on this thread''.
+ 	 Split the smallest SmallInteger (32-bit, 1 bit sign, 2-bit tags, leaving 29//2) into two 14 bit fields. The least significant
+ 	 14 bits are the thread id the receiver is temporarily affined to.  The most significant 14 bits are the thread id of the
+ 	 thread the proess is either bound to or excluded from.  If zero, the process is agnostic.  See CogThreadManager>>#maxNumThreads"
  	ThreadIdIndex := 4.
+ 	ThreadIdShift := 14. "could be 30 in 64-bits"
  
+ 	"disown result/own argument flags"
+ 	OwnVMForeignThreadFlag := 1.
+ 	VMAlreadyOwnedHenceDoNotDisown := 2.
+ 	ProcessUnaffinedOnDisown := 4.
+ 	"& defined in StackInterpreter are..."
+ 	DisownVMForFFICall := 8.
+ 	DisownVMForThreading := 16.
+ 	DisownFlagsShift := 5!
- 	"disown result/own argument flags & max number of threads"
- 	LockGUIThreadShift := 16.
- 	LockGUIThreadFlag := 1 << LockGUIThreadShift.
- 	OwnVMForeignThreadFlag := 1 << (LockGUIThreadShift + 1).
- 	VMAlreadyOwnedHenceDoNotDisown := 1 << (LockGUIThreadShift + 2).
- 	ProcessUnaffinedOnDisown := 1 << (LockGUIThreadShift + 3).
- 	DisownFlagsShift := LockGUIThreadShift + 4.
- 	ThreadIdMask := (1 << LockGUIThreadShift) - 1 "results in 64k thread indices"
- !

Item was added:
+ ----- Method: CoInterpreterMT>>affinedThreadId: (in category 'process primitive support') -----
+ affinedThreadId: threadIdField
+ 	"Answer the threadId of the thread threadIdField is temporarily bound to, or 0 if none."
+ 	^(objectMemory isIntegerObject: threadIdField)
+ 	 	ifTrue: [(objectMemory integerValueOf: threadIdField) anyMask: 1 << ThreadIdShift - 1]
+ 		ifFalse: [0]!

Item was changed:
  ----- Method: CoInterpreterMT>>bindProcess:toId: (in category 'process primitive support') -----
  bindProcess: aProcess toId: newId
  	"Change a Process's thread binding and answer 0, otherwise answer a suitable error code.
  	 Cases:
  		process is unbound & unaffined
  			id 0 nothing to do
  			id non-zero ensure thread and bind
  		process is affined (temporarily bound to a thread for the duration of a surrender of ownership)
  			id = affined index nothing to do
  			id = 0 nothing to do
  			id ~= 0 && id ~= affined index fail
  		process is bound (permanently bound to a thread)
  			id = bound index nothing to do
  			id ~= bound index set bound index"
+ 	| threadIdField ownerIndex affinedId |
- 	| threadId ownerIndex newThreadIndex |
  	processHasThreadId ifFalse:
  		[^PrimErrUnsupported].
  
+ 	threadIdField := self threadIdFieldOf: aProcess.
+ 	ownerIndex := self ownerIndexOfThreadId: threadIdField.
- 	threadId := self threadIdFieldOf: aProcess.
- 	newThreadIndex := self ownerIndexOfThreadId: newId.
- 	ownerIndex := self ownerIndexOfThreadId: threadId.
  
+ 	"If aProcess is affined (temporarily bound to) a thread then the operation can only
+ 	 succeed if the newId is the same as that aProcess is affined to, or is zero (is unbinding)."
+ 	(self isAffinedThreadId: threadIdField) ifTrue:
+ 		[affinedId := self affinedThreadId: threadIdField.
+ 		 (newId = 0
+ 		  or: [newId = affinedId]) ifTrue:
+ 			[self setThreadIdFieldOfProcess: aProcess to: newId << ThreadIdShift + affinedId.
+ 			 ^0].
- 	(self isAffinedThreadId: threadId) ifTrue:
- 		[(ownerIndex = newId
- 		  or: [newId = 0]) ifTrue:
- 			[^0].
  		^PrimErrInappropriate].
  
+ 	ownerIndex > 0 ifTrue:
+ 		[(self startThreadForThreadIndex: ownerIndex) ifFalse:
- 	newThreadIndex > 0 ifTrue:
- 		[(self startThreadForThreadIndex: newThreadIndex) ifFalse:
  			[^PrimErrLimitExceeded]].
  
+ 	self setThreadIdFieldOfProcess: aProcess to: newId << ThreadIdShift.
- 	self setOwnerIndexOfProcess: aProcess to: newId bind: true.
  	^0!

Item was changed:
  ----- Method: CoInterpreterMT>>disownVM: (in category 'vm scheduling') -----
  disownVM: flags
  	"Release the VM to other threads and answer the current thread's index.
  	 Currently valid flags:
  		DisownVMForFFICall			- informs the VM that it is entering an FFI call
  		DisownVMForThreading		- informs the VM that it is entering code during which threading should be permitted
  		OwnVMForeignThreadFlag	- indicates lowest-level entry from a foreign thread
  									- not to be used explicitly by clients
  									- only set by ownVMFromUnidentifiedThread
  		VMAlreadyOwnedHenceDoNotDisown
  									- indicates an ownVM from a callback was made when
  									  the vm was still owned.
  									- not to be used explicitly by clients
  									- only set by ownVMFromUnidentifiedThread
  
  	 This is the entry-point for plugins and primitives that wish to release the VM while
  	 performing some operation that may potentially block, and for callbacks returning
  	 back to some blocking operation.  If this thread does not reclaim the VM before-
  	 hand then when the next heartbeat occurs the thread manager will schedule a
  	 thread to acquire the VM which may start running the VM in place of this thread.
  
  	 N.B. Most of the state needed to resume after preemption is set in preemptDisowningThread."
  	<api>
  	<inline: false>
  	| vmThread result |
+ 	self assert: (flags >= 0 and: [flags < (1 bitShift: DisownFlagsShift)]).
- 	<var: #vmThread type: #'CogVMThread *'>
  	self assert: self successful.
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceDisownVM thing: (objectMemory integerObjectOf: flags) source: 0].
  	processHasThreadId ifFalse:
  		[willNotThreadWarnCount < 10 ifTrue:
  			[self print: 'warning: VM parameter 48 indicates Process doesn''t have threadId; VM will not thread'; cr.
  			 willNotThreadWarnCount := willNotThreadWarnCount + 1]].
  	vmThread := cogThreadManager currentVMThread.
  	(flags anyMask: VMAlreadyOwnedHenceDoNotDisown) ifTrue:
  		[disowningVMThread := vmThread.
  		 vmThread state: CTMUnavailable.
  		 ^0].
  	self assertCStackPointersBelongToCurrentThread.
  	self assertValidNewMethodPropertyFlags.
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		[| proc |
  		 (proc := objectMemory splObj: foreignCallbackProcessSlot) ~= objectMemory nilObject ifTrue:
  			[foreignCallbackPriority := self quickFetchInteger: PriorityIndex ofObject: proc].
  		 relinquishing := true.
  		 self sqLowLevelMFence].
- 	(noThreadingOfGUIThread and: [self inGUIThread]) ifTrue:
- 		[^vmThread index
- 		 + LockGUIThreadFlag
- 		 + (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown])
- 		 + (flags << DisownFlagsShift)].
  	disownCount := disownCount + 1.
  	disowningVMThread := vmThread.
  	"self cr; cr; print: 'disownVM  Csp: '; printHex: vmThread cStackPointer; cr.
  	(0 to: 16 by: 4) do:
  		[:offset|
  		self print: ' *(esp+'; printNum: offset; print: ': '; printHex: (stackPages longAt: cogit processor sp + offset); cr].
  	cogit processor printIntegerRegistersOn: Transcript."
  
  	"OwnVMForeignThreadFlag indicates lowest-level of entry by a foreign
  	 thread. If that's where we are then release the vmThread.  Otherwise
  	 indicate the vmThread is off doing something outside of the VM."
  	(flags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			["I don't think this is quite right.  Josh's use case is creating some foreign thread and then registering
  			 it with the VM. That's not the same as binding a process to a foreign thread given that the foreign
  			 callback process is about to terminate anyway (it is returning from a callback here).  So do we need
  			 an additional concept, that of a vmThread being either of the set known to the VM or floating?"
  			self flag: 'issue with registering foreign threads with the VM'.
  			(self isBoundProcess: self activeProcess) ifFalse:
  				[cogThreadManager unregisterVMThread: vmThread]]
  		ifFalse: [vmThread state: CTMUnavailable].
+ 	result := ((vmThread index bitShift: DisownFlagsShift)
+ 				 bitOr: (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown]))
+ 				 bitOr: flags.
- 	result := vmThread index
- 				+ (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown])
- 				+ (flags << DisownFlagsShift).
  	cogThreadManager releaseVM.
  	^result!

Item was changed:
  ----- Method: CoInterpreterMT>>getImageHeaderFlags (in category 'image save/restore') -----
  getImageHeaderFlags
  	"Answer the flags that are contained in the 7th long of the image header."
  	^fullScreenFlag "0 or 1"
  	+ (VMBIGENDIAN ifTrue: [0] ifFalse: [2]) "this is the imageFloatsLittleEndian flag"
  	+ (processHasThreadId ifTrue: [4] ifFalse: [0])
  	+ (flagInterpretedMethods ifTrue: [8] ifFalse: [0])
  	+ (preemptionYields ifTrue: [0] ifFalse: [16r10])
+ 	"was: noThreadingOfGUIThread ifTrue: [16r20] ifFalse: [0]); a broken idea"
- 	+ (noThreadingOfGUIThread ifTrue: [16r20] ifFalse: [0])
  	+ (newFinalization ifTrue: [16r40] ifFalse: [0])
  	+ (sendWheelEvents ifTrue: [16r80] ifFalse: [0])
  	+ (primitiveDoMixedArithmetic ifTrue: [0] ifFalse: [16r100])
  	+ (imageHeaderFlags bitClear: 16r1FF) "these are any flags we do not recognize"!

Item was removed:
- ----- Method: CoInterpreterMT>>inGUIThread (in category 'vm scheduling') -----
- inGUIThread
- 	"The first thread is assumed to be the GUI thread, the VM thread that expects to receive
- 	 window events, etc.  This might appear to invite race conditions but it is only to be used
- 	 to decide whether to not give up the VM from the GUI thread (see disownVM:)."
- 	self assert: noThreadingOfGUIThread.
- 	^cogThreadManager vmOwnerIs: 1!

Item was changed:
  ----- Method: CoInterpreterMT>>isAffinedProcess: (in category 'process primitive support') -----
  isAffinedProcess: aProcess
+ 	^self isAffinedThreadId: (self threadIdFieldValueOf: aProcess)!
- 	^self isAffinedThreadId: (self ownerIndexOfProcess: aProcess)!

Item was changed:
  ----- Method: CoInterpreterMT>>isAffinedThreadId: (in category 'process primitive support') -----
+ isAffinedThreadId: threadIdField
+ 	"Answer if the threadId has the bits set indicating the thread it is temporarily bound to."
+ 	^(self affinedThreadId: threadIdField) ~= 0!
- isAffinedThreadId: threadId
- 	^(objectMemory isIntegerObject: threadId)
- 	  and: [((objectMemory integerValueOf: threadId) bitAnd: 1) = 0]!

Item was removed:
- ----- Method: CoInterpreterMT>>isUnboundThreadId: (in category 'process primitive support') -----
- isUnboundThreadId: threadId
- 	"Answer if the threadId is neither affined nor bound.  Not the same as bound not."
- 	^threadId = objectMemory nilObject
- 	  or: [((objectMemory integerValueOf: threadId) bitAnd: (ThreadIdMask << 1) + 1) = 0]!

Item was changed:
  ----- Method: CoInterpreterMT>>ownVM: (in category 'vm scheduling') -----
  ownVM: threadIndexAndFlags
  	<api>
  	<inline: false>
  	"This is the entry-point for plugins and primitives that wish to reacquire the VM after having
  	 released it via disownVM or callbacks that want to acquire it without knowing their ownership
  	 status.  This call will block until the VM is owned by the current thread or an error occurs.
  	 The argument should be the value answered by disownVM, or 0 for callbacks that don't know
  	 if they have disowned or not.  This is both an optimization to avoid having to query thread-
  	 local storage for the current thread's index (since it can easily keep it in some local variable),
  	 and a record of when an unbound process becomes affined to a thread for the dynamic
  	 extent of some operation.
  
  	 Answer 0 if the current thread is known to the VM (and on return owns the VM).
  	 Answer 1 if the current thread is unknown to the VM and takes ownership.
  	 Answer -1 if the current thread is unknown to the VM and fails to take ownership."
  	| threadIndex flags vmThread |
  	threadIndexAndFlags = 0 ifTrue:
  		[^self ownVMFromUnidentifiedThread].
  
+ 	threadIndex := threadIndexAndFlags bitShift: DisownFlagsShift negated.
+ 	flags := threadIndexAndFlags bitAnd: (1 bitShift: DisownFlagsShift) - 1.
- 	threadIndex := threadIndexAndFlags bitAnd: ThreadIdMask.
- 	flags := threadIndexAndFlags >> DisownFlagsShift.
  
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		["Presumably we have nothing to do; this primitive is typically called from the
  		  background process. So we should /not/ try and activate any threads in the
  		  pool; they will waste cycles finding there is no runnable process, and will
  		  cause a VM abort if no runnable process is found.  But we /do/ want to allow
  		  FFI calls that have completed, or callbacks a chance to get into the VM; they
  		  do have something to do.  DisownVMForProcessorRelinquish indicates this."
  		 relinquishing := false.
  		 self sqLowLevelMFence].
  
- 	(threadIndexAndFlags anyMask: LockGUIThreadFlag) ifTrue:
- 		[self assert: (noThreadingOfGUIThread and: [self inGUIThread]).
- 		 self assert: disowningVMThread isNil.
- 		 cogit recordEventTrace ifTrue:
- 			[self recordTrace: TraceOwnVM thing: ConstZero source: 0].
- 		 ^0].
- 
  	vmThread := cogThreadManager acquireVMFor: threadIndex.
  	disownCount := disownCount - 1.
  
  	disowningVMThread ifNotNil:
  		[vmThread = disowningVMThread ifTrue:
  			[self assert: (vmThread cFramePointer isNil
  						or: [CFramePointer = vmThread cFramePointer and: [CStackPointer = vmThread cStackPointer]]).
  			 self assert: self successful.
  			 self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  			 disowningVMThread := nil.
  			 cogit recordEventTrace ifTrue:
  				[self recordTrace: TraceOwnVM thing: ConstOne source: 0].
  			 ^0].  "if not preempted we're done."
  		self preemptDisowningThread].
  
  	"We've been preempted; we must restore state and update the threadId
  	 in our process, and may have to put the active process to sleep."
  	self restoreVMStateFor: vmThread threadIndexAndFlags: threadIndexAndFlags.
  
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceOwnVM thing: ConstTwo source: 0].
  	^threadIndexAndFlags bitAnd: OwnVMForeignThreadFlag!

Item was changed:
  ----- Method: CoInterpreterMT>>ownerIndexOfThreadId: (in category 'process primitive support') -----
  ownerIndexOfThreadId: threadId
  	^(objectMemory isIntegerObject: threadId)
+ 		ifTrue: [(objectMemory integerValueOf: threadId) >> ThreadIdShift]
- 		ifTrue: [(objectMemory integerValueOf: threadId) >> 1 bitAnd: ThreadIdMask]
  		ifFalse: [0]!

Item was changed:
  ----- Method: CoInterpreterMT>>primitiveProcessBindToThreadId (in category 'process primitives') -----
  primitiveProcessBindToThreadId
  	"Attempt to bind the receiver to the thread with the id of the argument or nil, where the receiver is a Process.
  	 If successful the VM will ensure that there are at least id many threads active."
+ 	| aProcess id |
- 	| aProcess id ec |
  	<export: true>
  	self cCode: [] inSmalltalk: [cogThreadManager isNil ifTrue: [^self primitiveFail]].
+ 	processHasThreadId ifFalse:
+ 		[^self primitiveFailFor: PrimErrUnsupported].
  	id := self stackTop.
  	aProcess := self stackValue: 1.
  	((id = objectMemory nilObject or: [(objectMemory isIntegerObject: id)
+ 										and: [id ~= (objectMemory integerObjectOf: 0)]])
- 										and: [(objectMemory integerValueOf: id) >= 0]])
  	and: [(objectMemory isPointers: aProcess)
  	and: [(objectMemory slotSizeOf: aProcess) >= (ThreadIdIndex + 1)]]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	id := id = objectMemory nilObject ifTrue: [0] ifFalse: [objectMemory integerValueOf: id].
+ 	id abs >= cogThreadManager maxNumThreads ifTrue:
- 	id >= cogThreadManager maxNumThreads ifTrue:
  		[^self primitiveFailFor: PrimErrLimitExceeded].
+ 	(self bindProcess: aProcess toId: id) ifNotNil:
+ 		[:ec| ^self primitiveFailFor: ec].
+ 	id := self ownerIndexOfProcess: aProcess.
- 	(ec := self bindProcess: aProcess toId: id) ~= 0 ifTrue:
- 		[^self primitiveFailFor: ec].
  	(aProcess = self activeProcess
  	and: [(activeProcessAffined := id ~= 0)
+ 	and: [(cogThreadManager vmOwnerIsCompatibleWith: id) not]]) ifTrue:
- 	and: [(cogThreadManager vmOwnerIs: id) not]]) ifTrue:
  		[(self quickFetchInteger: PriorityIndex ofObject: aProcess) < maxWaitingPriority ifTrue:
  			[maxWaitingPriority = self quickFetchInteger: PriorityIndex ofObject: aProcess].
  		 checkThreadActivation := true.
  		 self forceInterruptCheck].
  	self methodReturnReceiver!

Item was changed:
  ----- Method: CoInterpreterMT>>primitiveProcessBoundThreadId (in category 'process primitives') -----
  primitiveProcessBoundThreadId
+ 	"Answer the receiver's current thread Id or nil, where the receiver is a Process.
+ 	 If the threadId is positive then the receiver is bound to the thread with that id.
+ 	 If the threadId is negative then the receiver is excluded from running on the thread with that id."
- 	"Answer the receiver's current thread Id or nil, where the receiver is a Process."
  	| aProcess id |
  	<export: true>
  	self cCode: [] inSmalltalk: [cogThreadManager isNil ifTrue: [^self primitiveFail]].
+ 	processHasThreadId ifFalse:
+ 		[^self primitiveFailFor: PrimErrUnsupported].
  	aProcess := self stackTop.
  	id := self ownerIndexOfProcess: aProcess.
+ 	self methodReturnValue: (id = 0
+ 								ifTrue: [objectMemory nilObject]
+ 								ifFalse: [objectMemory integerObjectOf: id])!
- 	self pop: argumentCount + 1
- 		thenPush: (id = 0
- 						ifTrue: [objectMemory nilObject]
- 						ifFalse: [objectMemory integerObjectOf: id])!

Item was changed:
  ----- Method: CoInterpreterMT>>setImageHeaderFlags: (in category 'internal interpreter access') -----
  setImageHeaderFlags: flags
  	"Set an array of flags indicating various properties of the saved image, responded to on image load.
  	 These are the same as the image header flags shifted right two bits, omitting the fullScreenFlag and float byte order flag.
  	 Bit 0: if set, implies the image's Process class has threadId as its 3rd inst var (zero relative)
  	 Bit 1: if set, methods that are interpreted will have the flag bit set in their header
  	 Bit 2: if set, implies preempting a process does not put it to the back of its run queue
+ 	 Bit 3: unassigned; used to mean if set, implies a threaded VM will not disown the VM if owned by the GUI thread; a broken idea
- 	 Bit 3: if set, implies a threaded VM will not disown the VM if owned by the GUI thread
  	 Bit 4: if set, implies the new finalization scheme where WeakArrays are queued
  	 Bit 5: if set, implies wheel events will be delivered as such and not mapped to arrow key events
  	 Bit 6: if set, implies arithmetic primitives will fail if given arguments of different types (float vs int)
  	 Bit 7: if set, implies file primitives (FilePlugin, FileAttributesPlugin) will answer file times in UTC not local times"
  	flags asUnsignedInteger > 255 ifTrue:
  		[^self primitiveFailFor: PrimErrUnsupported].
+ 	(flags anyMask: 8) ifTrue:
+ 		[^self primitiveFailFor: PrimErrInappropriate].
  	processHasThreadId := flags anyMask: 1.
  	flagInterpretedMethods := flags anyMask: 2.
  	preemptionYields := flags noMask: 4.
+ 	"was: noThreadingOfGUIThread := flags anyMask: 8. a broken idea"
- 	noThreadingOfGUIThread := flags anyMask: 8.
  	newFinalization := flags anyMask: 16.
  	sendWheelEvents := flags anyMask: 32.
  	primitiveDoMixedArithmetic := flags noMask: 64.
  	imageHeaderFlags := (flags anyMask: 128)
  							ifTrue: [imageHeaderFlags bitOr: 512]
  							ifFalse: [imageHeaderFlags bitClear: 512]!

Item was changed:
  ----- Method: CoInterpreterMT>>setImageHeaderFlagsFrom: (in category 'image save/restore') -----
  setImageHeaderFlagsFrom: headerFlags
  	"Set the flags that are contained in the 7th long of the image header."
  	imageHeaderFlags := headerFlags. "so as to preserve unrecognised flags."
  	fullScreenFlag := headerFlags bitAnd: 1.
  	imageFloatsBigEndian := (headerFlags noMask: 2) ifTrue: [1] ifFalse: [0].
  	processHasThreadId := headerFlags anyMask: 4.
  	flagInterpretedMethods := headerFlags anyMask: 8.
  	preemptionYields := headerFlags noMask: 16.
+ 	"was: noThreadingOfGUIThread := headerFlags anyMask: 32. a broken idea"
- 	noThreadingOfGUIThread := headerFlags anyMask: 32.
  	newFinalization := headerFlags anyMask: 64.
  	sendWheelEvents := headerFlags anyMask: 128.
  	primitiveDoMixedArithmetic := headerFlags noMask: 256.
  
  	processHasThreadId ifFalse:
  		[self print: 'warning, processHasThreadId flag is unset; cannot function as a threaded VM if so.'; cr]!

Item was added:
+ ----- Method: CoInterpreterMT>>setOwnerIndexOfProcess:to: (in category 'process primitive support') -----
+ setOwnerIndexOfProcess: aProcess to: threadIdField
+ 	| threadIdSlot |
+ 	threadIdSlot := threadIdField = 0
+ 					ifTrue: [objectMemory nilObject]
+ 					ifFalse: [objectMemory integerObjectOf: threadIdField].
+ 	objectMemory storePointerUnchecked: ThreadIdIndex ofObject: aProcess withValue: threadIdSlot!

Item was added:
+ ----- Method: CoInterpreterMT>>setThreadIdFieldOfProcess:to: (in category 'process primitive support') -----
+ setThreadIdFieldOfProcess: aProcess to: threadIdField
+ 	| threadIdSlot |
+ 	threadIdSlot := threadIdField = 0
+ 					ifTrue: [objectMemory nilObject]
+ 					ifFalse: [objectMemory integerObjectOf: threadIdField].
+ 	objectMemory storePointerUnchecked: ThreadIdIndex ofObject: aProcess withValue: threadIdSlot!

Item was added:
+ ----- Method: CoInterpreterMT>>threadIdFieldValueOf: (in category 'process primitive support') -----
+ threadIdFieldValueOf: aProcess
+ 	^processHasThreadId
+ 		ifTrue: 
+ 			[| field |
+ 			field := objectMemory fetchPointer: ThreadIdIndex ofObject: aProcess.
+ 			field = objectMemory nilObject
+ 				ifTrue: [0]
+ 				ifFalse: [objectMemory integerValueOf: field]]
+ 		ifFalse: [0]!

Item was changed:
  ----- Method: CogThreadManager>>maxNumThreads (in category 'simulation') -----
  maxNumThreads
+ 	"This could be a VM parameter (within the proscribed limits described below)...
+ 	 It is chosen so that two fields of this width fit in a SmallInteger, to fit the needs of threadId.
+ 	 The sign flag is used to say ``don't run on this thread'', and 32-bit Spur has 2-bit immediate tags,
+ 	 which leaves us 29 bits to play with. 2 raisedTo: (29 // 2) is 16k.  If this ever becomes a serious limit
+ 	 we can use a different value in 64-bits. 64-bit Spur has 3-bit immediate tags, which leaves us 60
+ 	 bits to play with. 2 raisedTo: (60 / 2) is  1g.  Note that the max number is 1 << ThreadIdShift - 1
+ 	 because 0 is not a valid threadId; it means ''the VM is unowned''"
+ 
+ 	^self cCode: [1 << ThreadIdShift - 1] inSmalltalk: [16]!
- 	^self cCode: [ThreadIdMask] inSmalltalk: [16]!

Item was added:
+ ----- Method: CogThreadManager>>threadIndex:isCompatibleWith: (in category 'public api-testing') -----
+ threadIndex: aThreadIndex isCompatibleWith: processThreadId
+ 	"Test if processThreadId is ok to run on a thread with the given index."
+ 	<inline: true>
+ 	^processThreadId >= 0
+ 		ifTrue: [aThreadIndex = (processThreadId >> 1)]
+ 		ifFalse: [aThreadIndex ~= (0 - (processThreadId >> 1))]!

Item was added:
+ ----- Method: CogThreadManager>>vmOwnerIsCompatibleWith: (in category 'public api-testing') -----
+ vmOwnerIsCompatibleWith: processThreadId
+ 	"Test if the vmOwner is index."
+ 	<inline: true>
+ 	self sqLowLevelMFence.
+ 	^self threadIndex: vmOwner isCompatibleWith: processThreadId!

Item was removed:
- ----- Method: CogVMSimulator>>inGUIThread (in category 'multi-threading simulation switch') -----
- inGUIThread
- 	"This method includes or excludes CoInterpreterMT methods as required.
- 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
- 
- 	^self perform: #inGUIThread
- 		withArguments: {}
- 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was removed:
- ----- Method: CogVMSimulator>>isUnboundThreadId: (in category 'multi-threading simulation switch') -----
- isUnboundThreadId: threadId
- 	"This method includes or excludes CoInterpreterMT methods as required.
- 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
- 
- 	^self perform: #isUnboundThreadId:
- 		withArguments: {threadId}
- 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was changed:
  SharedPool subclass: #VMThreadingConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'AWOLProcessesIncrement CTMAssignableOrInVM CTMInitializing CTMUnavailable CTMWantingOwnership ThreadIdIndex ThreadIdShift'
- 	classVariableNames: 'AWOLProcessesIncrement CTMAssignableOrInVM CTMInitializing CTMUnavailable CTMWantingOwnership ThreadIdIndex ThreadIdMask'
  	poolDictionaries: ''
  	category: 'VMMaker-Multithreading'!
  
  !VMThreadingConstants commentStamp: '<historical>' prior: 0!
  VMThreadingConstants ensureClassPool.
  CogThreadManager classPool keys do:
  	[:k| VMThreadingConstants classPool declare: k from: CogThreadManager classPool].
  CoInterpreterMT classPool keys do:
  	[:k| VMThreadingConstants classPool declare: k from: CoInterpreterMT classPool].!



More information about the Vm-dev mailing list