[Vm-dev] VM Maker: VMMaker-dtl.375.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jan 23 23:14:55 UTC 2016


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.375.mcz

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

Name: VMMaker-dtl.375
Author: dtl
Time: 23 January 2016, 6:09:35.618 pm
UUID: e3a6cde6-c09a-403d-a673-571c7abb98cb
Ancestors: VMMaker-dtl.374

VMMaker 4.15.2

Move the critical section primitives and related methods to InterpreterPrimitives from StackInterpreter, and make them work in the context interpreter.. Install as numbered primitives 185, 186, 187.

=============== Diff against VMMaker-dtl.374 ===============

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

Item was removed:
- ----- Method: Interpreter>>addLastLink:toList: (in category 'process primitive support') -----
- addLastLink: proc toList: aList 
- 	"Add the given process to the given linked list and set the 
- 	backpointer of process to its new list."
- 	| lastLink |
- 	(self isEmptyList: aList)
- 		ifTrue: [objectMemory storePointer: FirstLinkIndex ofObject: aList withValue: proc]
- 		ifFalse: [lastLink := objectMemory fetchPointer: LastLinkIndex ofObject: aList.
- 			objectMemory storePointer: NextLinkIndex ofObject: lastLink withValue: proc].
- 	objectMemory storePointer: LastLinkIndex ofObject: aList withValue: proc.
- 	objectMemory storePointer: MyListIndex ofObject: proc withValue: aList!

Item was added:
+ ----- Method: Interpreter>>putToSleep:yieldingIf: (in category 'process primitive support') -----
+ putToSleep: aProcess yieldingIf: yieldImplicitly
+ 	"Save the given process on the scheduler process list for its priority,
+ 	 adding to the back if yieldImplicitly or to the front if not yieldImplicitly."
+ 
+ 	| priority processLists processList |
+ 	priority := self quickFetchInteger: PriorityIndex ofObject: aProcess.
+ 	processLists := objectMemory fetchPointer: ProcessListsIndex ofObject: self schedulerPointer.
+ 	processList := objectMemory fetchPointer: priority - 1 ofObject: processLists.
+ 	yieldImplicitly
+ 		ifTrue: [self addLastLink: aProcess toList: processList]
+ 		ifFalse: [self addFirstLink: aProcess toList: processList]!

Item was removed:
- ----- Method: Interpreter>>schedulerPointer (in category 'process primitive support') -----
- schedulerPointer
- 
- 	^ objectMemory fetchPointer: ValueIndex ofObject: (objectMemory splObj: SchedulerAssociation)!

Item was changed:
  VMClass subclass: #InterpreterPrimitives
+ 	instanceVariableNames: 'objectMemory primFailCode argumentCount interruptKeycode newMethod preemptionYields'
- 	instanceVariableNames: 'objectMemory primFailCode argumentCount interruptKeycode newMethod'
  	classVariableNames: 'CrossedX EndOfRun InterpreterSourceVersion MillisecondClockMask'
  	poolDictionaries: 'VMObjectIndices VMSqueakV3ObjectRepresentationConstants'
  	category: 'VMMaker-Interpreter'!
  
  !InterpreterPrimitives commentStamp: 'dtl 4/14/2013 23:16' 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 various interpreters.
  
  Instance Variables
  	argumentCount:	<Integer>
  	messageSelector:	<Integer>
  	newMethod:		<Integer>
  	nextProfileTick:		<Integer>
  	objectMemory:		<ObjectMemory> (simulation only)
  	preemptionYields:	<Boolean>
  	primFailCode:		<Integer>
  	profileMethod:		<Integer>
  	profileProcess:		<Integer>
  	profileSemaphore:	<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
  	- primtiive success/failure flag, 0 for success, otherwise the reason code for failure
  
  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
  !

Item was added:
+ ----- Method: InterpreterPrimitives>>activeProcess (in category 'process primitive support') -----
+ activeProcess
+ 	"Answer the current activeProcess."
+ 	<api> "useful for VM debugging"
+ 	^objectMemory fetchPointer: ActiveProcessIndex ofObject: self schedulerPointer!

