[Vm-dev] VM Maker: VMMaker.oscog-cb.1770.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 6 01:31:57 UTC 2016


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1770.mcz

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

Name: VMMaker.oscog-cb.1770
Author: cb
Time: 5 April 2016, 6:28:46.687 pm
UUID: 0c623bff-4d52-436e-8ce8-20e48a36f265
Ancestors: VMMaker.oscog-cb.1769

block creation side of full block closure scheme.

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

Item was added:
+ ----- Method: CoInterpreter>>pushFullClosureNumArgs:copiedValues:compiledBlock:receiverIsOnStack: (in category 'stack bytecodes') -----
+ pushFullClosureNumArgs: numArgs copiedValues: numCopiedArg compiledBlock: compiledBlock receiverIsOnStack: receiverIsOnStack
+ 	"The compiler has pushed the values to be copied, if any. The receiver has been pushed on stack before if specified. 
+ 	 Create a Closure with space for the copiedValues and pop numCopied values off the stack into the closure.
+ 	 Sets outerContext, compiledBlock, numArgs and receiver as specified.."
+ 	<inline: true>
+ 	| numCopied newClosure context startIndex |
+ 	"No need to record the pushed copied values in the outerContext."
+ 	context := self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop).
+ 	newClosure := self
+ 					fullClosureIn: context 
+ 					numArgs: numArgs 
+ 					numCopiedValues: numCopiedArg 
+ 					compiledBlock: compiledBlock.
+ 	cogit recordSendTrace ifTrue:
+ 		[self recordTrace: TraceBlockCreation thing: newClosure source: TraceIsFromInterpreter].
+ 	receiverIsOnStack
+ 		ifFalse: 
+ 			[ startIndex := FullClosureFirstCopiedValueIndex.
+ 			   objectMemory storePointerUnchecked: FullClosureReceiverIndex
+ 				ofObject: newClosure
+ 				withValue: self receiver.
+ 			numCopied := numCopiedArg ]
+ 		ifTrue:
+ 			[ startIndex := FullClosureReceiverIndex.
+ 			numCopied := numCopiedArg + 1 ].
+ 	numCopied > 0 ifTrue:
+ 		[0 to: numCopied - 1 do:
+ 			[ :i |
+ 			"Assume: have just allocated a new BlockClosure; it must be young.
+ 			 Thus, can use unchecked stores."
+ 			 objectMemory storePointerUnchecked: i + startIndex
+ 				ofObject: newClosure
+ 				withValue: (self internalStackValue: numCopied - i - 1)].
+ 		 self internalPop: numCopied].
+ 	self fetchNextBytecode.
+ 	self internalPush: newClosure!

Item was changed:
  ----- Method: CoInterpreter>>startPCOrNilOfLiteral:in: (in category 'cog jit support') -----
  startPCOrNilOfLiteral: lit in: aMethodObj
  	"Answer the startPC of lit if it is a (clean) block in aMethodObj, otherwise answer nil."
  	<api>
  	| outerContext |
  	((objectMemory isNonImmediate: lit)
  	 and: [(objectMemory formatOf: lit) = objectMemory indexablePointersFormat
+ 	 and: [(objectMemory numSlotsOf: lit) >= ClosureFirstCopiedValueIndex]]) ifFalse:
- 	 and: [(objectMemory numSlotsOf: lit) >= ClosureCopiedValuesIndex]]) ifFalse:
  		[^nil].
  	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: lit.
  	(objectMemory isContext: outerContext) ifFalse:
  		[^nil].
  	aMethodObj ~~ (objectMemory fetchPointer: MethodIndex ofObject: outerContext) ifTrue:
  		[^nil].
  	^self quickFetchInteger: ClosureStartPCIndex ofObject: lit!

Item was changed:
  ----- Method: ObjectMemory class>>initializeSpecialObjectIndices (in category 'initialization') -----
  initializeSpecialObjectIndices
  	"Initialize indices into specialObjects array."
  
  	NilObject := 0.
  	FalseObject := 1.
  	TrueObject := 2.
  	SchedulerAssociation := 3.
  	ClassBitmap := 4.
  	ClassSmallInteger := 5.
  	ClassByteString := ClassString := 6. "N.B.  Actually class ByteString"
  	ClassArray := 7.
  	"SmalltalkDictionary := 8."  "Do not delete!!"
  	ClassFloat := 9.
  	ClassMethodContext := 10.
  	ClassBlockContext := 11.
  	ClassPoint := 12.
  	ClassLargePositiveInteger := 13.
  	TheDisplay := 14.
  	ClassMessage := 15.
  	"ClassCompiledMethod := 16. unused by the VM"
  	TheLowSpaceSemaphore := 17.
  	ClassSemaphore := 18.
  	ClassCharacter := 19.
  	SelectorDoesNotUnderstand := 20.
  	SelectorCannotReturn := 21.
  	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
  	SpecialSelectors := 23.
  	CharacterTable := 24.
  	SelectorMustBeBoolean := 25.
  	ClassByteArray := 26.
  	"ClassProcess := 27. unused"
  	CompactClasses := 28.
  	TheTimerSemaphore := 29.
  	TheInterruptSemaphore := 30.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
