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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 5 20:18:22 UTC 2014


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

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

Name: VMMaker.oscog-eem.966
Author: eem
Time: 5 December 2014, 12:15:48.45 pm
UUID: 46dd10c6-dc03-444c-bfa2-0f0b279c9b06
Ancestors: VMMaker.oscog-eem.965

Add support for a -breakmnu vm argument that calls
warning (or in the simulator, halts) on an mnu of a
specific selector.

Update StackInterpreter's class comment.

Eliminate a type clash with getLongFromFile:swap:

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

Item was removed:
- ----- Method: CogVMSimulator>>sendBreak:point:receiver: (in category 'debugging traps') -----
- sendBreak: selectorString point: selectorLength receiver: receiverOrNil
- 	"self shortPrintFrameAndCallers: localFP"
- 	| i |
- 	breakSelectorLength = selectorLength ifTrue:
- 		[i := breakSelectorLength.
- 		 [i > 0] whileTrue:
- 			[(objectMemory byteAt: selectorString + i - 1) = (breakSelector at: i) asInteger
- 				ifTrue: [(i := i - 1) = 0 ifTrue:
- 							[self changed: #byteCountText.
- 							 self halt: 'Send of '
- 									, breakSelector,
- 									(receiverOrNil
- 										ifNotNil: [' to ', (self shortPrint: receiverOrNil)]
- 										ifNil: [''])]]
- 				ifFalse: [i := 0]]]!

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'
  	category: 'VMMaker-Interpreter'!
  
+ !StackInterpreter commentStamp: 'eem 12/5/2014 11:32' prior: 0!
- !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.
  
+ StackInterpreter and subclasses support multiple memory managers.  Currently there are two.  NewMemoryManager is a slightly refined version of ObjectMemory, and is the memory manager and garbage collector for the original Squeak object representation as described in "Back to the Future The Story of Squeak, A Practical Smalltalk Written in Itself", see http://ftp.squeak.org/docs/OOPSLA.Squeak.html.  Spur is a faster, more regular object representation that is designed for more performance and functionality, and to have a common header format for both 32-bit and 64-bit versions.  You can read about it in SpurMemoryManager's class comment.  There is also a video of a presentation at ESUG 2014 (https://www.youtube.com/watch?v=k0nBNS1aHZ4), along with slides (http://www.slideshare.net/esug/spur-a-new-object-representation-for-cog?related=1).!
- 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>>createActualMessageTo: (in category 'message sending') -----
  createActualMessageTo: lookupClass 
  	"Bundle up the selector, arguments and lookupClass into a Message object. 
  	 In the process it pops the arguments off the stack, and pushes the message object. 
  	 This can then be presented as the argument of e.g. #doesNotUnderstand:"
  	| argumentArray message |
  	<inline: false> "This is a useful break-point"
  	self assert: ((objectMemory isImmediate: messageSelector) or: [objectMemory addressCouldBeObj: messageSelector]).
+ 	self mnuBreakpoint: messageSelector receiver: nil.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[argumentArray := objectMemory
  								eeInstantiateSmallClassIndex: ClassArrayCompactIndex
  								format: objectMemory arrayFormat
  								numSlots: argumentCount.
  			 message := objectMemory
  								eeInstantiateSmallClassIndex: ClassMessageCompactIndex
  								format: objectMemory nonIndexablePointerFormat
  								numSlots: MessageLookupClassIndex + 1]
  		ifFalse:
  			[argumentArray := objectMemory
  								eeInstantiateSmallClass: (objectMemory splObj: ClassArray)
  								numSlots: argumentCount.
  			 message := objectMemory
  								eeInstantiateSmallClass: (objectMemory splObj: ClassMessage)
  								numSlots: MessageLookupClassIndex + 1].
  
  	"Since the array is new can use unchecked stores."
  	(argumentCount - 1) * objectMemory bytesPerOop to: 0 by: objectMemory bytesPerOop negated do:
  		[:i|
  		self longAt:  argumentArray + objectMemory baseHeaderSize + i put: self popStack].
  	"Since message is new can use unchecked stores."
  	objectMemory
  		storePointerUnchecked: MessageSelectorIndex ofObject: message withValue: messageSelector;
  		storePointerUnchecked: MessageArgumentsIndex ofObject: message withValue: argumentArray;
  		storePointerUnchecked: MessageLookupClassIndex ofObject: message withValue: lookupClass.
  
  	self push: message.
  
  	argumentCount := 1!

Item was changed:
  ----- Method: StackInterpreter>>getLongFromFile:swap: (in category 'image save/restore') -----
  getLongFromFile: aFile swap: swapFlag
  	"Answer the next 32 or 64 bit word read from aFile, byte-swapped according to the swapFlag."
- 
  	<var: #aFile type: #sqImageFile>
  	| w |
