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

commits at source.squeak.org commits at source.squeak.org
Wed Nov 19 02:16:05 UTC 2014


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

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

Name: VMMaker.oscog-eem.941
Author: eem
Time: 18 November 2014, 6:13:23.662 pm
UUID: 729c5ae6-4737-4218-905d-063cc7afb645
Ancestors: VMMaker.oscog-eem.940

64-bit-ise string printing and method header numArgs
and numTemps access.

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

Item was changed:
  ----- Method: CoInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr errorCode switched |
  	<inline: true>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader) not.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
+ 	self assert: argumentCount = (self argumentCountOfMethodHeader: methodHeader).
- 
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: 0. "FoxIFSavedIP"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: localIP + 1)
  			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 switched := self handleStackOverflowOrEventAllowContextSwitch:
  						(self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self returnToExecutive: true postContextSwitch: switched.
  		 self internalizeIPandSP]!

Item was changed:
  ----- Method: CogVMSimulatorLSB>>charsOfLong: (in category 'debug support') -----
  charsOfLong: long
+ 	^ (1 to: objectMemory wordSize) collect:
- 	^ (1 to: 4) collect:
  		[:i | ((long digitAt: i) between: 14 and: 126)
  					ifTrue: [(long digitAt: i) asCharacter]
  					ifFalse: [$?]]!

Item was removed:
- ----- Method: NewCoObjectMemorySimulatorLSB>>charsOfLong: (in category 'debug support') -----
- charsOfLong: long
- 	^ (1 to: 4) collect:
- 		[:i | ((long digitAt: i) between: 14 and: 126)
- 					ifTrue: [(long digitAt: i) asCharacter]
- 					ifFalse: [$?]]!

Item was removed:
- ----- Method: NewCoObjectMemorySimulatorMSB>>charsOfLong: (in category 'debug support') -----
- charsOfLong: long
- 	^ (self wordSize to: 1 by: -1) collect:
- 		[:i | ((long digitAt: i) between: 14 and: 126)
- 					ifTrue: [(long digitAt: i) asCharacter]
- 					ifFalse: [$?]]!

Item was removed:
- ----- Method: NewObjectMemorySimulatorLSB>>charsOfLong: (in category 'debug support') -----
- charsOfLong: long
- 	^ (1 to: 4) collect:
- 		[:i | ((long digitAt: i) between: 14 and: 126)
- 					ifTrue: [(long digitAt: i) asCharacter]
- 					ifFalse: [$?]]!

Item was removed:
- ----- Method: NewObjectMemorySimulatorMSB>>charsOfLong: (in category 'debug support') -----
- charsOfLong: long
- 	^ (self wordSize to: 1 by: -1) collect:
- 		[:i | ((long digitAt: i) between: 14 and: 126)
- 					ifTrue: [(long digitAt: i) asCharacter]
- 					ifFalse: [$?]]!

Item was added:
+ ----- Method: ObjectMemory class>>numSmallIntegerTagBits (in category 'accessing') -----
+ numSmallIntegerTagBits
+ 	^1!

Item was added:
+ ----- Method: ObjectMemory>>numSmallIntegerTagBits (in category 'interpreter access') -----
+ numSmallIntegerTagBits
+ 	^1!

Item was added:
+ ----- Method: Spur32BitMemoryManager class>>numSmallIntegerTagBits (in category 'simulation only') -----
+ numSmallIntegerTagBits
+ 	^1!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>numSmallIntegerTagBits (in category 'interpreter access') -----
+ numSmallIntegerTagBits
+ 	^1!

Item was added:
+ ----- Method: Spur64BitMemoryManager class>>numSmallIntegerTagBits (in category 'simulation only') -----
+ numSmallIntegerTagBits
+ 	^3!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>numSmallIntegerTagBits (in category 'interpreter access') -----
+ numSmallIntegerTagBits
+ 	^3!

Item was added:
+ ----- Method: SpurMemoryManager class>>numSmallIntegerTagBits (in category 'accessing') -----
+ numSmallIntegerTagBits
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>numSmallIntegerTagBits (in category 'interpreter access') -----
+ numSmallIntegerTagBits
+ 	^self subclassResponsibility!