+ 	ClassFullBlockClosure := 37. "Was BlockContextProto := 37."
- 	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
  	ClassMutex := 39.
  	"Was: ClassTranslatedMethod := 40."
  	ProcessInExternalCodeTag := 40.
  	TheFinalizationSemaphore := 41.
  	ClassLargeNegativeInteger := 42.
  
  	ClassExternalAddress := 43.
  	ClassExternalStructure := 44.
  	ClassExternalData := 45.
  	ClassExternalFunction := 46.
  	ClassExternalLibrary := 47.
  
  	SelectorAboutToReturn := 48.
  	SelectorRunWithIn := 49.
  
  	SelectorAttemptToAssign := 50.
  	"PrimErrTableIndex := 51. in VMClass class>>initializePrimitiveErrorCodes"
  	ClassAlien := 52.
  	SelectorInvokeCallback := 53.
  	ClassUnsafeAlien := 54.
  
  	ClassWeakFinalizer := 55.
  
  	ForeignCallbackProcess := 56.
  
  	SelectorUnknownBytecode := 57.
  	SelectorCounterTripped := 58.
  	SelectorSistaTrap := 59
  !

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeCompactClassIndices (in category 'class initialization') -----
  initializeCompactClassIndices
  	"Reuse the compact class indices to name known classIndices.
  	 This helps reduce the churn in the interpreters."
  	"c.f. SpurBootstrap>>defineKnownClassIndices"
  	FirstValidClassIndex :=
  	ClassLargeNegativeIntegerCompactIndex := 32.
  	ClassLargePositiveIntegerCompactIndex := 33.
  	ClassFloatCompactIndex := 34.
  
  	ClassMessageCompactIndex := 35.
  	ClassMethodContextCompactIndex := 36.
  	ClassBlockContextCompactIndex := 0.
  	ClassBlockClosureCompactIndex := 37.