- 	<var: #w type: #long>
  	w := 0.
  	self cCode: [self
  					sq: (self addressOf: w)
+ 					Image: (self sizeof: w)
- 					Image: (self sizeof: #long)
  					File: 1
  					Read: aFile]
  		inSmalltalk: [w := objectMemory nextLongFrom: aFile].
  	^swapFlag
  		ifTrue: [objectMemory byteSwapped: w]
  		ifFalse: [w]!

Item was added:
+ ----- Method: StackInterpreter>>mnuBreak:point:receiver: (in category 'debugging traps') -----
+ mnuBreak: selectorString point: selectorLength receiver: receiverOrNil
+ 	<doNotGenerate> "C version is in platforms/Cross/vm/dispdbg.h"
+ 	"self shortPrintFrameAndCallers: localFP"
+ 	| i |
+ 	breakSelectorLength negated = selectorLength ifTrue:
+ 		[i := breakSelectorLength negated.
+ 		 [i > 0] whileTrue:
+ 			[(objectMemory byteAt: selectorString + i - 1) = (breakSelector at: i) asInteger
+ 				ifTrue: [(i := i - 1) = 0 ifTrue:
+ 							[self changed: #byteCountText.
+ 							 self halt: 'MNU of '
+ 									, breakSelector,
+ 									(receiverOrNil
+ 										ifNotNil: [' to ', (self shortPrint: receiverOrNil)]
+ 										ifNil: [''])]]
+ 				ifFalse: [i := 0]]]!

Item was added:
+ ----- Method: StackInterpreter>>mnuBreakpoint:receiver: (in category 'debug support') -----
+ mnuBreakpoint: selector receiver: rcvr
+ 	<inline: true>
+ 	self mnuBreak: (objectMemory firstFixedFieldOfMaybeImmediate: selector)
+ 		point: (objectMemory lengthOfMaybeImmediate: selector)
+ 		receiver: rcvr!

Item was added:
+ ----- Method: StackInterpreter>>sendBreak:point:receiver: (in category 'debugging traps') -----
+ sendBreak: selectorString point: selectorLength receiver: receiverOrNil
+ 	<doNotGenerate> "C version is in platforms/Cross/vm/dispdbg.h"
+ 	"self shortPrintFrameAndCallers: localFP"
+ 	| i |
+ 	breakSelectorLength = selectorLength ifTrue:
+ 		[i := breakSelectorLength.
+ 		 [i > 0] whileTrue:
+ 			[(objectMemory byteAt: selectorString + i - 1) = (breakSelector at: i) asInteger
+ 				ifTrue: [(i := i - 1) = 0 ifTrue:
+ 							[self changed: #byteCountText.
+ 							 self halt: 'Send of '
+ 									, breakSelector,
+ 									(receiverOrNil
+ 										ifNotNil: [' to ', (self shortPrint: receiverOrNil)]
+ 										ifNil: [''])]]
+ 				ifFalse: [i := 0]]]!

Item was added:
+ ----- Method: StackInterpreter>>setBreakMNUSelector: (in category 'debug support') -----
+ setBreakMNUSelector: aString
+ 	<api>
+ 	<var: #aString type: #'char *'>
+ 	(breakSelector := aString)
+ 		ifNil: [breakSelectorLength := objectMemory minSmallInteger "nil's effective length is zero"]
+ 		ifNotNil: [breakSelectorLength := (self strlen: aString) negated]!

Item was changed:
  ----- Method: StackInterpreter>>setBreakSelector: (in category 'debug support') -----
  setBreakSelector: aString
  	<api>
  	<var: #aString type: #'char *'>
+ 	(breakSelector := aString)
+ 		ifNil: [breakSelectorLength := objectMemory minSmallInteger "nil's effective length is zero"]
+ 		ifNotNil: [breakSelectorLength := self strlen: aString]!
- 	aString isNil
- 		ifTrue: [breakSelectorLength := -1. "nil's effective length is zero" breakSelector := nil]
- 		ifFalse: [breakSelectorLength := self strlen: aString. breakSelector := aString]!

Item was removed:
- ----- Method: StackInterpreterSimulator>>sendBreak:point:receiver: (in category 'debugging traps') -----
- sendBreak: selectorString point: selectorLength receiver: receiverOrNil
- 	"self shortPrintFrameAndCallers: localFP"
- 	| i |
- 	breakSelectorLength = selectorLength ifTrue:
- 		[i := breakSelectorLength.
- 		 [i > 0] whileTrue:
- 			[(objectMemory byteAt: selectorString + i - 1) = (breakSelector at: i) asInteger
- 				ifTrue: [(i := i - 1) = 0 ifTrue:
- 							[self halt: 'Send of '
- 									, breakSelector,
- 									(receiverOrNil
- 										ifNotNil: [' to ', (self shortPrint: receiverOrNil)]
- 										ifNil: [''])]]
- 				ifFalse: [i := 0]]]!



More information about the Vm-dev mailing list