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

commits at source.squeak.org commits at source.squeak.org
Wed Nov 19 02:47:36 UTC 2014


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

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

Name: VMMaker.oscog-eem.942
Author: eem
Time: 18 November 2014, 6:45:04.634 pm
UUID: 0e7b390b-5dac-4ff1-84a3-55e02ad8de11
Ancestors: VMMaker.oscog-eem.941

64-bit-ise access to method primitive numbers.
Nuke obsolete ImmediateTagMask & SmallIntegerShift
constants in VMSqueakV3ObjectRepresentationConstants
and remove its use in InterpreterPrimtiives and StackInterpreter.
64-bit Spur now executes as far as the first bitShift:
primitive, 161 bytecodes in.

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

Item was changed:
  VMClass subclass: #InterpreterPrimitives
  	instanceVariableNames: 'objectMemory messageSelector argumentCount newMethod primFailCode profileMethod profileProcess profileSemaphore nextProfileTick preemptionYields'
  	classVariableNames: 'CrossedX EndOfRun MillisecondClockMask'
+ 	poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMSqueakV3BytecodeConstants VMStackFrameOffsets'
- 	poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices VMSqueakV3BytecodeConstants VMSqueakV3ObjectRepresentationConstants VMStackFrameOffsets'
  	category: 'VMMaker-Interpreter'!
  
  !InterpreterPrimitives commentStamp: 'eem 12/11/2012 17:11' 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 varioius 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 removed:
- ----- Method: ObjectMemory class>>initializeImmediates (in category 'initialization') -----
- initializeImmediates
- 	"The Squeak VM supports 31-bit immediate 2's compliment SmallInteger objects as the only immediate type."
- 	ImmediateTagMask := SmallIntegerShift := 1!

Item was changed:
  ----- Method: ObjectMemory class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"ObjectMemory initializeWithOptions: Dictionary new"
  
  	self initBytesPerWord: (optionsDictionary at: #BytesPerWord ifAbsent: [4]).
  	BytesPerOop := optionsDictionary at: #BytesPerOop ifAbsent: [BytesPerWord].
  
  	"Translation flags (booleans that control code generation via conditional translation):"
  	"generate assertion checks"
  	DoAssertionChecks := optionsDictionary at: #DoAssertionChecks ifAbsent: [false].
  	DoExpensiveAssertionChecks := optionsDictionary at: #DoExpensiveAssertionChecks ifAbsent: [false].
  
  	self initializeObjectHeaderConstants. "Initializes BaseHeaderSize so do early"
- 	self initializeImmediates.
  	self initializeSpecialObjectIndices.
  	self initializeCompactClassIndices.
  	self initializePrimitiveErrorCodes.
  
  	NilContext := 1.  "the oop for the integer 0; used to mark the end of context lists"
  
  	RemapBufferSize := 25.
  	RootTableSize := 2500.  	"number of root table entries (4 bytes/entry)"
  	RootTableRedZone := RootTableSize - 100.	"red zone of root table - when reached we force IGC"
  	WeakRootTableSize := RootTableSize + RemapBufferSize + 100.
  
  	"tracer actions"
  	StartField := 1.
  	StartObj := 2.
  	Upward := 3.
  	Done := 4.
  
  	ExtraRootSize := 2048. "max. # of external roots"!

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 AlternateHeaderHasPrimFlag 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 V3PrimitiveBitsMask'
+ 	poolDictionaries: 'VMBasicConstants VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants VMSqueakClassIndices VMSqueakV3BytecodeConstants VMStackFrameOffsets'
- 	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'
- 	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.
+ 	V3PrimitiveBitsMask := 16r100001FF << tagBits.
+ 	AlternateHeaderHasPrimFlag := 16r10000 << tagBits.
  	"The position of the unused flag bit in the method header, not including tag bit(s)"
  	HeaderFlagBitPosition := 29!

Item was changed:
  ----- Method: StackInterpreter>>alternateHeaderHasPrimitiveFlag: (in category 'compiled methods') -----
  alternateHeaderHasPrimitiveFlag: methodHeader
  	<inline: true>
+ 	^methodHeader anyMask: AlternateHeaderHasPrimFlag!
- 	^methodHeader anyMask: 16r10000 << SmallIntegerShift!

Item was changed:
  ----- Method: StackInterpreter>>literalCountOfAlternateHeader: (in category 'compiled methods') -----
  literalCountOfAlternateHeader: headerPointer
  	<inline: true>
+ 	^(objectMemory integerValueOf: headerPointer) bitAnd: 16rFFFF!
- 	^(headerPointer >> 1) bitAnd: 16rFFFF!

Item was changed:
  ----- Method: StackInterpreter>>methodHeaderHasPrimitive: (in category 'compiled methods') -----
  methodHeaderHasPrimitive: methodHeader
  	"Note: We now have 10 bits of primitive index, but they are in two places
  	 for temporary backward compatibility.  The time to unpack is negligible,
  	 since the derived primitive function pointer is stored in the method cache."
  	^objectMemory hasSpurMemoryManagerAPI
  		ifTrue: [self alternateHeaderHasPrimitiveFlag: methodHeader]
  		ifFalse:
  			[MULTIPLEBYTECODESETS
  				ifTrue:
  					[(self headerIndicatesAlternateBytecodeSet: methodHeader)
  						ifTrue: [self alternateHeaderHasPrimitiveFlag: methodHeader]
+ 						ifFalse: [methodHeader anyMask: V3PrimitiveBitsMask]]
- 						ifFalse: [(methodHeader bitAnd: 16r200003FE) ~= 0]]
  				ifFalse:
+ 					[methodHeader anyMask: V3PrimitiveBitsMask]]!
- 					[(methodHeader bitAnd: 16r200003FE) ~= 0]]!

