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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 31 11:30:27 UTC 2016


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

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

Name: VMMaker.oscog-cb.1925
Author: cb
Time: 31 August 2016, 1:27:47.355435 pm
UUID: b77be8d3-8f56-4e47-a88f-960dc3050d55
Ancestors: VMMaker.oscog-cb.1924

assertion improvement to make the simulator more robust.

Added immutability check in maybe context object store in jitted code.

Added an annotation for inst var store in the SistaV1 bytecode set to tip the JIT if the mutated object may be a context or not.

StackSpur VM are now generated with dual bytecode set support.

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

Item was changed:
  ----- Method: StackInterpreter>>objCouldBeClassObj: (in category 'debug support') -----
  objCouldBeClassObj: objOop
  	"Answer if objOop looks like a class object.  WIth Spur be lenient if the object doesn't
  	 yet have a hash (i.e. is not yet in the classTable), and accept forwarding pointers."
  	<api>
  	<inline: false>
  	| fieldOop |
  	^(objectMemory isPointersNonImm: objOop)
  	  and: [(objectMemory numSlotsOfAny: objOop) > InstanceSpecificationIndex
  	  and: [fieldOop := objectMemory fetchPointer: SuperclassIndex ofObject: objOop.
+ 			((objectMemory addressCouldBeObj: fieldOop)
- 			((objectMemory isNonImmediate: fieldOop)
  			and:[ (objectMemory isPointersNonImm: fieldOop)
  				or: [(objectMemory isOopForwarded: fieldOop)
  					and: [objectMemory isPointers: (objectMemory followForwarded: fieldOop)]]])
  	  and: [fieldOop := objectMemory fetchPointer: MethodDictionaryIndex ofObject: objOop.
+ 			((objectMemory addressCouldBeObj: fieldOop)
- 			((objectMemory isNonImmediate: fieldOop)
  			and:[ (objectMemory isPointersNonImm: fieldOop)
  				or: [(objectMemory isOopForwarded: fieldOop)
  					and: [objectMemory isPointers: (objectMemory followForwarded: fieldOop)]]])
  	  and: [(objectMemory isIntegerObject: (objectMemory fetchPointer: InstanceSpecificationIndex ofObject: objOop))]]]]!

Item was changed:
  ----- Method: StackInterpreter>>shortPrint: (in category 'simulation') -----
  shortPrint: oop
  	<doNotGenerate>
  	| name classOop |
  	(objectMemory isImmediate: oop) ifTrue:
  		[(objectMemory isImmediateCharacter: oop) ifTrue:
  			[^(objectMemory characterValueOf: oop) < 256
  				ifTrue:
  					['=$', (objectMemory characterValueOf: oop) printString,
  					' (', (String with: (Character value: (objectMemory characterValueOf: oop))), ')']
  				ifFalse:
  					['=$', (objectMemory characterValueOf: oop) printString, '(???)']].
  		(objectMemory isIntegerObject: oop) ifTrue:
  			[^'=', (objectMemory integerValueOf: oop) printString,
  			' (', (objectMemory integerValueOf: oop) hex, ')'].
  		(objectMemory isImmediateFloat: oop) ifTrue:
  			[^ '=', (objectMemory floatValueOf: oop) printString, ' (', oop hex, ')'].
  		^'= UNKNOWN IMMEDIATE', ' (', (objectMemory integerValueOf: oop) hex, ')'].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^(oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  			ifTrue: [' is misaligned']
  			ifFalse: [self whereIs: oop]].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[^' is a free chunk of size ', (objectMemory sizeOfFree: oop) printString,
  			(objectMemory hasSpurMemoryManagerAPI
  				ifTrue: [' 0th: ', (objectMemory fetchPointer: 0 ofFreeChunk: oop) hex]
  				ifFalse: [''])].
  	(objectMemory isForwarded: oop) ifTrue:
  		[^' is a forwarded object to ', (objectMemory followForwarded: oop) hex,
  			' of slot size ', (objectMemory numSlotsOfAny: oop) printString].
  	(objectMemory isFloatInstance: oop) ifTrue:
  		[^'=', (objectMemory dbgFloatValueOf: oop) printString].
  	oop = objectMemory nilObject ifTrue:
  		[^'nil'].
  	oop = objectMemory falseObject ifTrue:
  		[^'false'].
  	oop = objectMemory trueObject ifTrue:
  		[^'true'].
  
  	classOop := objectMemory fetchClassOfNonImm: oop.
  	((self objCouldBeClassObj: oop)
  	 and: [(objectMemory numSlotsOf: classOop) = metaclassNumSlots]) ifTrue:
  		[^'class ', (self nameOfClass: oop)].
  	name := self nameOfClass: classOop.
  	name size = 0 ifTrue: [name := '??'].
  	(#('String'  'ByteString') includes: name) ifTrue:
  		[^(self stringOf: oop) printString].
  	(#('Symbol'  'ByteSymbol') includes: name) ifTrue:
  		[^'#', (self stringOf: oop)].
  	name = 'Character' ifTrue: "SpurMemoryManager has immediate Characters (see above); ObjectMemory does not"
  		[^'=', (Character value: (objectMemory integerValueOf: 
  				(objectMemory fetchPointer: 0 ofObject: oop))) printString].
  
  	"Try to spot association-like things; they're all subclasses of LookupKey"
  	((objectMemory isPointersNonImm: oop)
  	 and: [classOop ~= objectMemory nilObject
  	 and: [((objectMemory instanceSizeOf: classOop) between: ValueIndex + 1 and: ValueIndex + 2)
+ 	 and: [(objectMemory addressCouldBeObj: (objectMemory fetchPointer: KeyIndex ofObject: oop))]
+ 	 and: [(objectMemory isBytesNonImm: (objectMemory fetchPointer: KeyIndex ofObject: oop))]]]) ifTrue:
- 	 and: [(objectMemory isBytes: (objectMemory fetchPointer: KeyIndex ofObject: oop))]]]) ifTrue:
  		[| classLookupKey |
  		 classLookupKey := objectMemory fetchClassOfNonImm: (objectMemory splObj: SchedulerAssociation).
  		 [classLookupKey = objectMemory nilObject ifTrue:
  			[^(('AEIOU' includes: name first) ifTrue: ['an '] ifFalse: ['a ']), name].
  		  (objectMemory instanceSizeOf: classLookupKey) = (KeyIndex + 1)] whileFalse:
  			[classLookupKey := self superclassOf: classLookupKey].
  		 (self includesBehavior: classOop ThatOf: classLookupKey) ifTrue:
  			[^(('AEIOU' includes: name first) ifTrue: ['an '] ifFalse: ['a ']), name,
  				' ', (self shortPrint: (objectMemory fetchPointer: KeyIndex ofObject: oop)),
  				' -> ',
  				(objectMemory fetchPointer: ValueIndex ofObject: oop) hex8]].
  
  	^(('AEIOU' includes: name first) ifTrue: ['an '] ifFalse: ['a ']), name!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genGenericStorePop:MaybeContextSlotIndex:needsStoreCheck:needsRestoreRcvr:needsImmutabilityCheck: (in category 'bytecode generator stores') -----
  genGenericStorePop: popBoolean MaybeContextSlotIndex: slotIndex needsStoreCheck: needsStoreCheck needsRestoreRcvr: needsRestoreReceiver needsImmutabilityCheck: needsImmCheck
  	"Generates a store into an object that *may* be a context.
  	Multiple settings:
  	- needsStoreCheck (young into old object check)
  	- needRestoreRcvr (ensures the recevier is live across the store)
  	- needsImmCheck (do the call-back if the receiver is immutable)"
  	<inline: true>
- 	| jmpSingle jmpDone |
  	<var: #jmpSingle type: #'AbstractInstruction *'>
  	<var: #jmpDone type: #'AbstractInstruction *'>
+ 	<var: #mutableJump type: #'AbstractInstruction *'>
+ 	<var: #immutabilityFailure type: #'AbstractInstruction *'>
+ 	| immutabilityFailure mutableJump |
  	"The reason we need a frame here is that assigning to an inst var of a context may
  	 involve wholesale reorganization of stack pages, and the only way to preserve the
  	 execution state of an activation in that case is if it has a frame."
- 	"Context stores do not require Imm checks as contexts can't be immutable"
  	self assert: needsFrame.
+ 	self 
+ 		cppIf: IMMUTABILITY
+ 		ifTrue:
+ 			[needsImmCheck
+ 				ifTrue: 
+ 					[mutableJump := objectRepresentation genJumpMutable: ReceiverResultReg scratchReg: TempReg.
+ 					 objectRepresentation genStoreTrampolineCall: slotIndex.
+ 					 needsRestoreReceiver ifTrue: [ self putSelfInReceiverResultReg ].
+ 					 immutabilityFailure := self Jump: 0.
+ 					 mutableJump jmpTarget: self Label.]].
  	self ssPop: 1.
  	self ssAllocateCallReg: ClassReg and: SendNumArgsReg. "for ceStoreContextInstVarTrampoline"
  	self ssPush: 1.
  	objectRepresentation
  		genLoadSlot: SenderIndex
  		sourceReg: ReceiverResultReg
  		destReg: TempReg.
  	self ssStoreAndReplacePop: popBoolean toReg: ClassReg.
+ 	self ssFlushTo: simStackPtr.
- 	jmpSingle := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	self MoveCq: slotIndex R: SendNumArgsReg.
  	self CallRT: ceStoreContextInstVarTrampoline.
- 	jmpDone := self Jump: 0.
- 	jmpSingle jmpTarget: self Label.
  	self 
  		cppIf: IMMUTABILITY
  		ifTrue:
+ 			[needsImmCheck ifTrue:[immutabilityFailure jmpTarget: self Label]].
- 			[needsImmCheck
- 				ifTrue: 
- 					[objectRepresentation 
- 						genStoreWithImmutabilityCheckSourceReg: ClassReg 
- 						slotIndex: slotIndex 
- 						destReg: ReceiverResultReg 
- 						scratchReg: TempReg 
- 						needsStoreCheck: needsStoreCheck 
- 						needRestoreRcvr: needsRestoreReceiver.
- 					jmpDone jmpTarget: self Label.
- 					^0]].
- 	objectRepresentation
- 			genStoreSourceReg: ClassReg
- 			slotIndex: slotIndex
- 			destReg: ReceiverResultReg
- 			scratchReg: TempReg
- 			inFrame: true
- 			needsStoreCheck: needsStoreCheck.
- 	jmpDone jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSistaExtStoreAndPopReceiverVariableBytecodePopBoolean: (in category 'bytecode generators') -----
+ genSistaExtStoreAndPopReceiverVariableBytecodePopBoolean: popBoolean
- genSistaExtStoreAndPopReceiverVariableBytecodePopBoolean: boolean
  	<inline: true>
+ 	| index needsStoreCheck needsImmCheck maybeContext |
- 	| index needsStoreCheck needsImmCheck |
  	needsStoreCheck := self sistaNeedsStoreCheck.
  	needsImmCheck := self extBSpecifiesImmCheck.
+ 	"Long form and short form exist for popInto. Only the long form exists for store.
+ 	Store have an explicit flag to mark context accessing, while popInto context accessing are done through the long form,
+ 	hence generate the context form if the flag is set or if this is a popInto."
+ 	maybeContext := popBoolean or: [self extBSpecifiesMaybeContext].
  	extB := 0.
  	index := byte1 + (extA << 8).
  	extA := 0.
+ 	^((coInterpreter isWriteMediatedContextInstVarIndex: index) and: [maybeContext])
- 	^(coInterpreter isWriteMediatedContextInstVarIndex: index)
  		ifTrue: [self 
+ 				genStorePop: popBoolean 
- 				genStorePop: boolean 
  				MaybeContextReceiverVariable: index 
  				needsStoreCheck: needsStoreCheck 
  				needsImmutabilityCheck: needsImmCheck]
  		ifFalse: [self 
+ 				 genStorePop: popBoolean 
- 				 genStorePop: boolean 
  				 ReceiverVariable: index 
  				 needsStoreCheck: needsStoreCheck 
  				 needsImmutabilityCheck: needsImmCheck]!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurStackVM (in category 'configurations') -----
  generateSqueakSpurStackVM
  	"No primitives since we can use those from the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(ObjectMemory Spur32BitMemoryManager
+ 				FailImbalancedPrimitives false
+ 				MULTIPLEBYTECODESETS true
+ 				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
- 				FailImbalancedPrimitives false)
  		to: (FileDirectory default pathFromURI: self sourceTree, '/spurstacksrc')
  		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!



More information about the Vm-dev mailing list