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

commits at source.squeak.org commits at source.squeak.org
Thu Jul 18 19:10:00 UTC 2013


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

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

Name: VMMaker.oscog-eem.306
Author: eem
Time: 18 July 2013, 12:07:47.208 pm
UUID: ef4dab92-e348-4081-8041-92ae24d73bea
Ancestors: VMMaker.oscog-eem.305

Add an assertValidExecutionPointers to the front side of process
switch.

Restore the simulator after adding the MaxStackAllocBytes limit
check to allocateOpcodes:bytecodes:ifFail: by adding size
approximations for CogAbstractInstruction et al.

Make cppIf:ifTrue:[ifFalse:] accept a symbol, thereby restoring the
simulator after Tim's ENABLE_FAST_BLT changes.

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

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.
  	 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 myProc activeProc sched |
  	<var: #vmThread type: #'CogVMThread *'>
  	threadIndexAndFlags = 0 ifTrue:
  		[^self ownVMFromUnidentifiedThread].
  	threadIndex := threadIndexAndFlags bitAnd: ThreadIdMask.
  	flags := threadIndexAndFlags >> DisownFlagsShift.
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		[relinquishing := false.
  		 self sqLowLevelMFence].
  	(threadIndexAndFlags anyMask: LockGUIThreadFlag) ifTrue:
  		[self assert: (noThreadingOfGUIThread and: [self inGUIThread]).
  		 self assert: disowningVMThread = nil.
  		 (flags anyMask: DisownVMLockOutFullGC) ifTrue:
  			[objectMemory decrementFullGCLock].
  		 cogit recordEventTrace ifTrue:
  			[self recordTrace: TraceOwnVM thing: ConstZero source: 0].
  		 ^0].
  
  	vmThread := cogThreadManager acquireVMFor: threadIndex.
  	disownCount := disownCount - 1.
  
  	(flags anyMask: DisownVMLockOutFullGC) ifTrue:
  		[objectMemory decrementFullGCLock].
  	disowningVMThread notNil ifTrue:
  		[vmThread = disowningVMThread ifTrue:
  			[self cCode: ''
  				inSmalltalk:
  					[| range |
  					 range := self cStackRangeForThreadIndex: threadIndex.
  					 self assert: (range includes: cogit getCStackPointer).
  					 self assert: (range includes: cogit getCFramePointer)].
  			 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."
  	activeProc := self activeProcess.
  	(threadIndexAndFlags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			[self assert: foreignCallbackProcessSlot == ForeignCallbackProcess.
  			 myProc := objectMemory splObj: foreignCallbackProcessSlot.
  			self assert: myProc ~= objectMemory nilObject.
  			objectMemory splObj: foreignCallbackProcessSlot put: objectMemory nilObject]
  		ifFalse: [myProc := cogThreadManager popAWOLProcess: vmThread].
  	self assert: activeProc ~= myProc.
  	(activeProc ~= objectMemory nilObject
  	 and: [(objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject]) ifTrue:
  		[self putToSleep: activeProc yieldingIf: preemptionYields].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: myProc) = (objectMemory splObj: ProcessInExternalCodeTag).
  	sched := self schedulerPointer.
  	objectMemory
  		storePointer: ActiveProcessIndex ofObject: sched withValue: myProc;
  		storePointerUnchecked: MyListIndex ofObject: myProc withValue: objectMemory nilObject.
  	"Only unaffine if the process was affined at this level and did not become bound in the interim."
  	((threadIndexAndFlags anyMask: ProcessUnaffinedOnDisown)
  	 and: [(self isBoundProcess: myProc) not]) ifTrue:
  		[self setOwnerIndexOfProcess: myProc to: 0 bind: false].
  	self initPrimCall.
  	self externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc.
  	"If this primitive is called from machine code maintain the invariant that the return pc
  	 of an interpreter callee calling a machine code caller is ceReturnToInterpreterPC."
- 	instructionPointer := self popStack.
  	(vmThread inMachineCode
  	 and: [instructionPointer >= objectMemory startOfMemory]) ifTrue:
  		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	newMethod := vmThread newMethodOrNull.
  	argumentCount := vmThread argumentCount.
  	self cCode:
  			[self mem: reenterInterpreter
  				cp: vmThread reenterInterpreter
  				y: (self sizeof: #'jmp_buf')]
  		inSmalltalk:
  			[reenterInterpreter := vmThread reenterInterpreter].
  	vmThread newMethodOrNull: nil.
  	self cCode: ''
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: threadIndex.
  			 self assert: (range includes: vmThread cStackPointer).
  			 self assert: (range includes: vmThread cFramePointer)].
  	cogit setCStackPointer: vmThread cStackPointer.
  	cogit setCFramePointer: vmThread cFramePointer.
  	self assert: newMethod ~~ nil..
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceOwnVM thing: ConstTwo source: 0].
  	^threadIndexAndFlags bitAnd: OwnVMForeignThreadFlag!

Item was changed:
  ----- Method: CoInterpreterMT>>transferTo:from: (in category 'process primitive support') -----
  transferTo: newProc from: sourceCode
  	"Record a process to be awoken on the next interpreter cycle.  Override to
  	 potentially switch threads either if the new process is bound to another thread,
  	 or if there is no runnable process but there is a waiting thread. Note that the
  	 abort on no runnable process has beeen moved here from wakeHighestPriority."
  	| sched oldProc activeContext vmThread |
  	<inline: false>
  	<var: #vmThread type: #'CogVMThread *'>
  	statProcessSwitch := statProcessSwitch + 1.
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
  	sched := self schedulerPointer.
  	oldProc := objectMemory fetchPointer: ActiveProcessIndex ofObject: sched.
  	self recordContextSwitchFrom: oldProc in: sourceCode.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	objectMemory storePointer: SuspendedContextIndex ofObject: oldProc withValue: activeContext.
  
  	newProc isNil ifTrue:
  		["Two possibilities.  One, there is at least one thread waiting to own the VM in which
  		  case it should be activated.  Two, there are no processes to run and so abort."
  		 vmThread := self willingVMThread.
  		 (vmThread notNil and: [vmThread state = CTMWantingOwnership]) ifTrue:
  			[self returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: sourceCode].
  		self error: 'scheduler could not find a runnable process'].
  
  	objectMemory storePointer: ActiveProcessIndex ofObject: sched withValue: newProc.
  	objectMemory storePointerUnchecked: MyListIndex ofObject: newProc withValue: objectMemory nilObject.
  
  	self threadSwitchIfNecessary: newProc from: sourceCode.
  
+ 	self externalSetStackPageAndPointersForSuspendedContextOfProcess: newProc!
- 	self externalSetStackPageAndPointersForSuspendedContextOfProcess: newProc.
- 	instructionPointer := self popStack!

Item was changed:
  ----- Method: CoInterpreterMT>>tryToExecuteSmalltalk: (in category 'vm scheduling') -----
  tryToExecuteSmalltalk: vmThread
  	"Attempt to run the current process, if it exists, on the given vmThread."
  	<var: #vmThread type: #'CogVMThread *'>
  	| dvmt activeProc ownerIndex |
  	<var: #dvmt type: #'CogVMThread *'>
  	self assert: cogThreadManager getVMOwner = vmThread index.
  	self assert: cogThreadManager ioGetThreadLocalThreadIndex = vmThread index.
  	dvmt := disowningVMThread.
  	disowningVMThread
  		ifNil: [activeProc := self activeProcess]
  		ifNotNil:
  			[self preemptDisowningThread.
  			 activeProc := self wakeHighestPriority.
  			 activeProc
  				ifNil: [activeProc := objectMemory nilObject]
  				ifNotNil: [objectMemory
  							storePointerUnchecked: MyListIndex
  							ofObject: activeProc
  							withValue: objectMemory nilObject].
  			 objectMemory
  				storePointer: ActiveProcessIndex
  				ofObject: self schedulerPointer
  				withValue: activeProc].
  	activeProc = objectMemory nilObject ifTrue:
  		[cogThreadManager releaseVM.
  		 ^nil].
  	ownerIndex := self ownerIndexOfProcess: activeProc.
  	(ownerIndex = 0
  	 or: [ownerIndex ~= 0 and: [ownerIndex = cogThreadManager getVMOwner]])
  		ifTrue:
  			[self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  			 (objectMemory fetchPointer: SuspendedContextIndex ofObject: activeProc) ~= objectMemory nilObject ifTrue:
+ 				[self externalSetStackPageAndPointersForSuspendedContextOfProcess: activeProc].
- 				[self externalSetStackPageAndPointersForSuspendedContextOfProcess: activeProc.
- 				 instructionPointer := self popStack].
  			 self enterSmalltalkExecutive.
  			 "When we return here we should have already given up
  			  the VM and so we cannot touch any interpreter state."]
  		ifFalse:
  			[cogThreadManager wakeVMThreadFor: ownerIndex]!

Item was added:
+ ----- Method: CogAbstractInstruction class>>byteSizeForSimulator: (in category 'simulation only') -----
+ byteSizeForSimulator: aVMClass
+ 	"Answer an approximation of the byte size of an AbstractInstruction struct.
+ 	 This is for estimating the alloca in allocateOpcodes:bytecodes:ifFail:"
+ 	| concreteClass ptrsize |
+ 	concreteClass := aVMClass processor abstractInstructionCompilerClass.
+ 	ptrsize := aVMClass sizeof: #'void *'.
+ 	^concreteClass instSize - 4 "cogit, objectMemory et al" * ptrsize
+ 	+ concreteClass basicNew machineCodeBytes
+ 		roundTo: ptrsize!

Item was added:
+ ----- Method: CogBytecodeFixup class>>byteSizeForSimulator: (in category 'simulation only') -----
+ byteSizeForSimulator: aVMClass
+ 	"Answer an approximation of the byte size of an AbstractInstruction struct.
+ 	 This is for estimating the alloca in allocateOpcodes:bytecodes:ifFail:"
+ 	^self instSize * (aVMClass sizeof: #'void *')!

Item was added:
+ ----- Method: CogInstructionAnnotation class>>byteSizeForSimulator: (in category 'simulation only') -----
+ byteSizeForSimulator: aVMClass
+ 	"Answer an approximation of the byte size of an AbstractInstruction struct.
+ 	 This is for estimating the alloca in allocateOpcodes:bytecodes:ifFail:"
+ 	^self instSize * (aVMClass sizeof: #'void *')!

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

Item was changed:
  ----- Method: Cogit>>allocateOpcodes:bytecodes:ifFail: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes ifFail: failBlock
  	"Allocate the various arrays needed to compile abstract instructions.
  	 This needs to be a macro since the arrays are alloca'ed (stack allocated)
  	 to ensure their being freed when compilation is done.
  	 Notionally we only need as many fixups as there are bytecodes.  But we
  	 reuse fixups to record pc-dependent instructions in generateInstructionsAt:
  	 and so need at least as many as there are abstract opcodes.
  
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
  	<cmacro: '(numberOfAbstractOpcodes,numberOfBytecodes,failBlock) do { \
  		int opcodeSize = sizeof(AbstractInstruction) * (numAbstractOpcodes = (numberOfAbstractOpcodes)); \
  		int fixupSize = sizeof(BytecodeFixup) * numAbstractOpcodes; \
  		int annotationSize = sizeof(InstructionAnnotation) * ((numAbstractOpcodes + 3) / 4); \
  		int allocSize = opcodeSize + fixupSize + annotationSize; \
  		if (allocSize > MaxStackAllocSize) failBlock; \
  		abstractOpcodes = alloca(allocSize); \
  		bzero(abstractOpcodes, opcodeSize + fixupSize); \
  		fixups = (void *)((char *)abstractOpcodes + opcodeSize); \
  		annotations = (void *)((char *)fixups + fixupSize); \
  		opcodeIndex = labelCounter = annotationIndex = 0; \
  } while (0)'>
  	| opcodeSize fixupSize annotationSize allocSize |
+ 	opcodeSize := (self sizeof: CogAbstractInstruction) * numberOfAbstractOpcodes.
+ 	fixupSize := (self sizeof: CogBytecodeFixup) * numberOfAbstractOpcodes.
+ 	annotationSize := (self sizeof: CogInstructionAnnotation) * ((numberOfAbstractOpcodes + 3) / 4).
- 	opcodeSize := (self sizeof: #AbstractInstruction) * numberOfAbstractOpcodes.
- 	fixupSize := (self sizeof: #BytecodeFixup) * numberOfAbstractOpcodes.
- 	annotationSize := (self sizeof: #InstructionAnnotation) * ((numberOfAbstractOpcodes + 3) / 4).
  	allocSize := opcodeSize + fixupSize + annotationSize.
  	allocSize > MaxStackAllocSize ifTrue: [^failBlock value].
  	numAbstractOpcodes := numberOfAbstractOpcodes.
  	abstractOpcodes := CArrayAccessor on:
  						((1 to: numAbstractOpcodes) collect:
  							[:ign| processor abstractInstructionCompilerClass for: self]).
  	fixups := CArrayAccessor on:
  						((1 to: numAbstractOpcodes) collect:
  							[:ign| self bytecodeFixupClass new]).
  	annotations := CArrayAccessor on:
  						((1 to: numAbstractOpcodes + 3 // 4) collect:
  							[:ign| CogInstructionAnnotation new]).
  	opcodeIndex := labelCounter := annotationIndex := 0!

Item was changed:
  ----- Method: StackInterpreter>>externalSetStackPageAndPointersForSuspendedContextOfProcess: (in category 'frame access') -----
  externalSetStackPageAndPointersForSuspendedContextOfProcess: aProcess
+ 	"Set stackPage, instructionPointer, framePointer and stackPointer for the suspendedContext of
+ 	 aProcess, marrying the context if necessary, and niling the suspendedContext slot.  This is used
- 	"Set stackPage, framePointer and stackPointer for the suspendedContext of aProcess,
- 	 marrying the context if necessary, and niling the suspendedContext slot.  This is used
  	 on process switch to ensure a context has a stack frame and so can continue execution."
  	| newContext theFrame thePage newPage |
  	<var: #theFrame type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #newPage type: #'StackPage *'>
  	
  	newContext := objectMemory fetchPointer: SuspendedContextIndex ofObject: aProcess.
  	self assert: (objectMemory isContext: newContext).
  	(self isMarriedOrWidowedContext: newContext) ifTrue:
  		[self assert: (self checkIsStillMarriedContext: newContext currentFP: framePointer)].
  	objectMemory
  		storePointerUnchecked: SuspendedContextIndex
  		ofObject: aProcess
  		withValue: objectMemory nilObject.
  	(self isStillMarriedContext: newContext)
  		ifTrue:
  			[theFrame := self frameOfMarriedContext: newContext.
  			 thePage := stackPages stackPageFor: theFrame.
  			 theFrame ~= thePage headFP ifTrue:
  				["explicit assignment of suspendedContext can cause switch to interior frame."
  				 newPage := self newStackPage.
  				 self moveFramesIn: thePage
  					through: (self findFrameAbove: theFrame inPage: thePage)
  					toPage: newPage.
  				  stackPages markStackPageLeastMostRecentlyUsed: newPage].
  			 self assert: thePage headFP = theFrame]
  		ifFalse:
  			[thePage := self makeBaseFrameFor: newContext.
  			 theFrame := thePage baseFP].
  	self setStackPageAndLimit: thePage.
  	stackPointer := thePage headSP.
  	framePointer := thePage headFP.
  	(self isMachineCodeFrame: framePointer) ifFalse:
+ 		[self setMethod: (self iframeMethod: framePointer)]..
+ 	instructionPointer := self popStack.
+ 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer!
- 		[self setMethod: (self iframeMethod: framePointer)].
- 	self assertValidExecutionPointe: self stackTop asUnsignedInteger r: framePointer s: stackPointer!

Item was changed:
  ----- Method: StackInterpreter>>transferTo: (in category 'process primitive support') -----
  transferTo: newProc 
  	"Record a process to be awoken on the next interpreter cycle."
  	| activeContext sched oldProc |
  	<inline: false>
  	statProcessSwitch := statProcessSwitch + 1.
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
+ 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer.
  	sched := self schedulerPointer.
  	oldProc := objectMemory fetchPointer: ActiveProcessIndex ofObject: sched.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	objectMemory storePointer: SuspendedContextIndex ofObject: oldProc withValue: activeContext.
  	objectMemory storePointer: ActiveProcessIndex ofObject: sched withValue: newProc.
  	objectMemory storePointerUnchecked: MyListIndex ofObject: newProc withValue: objectMemory nilObject.
+ 	self externalSetStackPageAndPointersForSuspendedContextOfProcess: newProc!
- 	self externalSetStackPageAndPointersForSuspendedContextOfProcess: newProc.
- 	instructionPointer := self popStack!

Item was changed:
  ----- Method: VMClass>>cppIf:ifTrue: (in category 'translation support') -----
  cppIf: conditionBlockOrValue ifTrue: trueExpressionOrBlock
  	"When translated, produces #if (condition) #else #endif CPP directives.
  	 Example usage:
  
  		self cppIf: IMMUTABILITY
  			ifTrue: [(self internalIsImmutable: obj) ifTrue:
  						[^self primitiveFailFor: PrimErrNoModification]]"
+ 	^self cppIf: conditionBlockOrValue ifTrue: trueExpressionOrBlock ifFalse: nil!
- 	^self cppIf: conditionBlockOrValue ifTrue: trueExpressionOrBlock ifFalse: []!

Item was changed:
  ----- Method: VMClass>>cppIf:ifTrue:ifFalse: (in category 'translation support') -----
+ cppIf: conditionBlockOrSymbolValue ifTrue: trueExpressionOrBlock ifFalse: falseExpressionOrBlockOrNil
- cppIf: conditionBlockOrValue ifTrue: trueExpressionOrBlock ifFalse: falseExpressionOrBlockOrNil
  	"When translated, produces #if (condition) #else #endif CPP directives.
  	 Example usage:
  
  		self cppIf: [BytesPerWord = 8]
  			ifTrue: [self doSomethingFor64Bit]
  			ifFalse: [self doSomethingFor32Bit]
  		self cppIf: BytesPerWord = 8
  			ifTrue: [self doSomethingFor64Bit]
+ 			ifFalse: [self doSomethingFor32Bit]
+ 		self cppIf: #A_GLOBAL
+ 			ifTrue: [self doSomethingFor64Bit]
  			ifFalse: [self doSomethingFor32Bit]"
+ 	^(conditionBlockOrSymbolValue value
- 	^(conditionBlockOrValue value
  		ifNil: [false]
  		ifNotNil: [:value|
  			value isInteger
  				ifTrue: [value ~= 0]
+ 				ifFalse:
+ 					[value isSymbol
+ 						ifTrue: [(self class bindingOf: value)
+ 									ifNil: [false]
+ 									ifNotNil: [:binding| binding value]]
+ 						ifFalse: [value]]])
- 				ifFalse: [value]])
  		ifTrue: trueExpressionOrBlock
  		ifFalse: falseExpressionOrBlockOrNil!

Item was added:
+ ----- Method: VMStructType class>>alignedByteSizeOf:forClient: (in category 'simulation only') -----
+ alignedByteSizeOf: objectSymbolOrClass forClient: aVMClass
+ 	^objectSymbolOrClass byteSizeForSimulator: aVMClass!



More information about the Vm-dev mailing list