Item was changed:
  ----- Method: StackInterpreter>>primitiveIndexOfMethod:header: (in category 'compiled methods') -----
  primitiveIndexOfMethod: theMethod header: methodHeader
  	"Note: With the Squeak V0 format we now have 10 bits of primitive index, but they are in
  	 two places for temporary backward compatibility.  The time to unpack is negligible,
  	 since the derived primitive function pointer is stored in the method cache.  With the new
  	 format we assume a 3-byte CallPrimitive with a little-endian 16-bit primitive index."
  	<api>
  	<inline: true>
  	| firstBytecode |
  	^objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(self alternateHeaderHasPrimitiveFlag: methodHeader)
  				ifTrue:
  					[firstBytecode := self firstBytecodeOfAlternateHeader: methodHeader method: theMethod.
  					 (objectMemory byteAt: firstBytecode + 1) + ((objectMemory byteAt: firstBytecode + 2) << 8)]
  				ifFalse:
  					[0]]
  		ifFalse:
  			[MULTIPLEBYTECODESETS
  				ifTrue:
  					[(self headerIndicatesAlternateBytecodeSet: methodHeader)
  						ifTrue:
  							[(self alternateHeaderHasPrimitiveFlag: methodHeader)
  								ifTrue:
  									[firstBytecode := self firstBytecodeOfAlternateHeader: methodHeader method: theMethod.
  									 (objectMemory byteAt: firstBytecode + 1) + ((objectMemory byteAt: firstBytecode + 2) << 8)]
  								ifFalse:
  									[0]]
  						ifFalse:
  							[| primBits |
  							 primBits := objectMemory integerValueOf: methodHeader.
  							 (primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]]
  				ifFalse:
  					[| primBits |
  					 primBits := objectMemory integerValueOf: methodHeader.
  					 (primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]]!

Item was changed:
  VMBasicConstants subclass: #VMSqueakV3ObjectRepresentationConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'AllButTypeMask CompactClassMask HashBitsOffset HashMaskUnshifted HeaderTypeShort HeaderTypeSizeAndClass ImmutabilityBit LongSizeMask MarkBit RootBit Size4Bit SizeMask TypeMask'
- 	classVariableNames: 'AllButTypeMask CompactClassMask HashBitsOffset HashMaskUnshifted HeaderTypeShort HeaderTypeSizeAndClass ImmediateTagMask ImmutabilityBit LongSizeMask MarkBit RootBit Size4Bit SizeMask SmallIntegerShift TypeMask'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMSqueakV3ObjectRepresentationConstants commentStamp: '<historical>' prior: 0!
  I am a shared pool for the constants that define the Squeak V3 object representation shared between the object memories (e.g. ObjectMemory, NewObjectMemory), the interpreters (e.g. StackInterpreter, CoInterpreter) and the object representations (e.g. ObjectRepresentationForSqueakV3).
  
  self ensureClassPool
  self classPool declare: #AllButTypeMask from: VMObjectOffsets classPool
  (ObjectMemory classPool keys select: [:k| k includesSubString: 'Compact']) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list