Item was added:
+ ----- Method: InterpreterPrimitives>>addFirstLink:toList: (in category 'process primitive support') -----
+ addFirstLink: proc toList: aList 
+ 	"Add the given process to the front of the given linked list
+ 	 and set the backpointer of process to its new list."
+ 	| firstLink |
+ 	self assert: (objectMemory fetchPointer: NextLinkIndex ofObject: proc) = objectMemory nilObject.
+ 	firstLink := objectMemory fetchPointer: FirstLinkIndex ofObject: aList.
+ 	self assert: firstLink ~= proc.
+ 	objectMemory storePointer: FirstLinkIndex ofObject: aList withValue: proc.
+ 	firstLink = objectMemory nilObject "a.k.a. (self isEmptyList: aList)"
+ 		ifTrue: [objectMemory storePointer: LastLinkIndex ofObject: aList withValue: proc]
+ 		ifFalse: [objectMemory storePointer: NextLinkIndex ofObject: proc withValue: firstLink].
+ 	objectMemory storePointer: MyListIndex ofObject: proc withValue: aList!

Item was added:
+ ----- Method: InterpreterPrimitives>>addLastLink:toList: (in category 'process primitive support') -----
+ addLastLink: proc toList: aList 
+ 	"Add the given process to the end of the given linked list
+ 	 and set the backpointer of process to its new list."
+ 	| lastLink |
+ 	self assert: (objectMemory fetchPointer: NextLinkIndex ofObject: proc) = objectMemory nilObject.
+ 	(self isEmptyList: aList)
+ 		ifTrue: [objectMemory storePointer: FirstLinkIndex ofObject: aList withValue: proc]
+ 		ifFalse:
+ 			[lastLink := objectMemory fetchPointer: LastLinkIndex ofObject: aList.
+ 			 self assert: lastLink ~= proc.
+ 			 objectMemory storePointer: NextLinkIndex ofObject: lastLink withValue: proc].
+ 	objectMemory storePointer: LastLinkIndex ofObject: aList withValue: proc.
+ 	objectMemory storePointer: MyListIndex ofObject: proc withValue: aList!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveEnterCriticalSection (in category 'process primitives') -----
+ primitiveEnterCriticalSection
+ 	"Attempt to enter a CriticalSection/Mutex.  If not owned, set the owner to the current
+ 	 process and answer false. If owned by the current process  answer true.   Otherwise
+ 	 suspend the process.  Answer if the receiver is owned by the current process.
+ 	 For simulation if there is an argument it is taken to be the effective activeProcess
+ 	 (see Process>>effectiveProcess)."
+ 	| criticalSection owningProcessIndex owningProcess activeProc |
+ 	argumentCount > 0
+ 		ifTrue:
+ 			[criticalSection := self stackValue: 1.  "rcvr"
+ 			 activeProc := self stackTop]
+ 		ifFalse:
+ 			[criticalSection := self stackTop.  "rcvr"
+ 			 activeProc := self activeProcess].
+ 	owningProcessIndex := ExcessSignalsIndex. "CriticalSections are laid out like Semaphores"
+ 	owningProcess := objectMemory fetchPointer: owningProcessIndex ofObject: criticalSection.
+ 	owningProcess = objectMemory nilObject ifTrue:
+ 		[objectMemory storePointer: owningProcessIndex
+ 			ofObject: criticalSection
+ 			withValue: activeProc.
+ 		 ^self pop: argumentCount + 1 thenPush: objectMemory falseObject].
+ 	owningProcess = activeProc ifTrue:
+ 		[^self pop: argumentCount + 1 thenPush: objectMemory trueObject].
+ 	"Arrange to answer false (unowned) when the process is resumed."
+ 	self pop: argumentCount + 1 thenPush: objectMemory falseObject.
+ 	self addLastLink: activeProc toList: criticalSection.
+ 	self transferTo: self wakeHighestPriority!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveExitCriticalSection (in category 'process primitives') -----
+ primitiveExitCriticalSection
+ 	"Exit the critical section.
+ 	 This may change the active process as a result."
+ 	| criticalSection owningProcessIndex owningProcess |
+ 	criticalSection := self stackTop.  "rcvr"
+ 	owningProcessIndex := ExcessSignalsIndex. "CriticalSections are laid out like Semaphores"
+ 	(self isEmptyList: criticalSection)
+ 		ifTrue:
+ 			[objectMemory storePointerUnchecked: owningProcessIndex
+ 				ofObject: criticalSection
+ 				withValue: objectMemory nilObject]
+ 		ifFalse:
+ 			[owningProcess := self removeFirstLinkOfList: criticalSection.
+ 			 "store check unnecessary because criticalSection referred to owningProcess
+ 			  via its FirstLinkIndex slot before owningProcess was removed."
+ 			 objectMemory storePointerUnchecked: owningProcessIndex
+ 				ofObject: criticalSection
+ 				withValue: owningProcess.
+ 			 "Note that resume: isn't fair; it won't suspend the active process.
+ 			  For fairness we must do the equivalent of a primitiveYield, but that
+ 			  may break old code, so we stick with unfair resume:."
+ 			self resume: owningProcess preemptedYieldingIf: preemptionYields]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveTestAndSetOwnershipOfCriticalSection (in category 'process primitives') -----
+ primitiveTestAndSetOwnershipOfCriticalSection
+ 	"Attempt to test-and-set the ownership of the critical section.  If not owned,
+ 	 set the owner to the current process and answer false. If owned by the
+ 	 current process answer true.  If owned by some other process answer nil.
+ 	 For simulation if there is an argument it is taken to be the effective activeProcess
+ 	 (see Process>>effectiveProcess)."
+ 	| criticalSection owningProcessIndex owningProcess activeProc |
+ 	argumentCount > 0
+ 		ifTrue:
+ 			[criticalSection := self stackValue: 1.  "rcvr"
+ 			 activeProc := self stackTop]
+ 		ifFalse:
+ 			[criticalSection := self stackTop.  "rcvr"
+ 			 activeProc := self activeProcess].
+ 	owningProcessIndex := ExcessSignalsIndex. "CriticalSections are laid out like Semaphores"
+ 	owningProcess := objectMemory fetchPointer: owningProcessIndex ofObject: criticalSection.
+ 	owningProcess = objectMemory nilObject ifTrue:
+ 		[objectMemory storePointer: owningProcessIndex
+ 			ofObject: criticalSection
+ 			withValue: activeProc.
+ 		 ^self pop: argumentCount + 1 thenPush: objectMemory falseObject].
+ 	owningProcess = activeProc ifTrue:
+ 		[^self pop: argumentCount + 1 thenPush: objectMemory trueObject].
+ 	self pop: argumentCount + 1 thenPush: objectMemory nilObject!

