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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 15 19:40:18 UTC 2015


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

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

Name: VMMaker.oscog-eem.1020
Author: eem
Time: 15 January 2015, 11:39:01.031 am
UUID: ef73cd3f-99cc-4bb1-83ac-31e56411dc5c
Ancestors: VMMaker.oscog-cb.1019

Fix monumental blunder in jitted store-check code.
The saved registers mask needs to be the *or* of
the value reg and the caller-saved registers, not
the *and*!!

Merge with VMMaker.oscog-cb.1019's changes that
use the method header flag bit to identify optimized
methods.  rename HeaderFlagBitPosition and
MethodHeaderOptimizedBitShift to
MethodHeaderFlagBitPosition.

Slang:
Eliminate null expressions in and: and or: if
generateDeadCode is false.

=============== Diff against VMMaker.oscog-cb.1019 ===============

Item was changed:
  ----- Method: CCodeGenerator>>generateSequentialAnd:on:indent: (in category 'C translation') -----
  generateSequentialAnd: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
+ 	(self nilOrBooleanConstantReceiverOf: msgNode receiver)
+ 		ifNil:
+ 			[self emitCExpression: msgNode receiver on: aStream indent: level.
+ 			 aStream crtab: level; nextPutAll: ' && ('.
+ 			 self emitCTestBlock: msgNode args first on: aStream indent: level.
+ 			 aStream nextPut: $)]
+ 		ifNotNil:
+ 			[:const |
+ 			const
+ 				ifTrue: [self emitCTestBlock: msgNode args first on: aStream indent: level]
+ 				ifFalse: [aStream nextPut: $0]]!
- 	self emitCExpression: msgNode receiver on: aStream indent: level.
- 	aStream crtab: level; nextPutAll: ' && ('.
- 	self emitCTestBlock: msgNode args first on: aStream indent: level.
- 	aStream nextPut: $)!

Item was changed:
  ----- Method: CCodeGenerator>>generateSequentialOr:on:indent: (in category 'C translation') -----
  generateSequentialOr: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  	"Note: PP 2.3 compiler produces two arguments for or:, presumably
  	 to help with inlining later. Taking the last agument should do the correct
  	 thing even if your compiler is different."
  
+ 	(self nilOrBooleanConstantReceiverOf: msgNode receiver)
+ 		ifNil:
+ 			[self emitCExpression: msgNode receiver on: aStream indent: level.
+ 			 aStream crtab: level; nextPutAll: ' || ('.
+ 			 self emitCTestBlock: msgNode args last on: aStream indent: level.
+ 			 aStream nextPut: $)]
+ 		ifNotNil:
+ 			[:const |
+ 			const
+ 				ifTrue: [aStream nextPut: $1]
+ 				ifFalse: [self emitCTestBlock: msgNode args first on: aStream indent: level]]!
- 	self emitCExpression: msgNode receiver on: aStream indent: level.
- 	aStream crtab: level; nextPutAll: ' || ('.
- 	self emitCTestBlock: msgNode args last on: aStream indent: level.
- 	aStream nextPutAll: ')'!

Item was changed:
  ----- Method: CoInterpreter>>maybeFlagMethodAsInterpreted: (in category 'compiled methods') -----
  maybeFlagMethodAsInterpreted: aMethod
+ 	"In the Sista VM the flag bit in the method header is taken to identify optimized methods.
+ 	 In other VMs it can be used to flag methods that are interpreted, if it has been requested
+ 	 from the image header flags."
+ 	(SistaVM not and: [flagInterpretedMethods]) ifTrue:
+ 		[| rawHeader realHeader |
+ 		 rawHeader := self rawHeaderOf: aMethod.
- 	| rawHeader realHeader |
- 	flagInterpretedMethods ifTrue:
- 		[rawHeader := self rawHeaderOf: aMethod.
  		 realHeader := (self isCogMethodReference: rawHeader)
  						ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader]
  						ifFalse: [rawHeader].
+ 		 realHeader := realHeader bitOr: (objectMemory integerObjectOf: 1 << MethodHeaderFlagBitPosition).
- 		 realHeader := realHeader bitOr: (objectMemory integerObjectOf: 1 << HeaderFlagBitPosition).
  		 (self isCogMethodReference: rawHeader)
  			ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader: realHeader]
  			ifFalse: [objectMemory storePointerUnchecked: 0 ofObject: aMethod withValue: realHeader]]!

Item was changed:
  ----- Method: CoInterpreter>>setImageHeaderFlagsFrom: (in category 'image save/restore') -----
  setImageHeaderFlagsFrom: headerFlags
  	"Set the flags that are contained in the 7th long of the image header."
  	imageHeaderFlags := headerFlags. "so as to preserve unrecognised flags."
  	fullScreenFlag := headerFlags bitAnd: 1.
  	imageFloatsBigEndian := (headerFlags bitAnd: 2) = 0 ifTrue: [1] ifFalse: [0].
  	processHasThreadId := (headerFlags bitAnd: 4) ~= 0.
  	flagInterpretedMethods := (headerFlags bitAnd: 8) ~= 0.
  	preemptionYields := (headerFlags bitAnd: 16) = 0.
