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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 23 00:27:24 UTC 2014


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

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

Name: VMMaker.oscog-eem.588
Author: eem
Time: 22 January 2014, 4:23:19.421 pm
UUID: d25a3958-3120-443b-a37e-d0611d81e833
Ancestors: VMMaker.oscog-eem.587

Add missing ObjectMemory>>followObjField:ofObject:.

Fix valid instruction pointer asserts for instructionPointer pointing
at byte before first bytecode.

Go some way to restoring in-image compilation which was broken
by VMMaker.oscog-eem.344/343's revamp of simulator instantiation.

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

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur class>>defaultObjectMemoryClass (in category 'accessing') -----
+ defaultObjectMemoryClass
+ 	"For in-image compilation."
+ 	^Spur32BitCoMemoryManager!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur class>>defaultObjectMemoryClass (in category 'accessing') -----
+ defaultObjectMemoryClass
+ 	"For in-image compilation.  Spur64BitCoMemoryManager is as yet undefined."
+ 	^Smalltalk classNamed: #Spur64BitCoMemoryManager!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3 class>>defaultObjectMemoryClass (in category 'accessing') -----
+ defaultObjectMemoryClass
+ 	"For in-image compilation."
+ 	^NewCoObjectMemory!

Item was changed:
  ----- Method: Cogit class>>cog:selector:options: (in category 'in-image compilation') -----
  cog: aCompiledMethod selector: aSelector options: optionsDictionaryOrArray
  	"StackToRegisterMappingCogit cog: (Integer >> #benchFib) selector: #benchFib options: #(COGMTVM false)"
  	| coInterpreter cogit |
  	self initializeWithOptions: (self asOptionsDictionary: optionsDictionaryOrArray).
+ 	coInterpreter := CurrentImageCoInterpreterFacade forCogit: (cogit := self new).
- 	coInterpreter := CurrentImageCoInterpreterFacade new cogit: (cogit := self new); yourself.
  	[cogit
  		setInterpreter: coInterpreter;
  		singleStep: true;
  		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size.
  	 cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
  		on: Notification
  		do: [:ex|
  			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
  				[ex resume: coInterpreter].
  			ex pass].
  	^{ coInterpreter.
  		cogit.
  		cogit cog: (coInterpreter oopForObject: aCompiledMethod) selector: (coInterpreter oopForObject: aSelector) }!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade class>>forCogit: (in category 'instance creation') -----
+ forCogit: aCogit
+ 	| class |
+ 	class := self allSubclasses
+ 				detect: [:subclass| aCogit class objectMemoryClass = subclass objectRepresentationClass objectMemoryClass]
+ 				ifNone: [self error: 'cannot find subclass for the Cogit''s objectRepresentation and/or objectMemory'].
+ 	^class new
+ 		cogit: aCogit;
+ 		yourself!

Item was added:
+ CurrentImageCoInterpreterFacade subclass: #CurrentImageCoInterpreterFacadeForSpurObjectRepresentation
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Support'!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation class>>objectRepresentationClass (in category 'accessing') -----
+ objectRepresentationClass
+ 	^CogObjectRepresentationFor32BitSpur!

Item was changed:
  ----- Method: ObjectMemory>>followField:ofObject: (in category 'forward compatibility') -----
  followField: fieldIndex ofObject: anObject
+ 	<inline: true>
  	^self fetchPointer: fieldIndex ofObject: anObject!

Item was added:
+ ----- Method: ObjectMemory>>followObjField:ofObject: (in category 'forward compatibility') -----
+ followObjField: fieldIndex ofObject: anObject
+ 	<inline: true>
+ 	^self fetchPointer: fieldIndex ofObject: anObject!

Item was changed:
  ----- Method: StackInterpreter>>contextInstructionPointer:frame: (in category 'frame access') -----
  contextInstructionPointer: theIP frame: theFP
  	<var: #theFP type: #'char *'>
+ 	self assert: (self validInstructionPointer: theIP + 1 inFrame: theFP).
- 	self assert: (self validInstructionPointer: theIP inFrame: theFP).
  	^objectMemory integerObjectOf: theIP - (self iframeMethod: theFP) - BaseHeaderSize + 2!

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
  	 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 + 1 r: framePointer s: stackPointer!
- 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer!

Item was changed:
  ----- Method: StackInterpreter>>handleStackOverflow (in category 'message sending') -----
  handleStackOverflow
  	"Check for stack overflow, moving frames to another stack if so."
  	| newPage theFP callerFP overflowLimitAddress overflowCount |
  	<var: #newPage type: #'StackPage *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #overflowLimitAddress type: #'char *'>
  
  	"After checkForInterrupts another event check may have been forced, setting both
  	 stackLimit and stackPage stackLimit to all ones.  So here we must check against
  	 the real stackLimit, not the effective stackLimit."
  	stackPointer < stackPage realStackLimit ifFalse:
  		[^self].
  
  	self maybeTraceStackOverflow.
  	statStackOverflow := statStackOverflow + 1.
  
  	"The stack has overflowed this page.  If the system is executing some recursive algorithm,
  	 e.g. fibonacci, then the system could thrash overflowing the stack if the call soon returns
  	 back to the current page.  To avoid thrashing, since overflow is quite slow, we can move
  	 more than one frame.  The idea is to record which page has overflowed, and the first
  	 time it overflows move one frame, the second time two frames, and so on.  We move no
  	 more frames than would leave the page half occupied."
  	theFP := framePointer.
  	stackPage = overflowedPage
  		ifTrue:
  			[overflowLimitAddress := stackPage baseAddress - stackPages overflowLimit.
  			 overflowCount := extraFramesToMoveOnOverflow := extraFramesToMoveOnOverflow + 1.
  			 [(overflowCount := overflowCount - 1) >= 0
  			   and: [(callerFP := self frameCallerFP: theFP) < overflowLimitAddress
  			   and: [(self isBaseFrame: callerFP) not]]] whileTrue:
  				[theFP := callerFP]]
  		ifFalse:
  			[overflowedPage := stackPage.
  			 extraFramesToMoveOnOverflow := 0].
  
  	self ensureCallerContext: theFP.
  	newPage := self newStackPage.
  	self moveFramesIn: stackPage through: theFP toPage: newPage.
  	self setStackPageAndLimit: newPage.
  	framePointer := stackPage headFP.
  	stackPointer := stackPage headSP.
  	self isCog
  		ifFalse: "To overflow the stack this must be a new frame, but in Cog base frames are married."
  			[self assert: (self frameHasContext: framePointer) not.
+ 			 self assert: (self validInstructionPointer: instructionPointer + 1
- 			 self assert: (self validInstructionPointer: instructionPointer
  							inMethod: method
  							framePointer: framePointer)]
  		ifTrue:
+ 			[self assert: (self validInstructionPointer: instructionPointer + 1
- 			[self assert: (self validInstructionPointer: instructionPointer
  							inFrame: framePointer).
  			 self assert: ((self frameHasContext: framePointer) not
  						or: [objectMemory isContext: (self frameContext: framePointer)])]!

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 + 1 r: framePointer s: stackPointer.
- 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer.
  	sched := self schedulerPointer.
  	oldProc := objectMemory fetchPointer: ActiveProcessIndex ofObject: sched.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer + BytesPerWord.
  	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!

Item was changed:
  ----- Method: StackInterpreter>>validInstructionPointer:inMethod:framePointer: (in category 'debug support') -----
  validInstructionPointer: theInstrPointer inMethod: aMethod framePointer: fp
  	<var: #theInstrPointer type: #usqInt>
  	<var: #aMethod type: #usqInt>
  	<var: #fp type: #'char *'>
  	^self
  		cppIf: MULTIPLEBYTECODESETS
  		ifTrue:
  			[| methodHeader |
  			 methodHeader := self noAssertHeaderOf: aMethod. "-1 for pre-increment in fetchNextBytecode"
+ 			 theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerOop)
- 			 theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BaseHeaderSize - 1)
  			 and: [theInstrPointer < (aMethod + (objectMemory byteLengthOf: aMethod) + BaseHeaderSize - 1)
  			 and: ["If the method starts with a CallPrimitive opcode the instruction pointer should be past it."
  				((self headerIndicatesAlternateBytecodeSet: methodHeader)
  				and: [(self alternateHeaderHasPrimitiveFlag: methodHeader)
  				and: [theInstrPointer < (aMethod
  										+ BaseHeaderSize - 1
  										+ (objectMemory lastPointerOf: aMethod)
  										+ (self sizeOfCallPrimitiveBytecode: methodHeader) - 1)]])
  					not]]]
  		ifFalse: "-1 for pre-increment in fetchNextBytecode"
+ 			[theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerOop)
- 			[theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod))
  			 and: [theInstrPointer < (aMethod + (objectMemory byteLengthOf: aMethod) + objectMemory baseHeaderSize - 1)]]!