Item was added:
+ ----- Method: InterpreterPrimitives>>putToSleep:yieldingIf: (in category 'process primitive support') -----
+ putToSleep: aProcess yieldingIf: yieldImplicitly
+ 	"Save the given process on the scheduler process list for its priority,
+ 	 adding to the back if yieldImplicitly or to the front if not yieldImplicitly."
+ 
+ 	self subclassResponsibility
+ !

Item was added:
+ ----- Method: InterpreterPrimitives>>resume:preemptedYieldingIf: (in category 'process primitive support') -----
+ resume: aProcess preemptedYieldingIf: yieldImplicitly
+ 	"Make aProcess runnable and if its priority is higher than  that of the
+ 	 current process, preempt the current process.   Answer if the current
+ 	 process was preempted.  If the current process was preempted then if
+ 	 yieldImplicitly add the current process to the back of its run queue,
+ 	 causing an implicit yiled to other processes on the run queue,  otherwise
+ 	 add the current process to the front of its run queue, hence not yielding.
+ 	 Blue book behaviour is to yield implicitly but is arguably incorrect."
+ 	| activeProc activePriority newPriority |
+ 	<inline: false>
+ 	activeProc := self activeProcess.
+ 	activePriority := self quickFetchInteger: PriorityIndex ofObject: activeProc.
+ 	newPriority := self quickFetchInteger: PriorityIndex ofObject: aProcess.
+ 	newPriority <= activePriority ifTrue:
+ 		[self putToSleep: aProcess yieldingIf: true.
+ 		 ^false].
+ 	self putToSleep: activeProc yieldingIf: yieldImplicitly.
+ 	self transferTo: aProcess.
+ 	^true!