+ 	noThreadingOfGUIThread := (headerFlags bitAnd: 32) ~= 0.
+ 
+ 	(SistaVM and: [flagInterpretedMethods]) ifTrue:
+ 		[self print: 'warning, flagInterpretedMethods inoperable in Sista VMs.'; cr]!
- 	noThreadingOfGUIThread := (headerFlags bitAnd: 32) ~= 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreCheckReceiverReg:valueReg:scratchReg: (in category 'compile abstract instructions') -----
  genStoreCheckReceiverReg: destReg valueReg: valueReg scratchReg: scratchReg
  	"Generate the code for a store check of valueReg into destReg."
  	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered mask rememberedBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  	"Is value stored an integer?  If so we're done"
  	cogit MoveR: valueReg R: scratchReg.
  	cogit AndCq: objectMemory tagMask R: scratchReg.
  	jmpImmediate := cogit JumpNonZero: 0.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpBelow: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: valueReg. "N.B. FLAGS := valueReg - scratchReg"
  	jmpSourceOld := cogit JumpAboveOrEqual: 0.
  	"value is young and target is old.
  	 Need to remember this only if the remembered bit is not already set.
  	 Test the remembered bit.  Only need to fetch the byte containing it,
  	 which reduces the size of the mask constant."
  	rememberedBitByteOffset := jmpSourceOld isBigEndian
  									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
  									ifFalse:[objectMemory rememberedBitShift // 8].
  	mask := 1 << (objectMemory rememberedBitShift \\ 8).
  	"N.B. MoveMb:r:R: does not zero other bits"
  	cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
  	cogit AndCq: mask R: scratchReg.
  	jmpAlreadyRemembered := cogit JumpNonZero: 0.
  	"Remembered bit is not set.  Call store check to insert dest into remembered table."
  	self assert: destReg == ReceiverResultReg.
  	cogit
  		CallRT: ceStoreCheckTrampoline
  		registersToBeSavedMask: ((cogit registerMaskFor: valueReg)
+ 										bitOr: cogit callerSavedRegMask).
- 										bitAnd: cogit callerSavedRegMask).
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  	(jmpAlreadyRemembered jmpTarget:
  		cogit Label))).
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genStoreSourceReg:slotIndex:destReg:scratchReg: (in category 'compile abstract instructions') -----
  genStoreSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg
  	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRoot mask rootBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRoot type: #'AbstractInstruction *'>
  	"do the store"
  	cogit MoveR: sourceReg Mw: index * objectMemory wordSize + objectMemory baseHeaderSize r: destReg.
  	"now the check.  Is value stored an integer?  If so we're done"
  	cogit MoveR: sourceReg R: scratchReg.
  	cogit AndCq: 1 R: scratchReg.
  	jmpImmediate := cogit JumpNonZero: 0.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveAw: objectMemory youngStartAddress R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpAboveOrEqual: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := sourceReg - scratchReg"
  	jmpSourceOld := cogit JumpBelow: 0.
  	"value is young and target is old.
  	 Need to make this a root if the root bit is not already set.
  	 Test the root bit.  Only need to fetch the byte containing it,
  	 which reduces the size of the mask constant."
  	rootBitByteOffset := jmpSourceOld isBigEndian
  							ifTrue: [objectMemory wordSize - RootBitDigitLength]
  							ifFalse:[RootBitDigitLength - 1].
  	mask := RootBitDigitLength > 1
  				ifTrue: [RootBit >> (RootBitDigitLength - 1 * 8)]
  				ifFalse: [RootBit].
  	"N.B. MoveMb:r:R: does not zero other bits"
  	cogit MoveMb: rootBitByteOffset r: destReg R: scratchReg.
  	cogit AndCq: mask R: scratchReg.
  	jmpAlreadyRoot := cogit JumpNonZero: 0.
  	"Root bit is not set.  Call store check to insert dest into root table."
  	self assert: destReg == ReceiverResultReg.
  	cogit
  		CallRT: ceStoreCheckTrampoline
  		registersToBeSavedMask: ((cogit registerMaskFor: sourceReg)
+ 										bitOr: cogit callerSavedRegMask).
- 										bitAnd: cogit callerSavedRegMask).
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  	(jmpAlreadyRoot jmpTarget:
  		cogit Label))).
  	^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 LongStoreBytecode MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MethodHeaderArgCountShift MethodHeaderFlagBitPosition MethodHeaderTempCountShift MixinIndex PrimitiveExternalCallIndex PrimitiveTable StackPageReachedButUntraced StackPageTraceInvalid StackPageTraced StackPageUnreached V3PrimitiveBitsMask'
- 	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 MethodHeaderOptimizedBitShift 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!
  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).!

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."
- 	MethodHeaderOptimizedBitShift := 28 + tagBits.
  	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).
+ 	 This is used either as the `has been interpreted' flag or the `is an optimized method' flag; the
+ 	 latter if this is a Sista VM."
+ 	MethodHeaderFlagBitPosition := 28 + tagBits!
- 	"The position of the unused flag bit in the method header, not including tag bit(s)"
- 	HeaderFlagBitPosition := 29!

Item was changed:
  ----- Method: StackInterpreter>>isOptimizedMethod: (in category 'compiled methods') -----
  isOptimizedMethod: header
  	<api>
+ 	<option: #SistaVM>
+ 	^header >> MethodHeaderFlagBitPosition anyMask: 1!
- 	^ (header >> MethodHeaderOptimizedBitShift bitAnd: 1) = 1 !



More information about the Vm-dev mailing list