Item was added:
+ ----- Method: VMMaker class>>generateNewspeakSpurCogVM (in category 'configurations') -----
+ generateNewspeakSpurCogVM
+ 	"No primitives since we can use those for the Cog Newspeak VM"
+ 	^VMMaker
+ 		generate: CoInterpreter
+ 		and: StackToRegisterMappingCogit
+ 		with: #(	ObjectMemory Spur32BitCoMemoryManager
+ 				MULTIPLEBYTECODESETS true
+ 				NewspeakVM true)
+ 		to: (FileDirectory default pathFromURI: 'oscogvm/nsspursrc')
+ 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
+ 		including:#()!

Item was added:
+ ----- Method: VMMaker class>>generateNewspeakSpurStackVM (in category 'configurations') -----
+ generateNewspeakSpurStackVM
+ 	"No primitives since we can use those for the Cog Newspeak VM"
+ 	^VMMaker
+ 		generate: StackInterpreter
+ 		with: #(	ObjectMemory Spur32BitMemoryManager
+ 				MULTIPLEBYTECODESETS true
+ 				NewspeakVM true)
+ 		to: (FileDirectory default directoryNamed: 'oscogvm/nsspurstacksrc') fullName
+ 		platformDir: (FileDirectory default directoryNamed: 'oscogvm/platforms') fullName
+ 		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogVM (in category 'configurations') -----
  generateSqueakSpurCogVM
+ 	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS false
  				NewspeakVM false)
  		to: (FileDirectory default pathFromURI: 'oscogvm/spursrc')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurStackVM (in category 'configurations') -----
  generateSqueakSpurStackVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
+ 		with: #(	ObjectMemory Spur32BitCoMemoryManager
+ 				MULTIPLEBYTECODESETS false
+ 				NewspeakVM false)
- 		with: #(ObjectMemory Spur32BitMemoryManager)
  		to: (FileDirectory default directoryNamed: 'oscogvm/spurstacksrc') fullName
  		platformDir: (FileDirectory default directoryNamed: 'oscogvm/platforms') fullName
  		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!



More information about the Vm-dev mailing list