Item was added:
+ ----- Method: InterpreterPrimitives>>schedulerPointer (in category 'process primitive support') -----
+ schedulerPointer
+ 
+ 	^ objectMemory fetchPointer: ValueIndex ofObject: (objectMemory splObj: SchedulerAssociation)!

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
+ 	instanceVariableNames: 'currentBytecode localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue primitiveFunctionPointer methodCache atCache lkupClass highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptPending savedWindowSize imageHeaderFlags fullScreenFlag deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassSizeBytes interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered tempOop statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents theUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite statPendingFinalizationSignals classByteArrayCompactIndex messageSelector profileProcess nextProfileTick profileMethod profileSemaphore'
- 	instanceVariableNames: 'currentBytecode localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue primitiveFunctionPointer methodCache atCache lkupClass highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptPending savedWindowSize imageHeaderFlags fullScreenFlag deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassSizeBytes interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered tempOop statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents theUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite statPendingFinalizationSignals classByteArrayCompactIndex messageSelector preemptionYields profileProcess nextProfileTick profileMethod profileSemaphore'
  	classVariableNames: 'AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeTable BytesPerWord COGMTVM COGVM CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex FailImbalancedPrimitives HeaderFlagBitPosition IMMUTABILITY MULTIPLEBYTECODESETS MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MixinIndex NewspeakVM PrimitiveExternalCallIndex PrimitiveTable STACKVM VMBIGENDIAN'
  	poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSqueakV3BytecodeConstants VMSqueakV3ObjectRepresentationConstants VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !StackInterpreter commentStamp: '<historical>' prior: 0!
  This class is a complete implementation of the Smalltalk-80 virtual machine, derived originally from the Blue Book specification but quite different in some areas.  This VM supports Closures but *not* old-style BlockContexts.
  
  It has been modernized with 32-bit pointers, better management of Contexts (see next item), and attention to variable use that allows the CCodeGenerator (qv) to keep, eg, the instruction pointer and stack pointer in registers as well as keeping most simple variables in a global array that seems to improve performance for most platforms.
  
  The VM does not use Contexts directly.  Instead Contexts serve as proxies for a more conventional stack format that is invisible to the image.  There is considerable explanation at http://www.mirandabanda.org/cogblog/2009/01/14/under-cover-contexts-and-the-big-frame-up.  The VM maintains a fixed-size stack zone divided into pages, each page being capable of holding several method/block activations.  A send establishes a new frame in the current stack page, a return returns to the previous frame.  This eliminates allocation/deallocation of contexts and the moving of receiver and arguments from caller to callee on each send/return.  Contexts are created lazily when an activation needs a context (creating a block, explicit use of thisContext, access to sender when sender is a frame, or linking of stack pages together).  Contexts are either conventional and heap-resident ("single") or "married" and serve as proxies for their corresponding frame or "widowed", meaning that their spouse frame has been returned from (died).  A married context is specially marked (more details in the code) and refers to its frame.  Likewise a married frame is specially marked and refers to its context.
  
  In addition to SmallInteger arithmetic and Floats, the VM supports logic on 32-bit PositiveLargeIntegers, thus allowing it to simulate itself much more effectively than would otherwise be the case.
  
  NOTE:  Here follows a list of things to be borne in mind when working on this code, or when making changes for the future.
  
  1.  There are a number of things that should be done the next time we plan to release a completely incompatible image format.  These include unifying the instanceSize field of the class format word -- see instantiateClass:indexableSize:, and unifying the bits of the method primitive index (if we decide we need more than 512, after all) -- see primitiveIndexOf:.  Also, contexts should be given a special format code (see next item).
  
  2.  There are several fast checks for contexts (see isContextHeader: and isMethodContextHeader:) which will fail if the compact class indices of BlockContext or MethodContext change.  This is necessary because the oops may change during a compaction when the oops are being adjusted.  It's important to be aware of this when writing a new image using the SystemTracer.  A better solution would be to reserve one of the format codes for Contexts only.
  
  3.  We have made normal files tolerant to size and positions up to 32 bits.  This has not been done for async files, since they are still experimental.  The code in size, at: and at:put: should work with sizes and indices up to 31 bits, although I have not tested it (di 12/98); it might or might not work with 32-bit sizes.
  
  4.  Note that 0 is used in a couple of places as an impossible oop.  This should be changed to a constant that really is impossible (or perhaps there is code somewhere that guarantees it --if so it should be put in this comment).  The places include the method cache and the at cache.
  
  5. Moving to a 2 bit immediate tag and having immediate Characters is a good choice for Unicode and the JIT
  
  6.  If Eliot Miranda's 2 word header scheme is acceptable in terms of footprint (we estimate about a 10% increase in image size with about 35 reclaimed by better representation of CompiledMethod - loss of MethodProperties) then the in-line cache for the JIT is simplified, class access is faster and header access is the same in 32-bit and full 64-bit images.!