+ 	ClassFullBlockClosureCompactIndex := 38.
  
  	ClassByteArrayCompactIndex := 50.
  	ClassArrayCompactIndex := 51.
  	ClassByteStringCompactIndex := 52.
  	ClassBitmapCompactIndex := 53!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSistaV1 (in category 'initialization') -----
  initializeBytecodeTableForSistaV1
  	"See e.g. the cass comment for EncoderForSistaV1"
  	"StackInterpreter initializeBytecodeTableForSistaV1"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForSistaV1.
  	BytecodeSetHasDirectedSuperSend := true.
  
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 pushConstantTrueBytecode)
  		( 78	 pushConstantFalseBytecode)
  		( 79	 pushConstantNilBytecode)
  		( 80	 pushConstantZeroBytecode)
  		( 81	 pushConstantOneBytecode)
  		( 82	 extPushPseudoVariable)
  		( 83	 duplicateTopBytecode)
  	
  		( 84 87	unknownBytecode)
  		( 88	returnReceiver)
  		( 89	returnTrue)
  		( 90	returnFalse)
  		( 91	returnNil)
  		( 92	returnTopFromMethod)
  		( 93	returnNilFromBlock)
  		( 94	returnTopFromBlock)
  		( 95	extNopBytecode)
  
  		( 96	 bytecodePrimAdd)
  		( 97	 bytecodePrimSubtract)
  		( 98	 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
  		( 99	 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
  		(100	 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(101	 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(102	 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
  		(103	 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
  		(104	 bytecodePrimMultiply)
  		(105	 bytecodePrimDivide)
  		(106	 bytecodePrimMod)
  		(107	 bytecodePrimMakePoint)
  		(108	 bytecodePrimBitShift)
  		(109	 bytecodePrimDiv)
  		(110	 bytecodePrimBitAnd)
  		(111	 bytecodePrimBitOr)
  
  		(112	 bytecodePrimAt)
  		(113	 bytecodePrimAtPut)
  		(114	 bytecodePrimSize)
  		(115	 bytecodePrimNext)		 "i.e. a 0 arg special selector"
  		(116	 bytecodePrimNextPut)		 "i.e. a 1 arg special selector"
  		(117	 bytecodePrimAtEnd)
  		(118	 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
  		(119	 bytecodePrimClass)
  		(120	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(121	 bytecodePrimValue)
  		(122	 bytecodePrimValueWithArg)
  		(123	 bytecodePrimDo)			"i.e. a 1 arg special selector"
  		(124	 bytecodePrimNew)			"i.e. a 0 arg special selector"
  		(125	 bytecodePrimNewWithArg)	"i.e. a 1 arg special selector"
  		(126	 bytecodePrimPointX)		"i.e. a 0 arg special selector"
  		(127	 bytecodePrimPointY)		"i.e. a 0 arg special selector"
  
  		(128 143	sendLiteralSelector0ArgsBytecode)
  		(144 159	sendLiteralSelector1ArgBytecode)
  		(160 175	sendLiteralSelector2ArgsBytecode)
  
  		(176 183	shortUnconditionalJump)
  		(184 191	shortConditionalJumpTrue)
  		(192 199	shortConditionalJumpFalse)
  	
  		(200 207	storeAndPopReceiverVariableBytecode)
  		(208 215	storeAndPopTemporaryVariableBytecode)
  		(216		popStackBytecode)
  		(217		unconditionnalTrapBytecode)
  
  		(218 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		longPushTemporaryVariableBytecode)
  		(230		pushClosureTempsBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
  		(236		unknownBytecode)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
  		(240		extSistaStoreAndPopReceiverVariableBytecode)
  		(241		extSistaStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extSistaStoreReceiverVariableBytecode)
  		(244		extSistaStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		unknownBytecode) "reserved for Push Float"
  
  		(250		extPushClosureBytecode)
  		(251		extPushRemoteTempOrInstVarLongBytecode)
  		(252		extStoreRemoteTempOrInstVarLongBytecode)
  		(253		extStoreAndPopRemoteTempOrInstVarLongBytecode)
  				
  		(254		extJumpIfNotInstanceOfBehaviorsOrPopBytecode)
  
+ 		(255		extPushFullClosureBytecode)
- 		(255		unknownBytecode)
  	)!

Item was changed:
  ----- Method: StackInterpreter class>>initializeContextIndices (in category 'initialization') -----
  initializeContextIndices
  	"Class MethodContext"
  	SenderIndex := 0.
  	InstructionPointerIndex := 1.
  	StackPointerIndex := 2.
  	MethodIndex := 3.
  	ClosureIndex := 4. "N.B. Called receiverMap in old images, closureOrNil in newer images."
  	ReceiverIndex := 5.
  	CtxtTempFrameStart := 6.
  
  	SmallContextSlots := CtxtTempFrameStart + 16.  "16 indexable fields"
  	"Large contexts have 56 indexable fields.  Max with single header word of ObjectMemory [but not SpurMemoryManager ;-)]."
  	LargeContextSlots := CtxtTempFrameStart + 56.
  	
  	"Including the header size in these sizes is problematic for multiple memory managers,
  	 so we don't use them.  Set to #bogus for error checking."
  	SmallContextSize := #bogus.
  	LargeContextSize := #bogus.
  
  	"Class BlockClosure"
  	ClosureOuterContextIndex := 0.
  	ClosureStartPCIndex := 1.
  	ClosureNumArgsIndex := 2.
  	ClosureFirstCopiedValueIndex := 3.
+ 	
+ 	"Class FullBlockClosure, outercontext and numArgs index are shared with the BlockClosure class."	
+ 	FullClosureCompiledBlockIndex := 1.
+ 	FullClosureReceiverIndex := 3.
+ 	FullClosureFirstCopiedValueIndex := 4.!
- 	ClosureCopiedValuesIndex := 3!

Item was added:
+ ----- Method: StackInterpreter>>extPushFullClosureBytecode (in category 'stack bytecodes') -----
+ extPushFullClosureBytecode
+ 	"255		11111111	xxxxxxxx	siyyyyyy	
+ 		push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) 
+ 		numCopied yyyyyy 
+ 		receiverOnStack: s = 1 
+ 		(i reserved for needsOuterContext: i = 1)
+ 	 The compiler has pushed the values to be copied, if any. The receiver has been pushed on stack before if specified. 
+ 	 Create a Closure with space for the copiedValues and pop numCopied values off the stack into the closure.
+ 	 Sets outerContext, compiledBlock, numArgs and receiver as specified.."
+ 	| compiledBlockLiteralIndex compiledBlock byte numArgs numCopied receiverIsOnStack |
+ 	compiledBlockLiteralIndex := self fetchByte + (extA << 8).
+ 	extA := 0.
+ 	compiledBlock := self literal: compiledBlockLiteralIndex.
+ 	self assert: (objectMemory isOopCompiledMethod: compiledBlock).
+ 	numArgs := self argumentCountOf: compiledBlock.
+ 	byte := self fetchByte.
+ 	numCopied := byte bitAnd: 1<< 6 - 1.
+ 	receiverIsOnStack := byte anyMask: 1 << 7.
+ 	self pushFullClosureNumArgs: numArgs copiedValues: numCopied compiledBlock: compiledBlock receiverIsOnStack: receiverIsOnStack!

Item was added:
+ ----- Method: StackInterpreter>>fullClosureIn:numArgs:numCopiedValues:compiledBlock: (in category 'control primitives') -----
+ fullClosureIn: context numArgs: numArgs numCopiedValues: numCopied compiledBlock: compiledBlock 
+ 	| newClosure |
+ 	<inline: true>
+ 	self assert: ClassFullBlockClosureCompactIndex ~= 0.
+ 	ClassFullBlockClosureCompactIndex ~= 0
+ 		ifTrue:
+ 			[newClosure := objectMemory
+ 								eeInstantiateSmallClassIndex: ClassFullBlockClosureCompactIndex
+ 								format: objectMemory indexablePointersFormat
+ 								numSlots: ClosureFirstCopiedValueIndex + numCopied]
+ 		ifFalse:
+ 			[newClosure := objectMemory
+ 								eeInstantiateSmallClass: (objectMemory splObj: ClassFullBlockClosure)
+ 								numSlots: FullClosureFirstCopiedValueIndex + numCopied].
+ 	"Assume: have just allocated a new closure; it must be young. Thus, can use unchecked stores."
+ 	objectMemory
+ 		storePointerUnchecked: ClosureOuterContextIndex ofObject: newClosure withValue: context;
+ 		storePointerUnchecked: FullClosureCompiledBlockIndex ofObject: newClosure withValue: compiledBlock;
+ 		storePointerUnchecked: ClosureNumArgsIndex ofObject: newClosure withValue: (objectMemory integerObjectOf: numArgs).
+ 	^newClosure!

Item was changed:
  SharedPool subclass: #VMObjectIndices
  	instanceVariableNames: ''
+ 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFullBlockClosure ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess FullClosureCompiledBlockIndex FullClosureFirstCopiedValueIndex FullClosureReceiverIndex HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorSistaTrap SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
- 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureCopiedValuesIndex ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorSistaTrap SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMObjectIndices commentStamp: '<historical>' prior: 0!
  I am a shared pool for the constants that define object layout and well-known objects shared between the object memories (e.g. ObjectMemory, NewObjectMemory), the interpreters (e.g. StackInterpreter, CoInterpreter) and the object representations (e.g. ObjectRepresentationForSqueakV3).
  
  self classPool declare: #Foo from: StackInterpreter classPool
  
  (ObjectMemory classPool keys select: [:k| (k beginsWith: 'Class') and: [(k endsWith: 'Index') not]]) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!

Item was changed:
  VMBasicConstants subclass: #VMSqueakClassIndices
  	instanceVariableNames: ''
+ 	classVariableNames: 'ClassArrayCompactIndex ClassBitmapCompactIndex ClassBlockClosureCompactIndex ClassBlockContextCompactIndex ClassByteArrayCompactIndex ClassByteStringCompactIndex ClassFloatCompactIndex ClassFullBlockClosureCompactIndex ClassLargeNegativeIntegerCompactIndex ClassLargePositiveIntegerCompactIndex ClassMessageCompactIndex ClassMethodContextCompactIndex'
- 	classVariableNames: 'ClassArrayCompactIndex ClassBitmapCompactIndex ClassBlockClosureCompactIndex ClassBlockContextCompactIndex ClassByteArrayCompactIndex ClassByteStringCompactIndex ClassFloatCompactIndex ClassLargeNegativeIntegerCompactIndex ClassLargePositiveIntegerCompactIndex ClassMessageCompactIndex ClassMethodContextCompactIndex'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!



More information about the Vm-dev mailing list