Item was changed:
  InterpreterPrimitives subclass: #StackInterpreter
  	instanceVariableNames: 'currentBytecode bytecodeSetSelector localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue extA extB primitiveFunctionPointer methodCache atCache lkupClassTag lkupClass methodDictLinearSearchLimit highestRunnableProcessPriority nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptKeycode interruptPending savedWindowSize imageHeaderFlags fullScreenFlag deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable primitiveAccessorDepthTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2 theUnknownShort the2ndUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex classByteArrayCompactIndex statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents statPendingFinalizationSignals'
+ 	classVariableNames: 'AltBytecodeEncoderClassName AltLongStoreBytecode AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex FailImbalancedPrimitives HeaderFlagBitPosition LongStoreBytecode MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MethodHeaderArgCountShift MethodHeaderTempCountShift MixinIndex PrimitiveExternalCallIndex PrimitiveTable StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced StackPageUnreached'
- 	classVariableNames: 'AltBytecodeEncoderClassName AltLongStoreBytecode AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName BytecodeTable CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex FailImbalancedPrimitives HeaderFlagBitPosition LongStoreBytecode MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MixinIndex PrimitiveExternalCallIndex PrimitiveTable StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced StackPageUnreached'
  	poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices VMSqueakV3BytecodeConstants VMSqueakV3ObjectRepresentationConstants VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !StackInterpreter commentStamp: 'eem 9/11/2013 18:30' 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.  An even better solution is to eliminate compact classes altogether (see 6.).
  
  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. [Late news, the support has been extended to 64-bit file 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.  We can still have 31-bit SmallIntegers by allowing two tag patterns for SmallInteger.
  
  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.  [Late breaking news, the 2-word header scheme is more compact, by over 2%].  See SpurMemorymanager's class comment.!

Item was changed:
  ----- Method: StackInterpreter class>>initializeMethodIndices (in category 'initialization') -----
  initializeMethodIndices
+ 	| tagBits |
  	"Class CompiledMethod"
  	HeaderIndex := 0.
  	LiteralStart := 1.
  
+ 	tagBits := self objectMemoryClass numSmallIntegerTagBits.
+ 	LargeContextBit := 16r20000 << tagBits.  "This bit set in method headers if large context is needed."
+ 	MethodHeaderTempCountShift := 18 + tagBits.
+ 	MethodHeaderArgCountShift := 24 + tagBits.
- 	LargeContextBit := 16r40000.  "This bit set in method headers if large context is needed."
  	"The position of the unused flag bit in the method header, not including tag bit(s)"
  	HeaderFlagBitPosition := 29!

Item was changed:
  ----- Method: StackInterpreter>>argumentCountOfMethodHeader: (in category 'compiled methods') -----
  argumentCountOfMethodHeader: header
  	<api>
+ 	^header >> MethodHeaderArgCountShift bitAnd: 16rF!
- 	^header >> 25 bitAnd: 16r0F!

Item was changed:
  ----- Method: StackInterpreter>>initialPCForHeader:method: (in category 'compiled methods') -----
  initialPCForHeader: methodHeader method: theMethod
+ 	"Answer a pointer to the initial byte for a method; used only in methods that build a frame."
- 	"Answer the initial PC for a method; used only in methods that build a frame."
  	<inline: true>
  	^theMethod
  	+ ((LiteralStart + (objectMemory literalCountOfMethodHeader: methodHeader)) * objectMemory bytesPerOop)
  	+ objectMemory baseHeaderSize!

Item was changed:
  ----- Method: StackInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr errorCode |
  	<inline: true>
  
  	methodHeader := objectMemory methodHeaderOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
+ 	self assert: argumentCount = (self argumentCountOfMethodHeader: methodHeader).
- 
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: localIP + 1)
  			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self internalizeIPandSP]!

Item was changed:
  ----- Method: StackInterpreter>>temporaryCountOfMethodHeader: (in category 'compiled methods') -----
  temporaryCountOfMethodHeader: header
  	<api>
  	<inline: true>
+ 	^header >> MethodHeaderTempCountShift bitAnd: 16r3F!
- 	^(header >> 19) bitAnd: 16r3F!

Item was changed:
  ----- Method: StackInterpreterSimulatorLSB>>charsOfLong: (in category 'debug support') -----
  charsOfLong: long
+ 	^ (1 to: objectMemory wordSize) collect:
- 	^ (1 to: 4) collect:
  		[:i | ((long digitAt: i) between: 14 and: 126)
  					ifTrue: [(long digitAt: i) asCharacter]
  					ifFalse: [$?]]!



More information about the Vm-dev mailing list