Item was removed:
- ----- Method: StackInterpreter>>activeProcess (in category 'process primitive support') -----
- activeProcess
- 	"Answer the current activeProcess."
- 	<api> "useful for VM debugging"
- 	^objectMemory fetchPointer: ActiveProcessIndex ofObject: self schedulerPointer!

Item was removed:
- ----- Method: StackInterpreter>>addFirstLink:toList: (in category 'process primitive support') -----
- addFirstLink: proc toList: aList 
- 	"Add the given process to the front of the given linked list
- 	 and set the backpointer of process to its new list."
- 	| firstLink |
- 	self assert: (objectMemory fetchPointer: NextLinkIndex ofObject: proc) = objectMemory nilObject.
- 	firstLink := objectMemory fetchPointer: FirstLinkIndex ofObject: aList.
- 	self assert: firstLink ~= proc.
- 	objectMemory storePointer: FirstLinkIndex ofObject: aList withValue: proc.
- 	firstLink = objectMemory nilObject "a.k.a. (self isEmptyList: aList)"
- 		ifTrue: [objectMemory storePointer: LastLinkIndex ofObject: aList withValue: proc]
- 		ifFalse: [objectMemory storePointer: NextLinkIndex ofObject: proc withValue: firstLink].
- 	objectMemory storePointer: MyListIndex ofObject: proc withValue: aList!

Item was removed:
- ----- Method: StackInterpreter>>addLastLink:toList: (in category 'process primitive support') -----
- addLastLink: proc toList: aList 
- 	"Add the given process to the end of the given linked list
- 	 and set the backpointer of process to its new list."
- 	| lastLink |
- 	self assert: (objectMemory fetchPointer: NextLinkIndex ofObject: proc) = objectMemory nilObject.
- 	(self isEmptyList: aList)
- 		ifTrue: [objectMemory storePointer: FirstLinkIndex ofObject: aList withValue: proc]
- 		ifFalse:
- 			[lastLink := objectMemory fetchPointer: LastLinkIndex ofObject: aList.
- 			 self assert: lastLink ~= proc.
- 			 objectMemory storePointer: NextLinkIndex ofObject: lastLink withValue: proc].
- 	objectMemory storePointer: LastLinkIndex ofObject: aList withValue: proc.
- 	objectMemory storePointer: MyListIndex ofObject: proc withValue: aList!

Item was removed:
- ----- Method: StackInterpreter>>resume:preemptedYieldingIf: (in category 'process primitive support') -----
- resume: aProcess preemptedYieldingIf: yieldImplicitly
- 	"Make aProcess runnable and if its priority is higher than  that of the
- 	 current process, preempt the current process.   Answer if the current
- 	 process was preempted.  If the current process was preempted then if
- 	 yieldImplicitly add the current process to the back of its run queue,
- 	 causing an implicit yiled to other processes on the run queue,  otherwise
- 	 add the current process to the front of its run queue, hence not yielding.
- 	 Blue book behaviour is to yield implicitly but is arguably incorrect."
- 	| activeProc activePriority newPriority |
- 	<inline: false>
- 	activeProc := self activeProcess.
- 	activePriority := self quickFetchInteger: PriorityIndex ofObject: activeProc.
- 	newPriority := self quickFetchInteger: PriorityIndex ofObject: aProcess.
- 	newPriority <= activePriority ifTrue:
- 		[self putToSleep: aProcess yieldingIf: true.
- 		 ^false].
- 	self putToSleep: activeProc yieldingIf: yieldImplicitly.
- 	self transferTo: aProcess.
- 	^true!

Item was removed:
- ----- Method: StackInterpreter>>schedulerPointer (in category 'process primitive support') -----
- schedulerPointer
- 
- 	^ objectMemory fetchPointer: ValueIndex ofObject: (objectMemory splObj: SchedulerAssociation)!

Item was removed:
- ----- Method: StackInterpreterPrimitives>>primitiveEnterCriticalSection (in category 'process primitives') -----
- primitiveEnterCriticalSection
- 	"Attempt to enter a CriticalSection/Mutex.  If not owned, set the owner to the current
- 	 process and answer false. If owned by the current process  answer true.   Otherwise
- 	 suspend the process.  Answer if the receiver is owned by the current process.
- 	 For simulation if there is an argument it is taken to be the effective activeProcess
- 	 (see Process>>effectiveProcess)."
- 	| criticalSection owningProcessIndex owningProcess activeProc |
- 	argumentCount > 0
- 		ifTrue:
- 			[criticalSection := self stackValue: 1.  "rcvr"
- 			 activeProc := self stackTop]
- 		ifFalse:
- 			[criticalSection := self stackTop.  "rcvr"
- 			 activeProc := self activeProcess].
- 	owningProcessIndex := ExcessSignalsIndex. "CriticalSections are laid out like Semaphores"
- 	owningProcess := objectMemory fetchPointer: owningProcessIndex ofObject: criticalSection.
- 	owningProcess = objectMemory nilObject ifTrue:
- 		[objectMemory storePointer: owningProcessIndex
- 			ofObject: criticalSection
- 			withValue: activeProc.
- 		 ^self pop: argumentCount + 1 thenPush: objectMemory falseObject].
- 	owningProcess = activeProc ifTrue:
- 		[^self pop: argumentCount + 1 thenPush: objectMemory trueObject].
- 	"Arrange to answer false (unowned) when the process is resumed."
- 	self pop: argumentCount + 1 thenPush: objectMemory falseObject.
- 	self addLastLink: activeProc toList: criticalSection.
- 	self transferTo: self wakeHighestPriority!

Item was removed:
- ----- Method: StackInterpreterPrimitives>>primitiveExitCriticalSection (in category 'process primitives') -----
- primitiveExitCriticalSection
- 	"Exit the critical section.
- 	 This may change the active process as a result."
- 	| criticalSection owningProcessIndex owningProcess |
- 	criticalSection := self stackTop.  "rcvr"
- 	owningProcessIndex := ExcessSignalsIndex. "CriticalSections are laid out like Semaphores"
- 	(self isEmptyList: criticalSection)
- 		ifTrue:
- 			[objectMemory storePointerUnchecked: owningProcessIndex
- 				ofObject: criticalSection
- 				withValue: objectMemory nilObject]
- 		ifFalse:
- 			[owningProcess := self removeFirstLinkOfList: criticalSection.
- 			 "store check unnecessary because criticalSection referred to owningProcess
- 			  via its FirstLinkIndex slot before owningProcess was removed."
- 			 objectMemory storePointerUnchecked: owningProcessIndex
- 				ofObject: criticalSection
- 				withValue: owningProcess.
- 			 "Note that resume: isn't fair; it won't suspend the active process.
- 			  For fairness we must do the equivalent of a primitiveYield, but that
- 			  may break old code, so we stick with unfair resume:."
- 			self resume: owningProcess preemptedYieldingIf: preemptionYields]!

Item was removed:
- ----- Method: StackInterpreterPrimitives>>primitiveTestAndSetOwnershipOfCriticalSection (in category 'process primitives') -----
- primitiveTestAndSetOwnershipOfCriticalSection
- 	"Attempt to test-and-set the ownership of the critical section.  If not owned,
- 	 set the owner to the current process and answer false. If owned by the
- 	 current process answer true.  If owned by some other process answer nil.
- 	 For simulation if there is an argument it is taken to be the effective activeProcess
- 	 (see Process>>effectiveProcess)."
- 	| criticalSection owningProcessIndex owningProcess activeProc |
- 	argumentCount > 0
- 		ifTrue:
- 			[criticalSection := self stackValue: 1.  "rcvr"
- 			 activeProc := self stackTop]
- 		ifFalse:
- 			[criticalSection := self stackTop.  "rcvr"
- 			 activeProc := self activeProcess].
- 	owningProcessIndex := ExcessSignalsIndex. "CriticalSections are laid out like Semaphores"
- 	owningProcess := objectMemory fetchPointer: owningProcessIndex ofObject: criticalSection.
- 	owningProcess = objectMemory nilObject ifTrue:
- 		[objectMemory storePointer: owningProcessIndex
- 			ofObject: criticalSection
- 			withValue: activeProc.
- 		 ^self pop: argumentCount + 1 thenPush: objectMemory falseObject].
- 	owningProcess = activeProc ifTrue:
- 		[^self pop: argumentCount + 1 thenPush: objectMemory trueObject].
- 	self pop: argumentCount + 1 thenPush: objectMemory nilObject!

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
  
  	"VMMaker versionString"
  
+ 	^'4.15.2'!
- 	^'4.15.1'!



More information about the Vm-dev mailing list