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

commits at source.squeak.org commits at source.squeak.org
Tue Jul 12 21:12:09 UTC 2016


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

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

Name: VMMaker.oscog-eem.1902
Author: eem
Time: 12 July 2016, 2:10:27.739315 pm
UUID: d5860bb5-b41c-4337-90d4-c2abc979248d
Ancestors: VMMaker.oscog-topa.1901

Add support for inline unchecked pointer basicNew, inline prim #1011.

Fix slips in isUnannotatableConstant: and ssTopNeedsStoreCheck to include/exclude immediates respectively.

In-image compilation:
Update facade support to allow compilation of inline prim #1011.

Simulation:
Fix slip in StackInterpreter class>>initializeWithOptions: which breaks StackInterpreter launch.

Add support for recording and replaying sends to check for divergence between different runs.  See CogVMSimulator>>collectSends & CogVMSimulator>>expectSends: & the ExpectedSends class var.

In 1902 Walter Sutton (in the United States) and Theodor Boveri (in Germany) independently develop the Boveri-Sutton chromosome theory, explaining the mechanism underlying the laws of Mendelian inheritance by identifying chromosomes as the carriers of genetic material, Bertrand Russell writes to Gottlob Frege informing him of the problem in naive set theory that will become known as Russell's paradox, and William Bayliss and Ernest Starling make the first discovery of a hormone, secretin.

=============== Diff against VMMaker.oscog-topa.1901 ===============

Item was added:
+ ----- Method: Bitmap class>>defaultIntegerBaseInDebugger (in category '*VMMaker-debugger') -----
+ defaultIntegerBaseInDebugger
+ 	^16!

Item was added:
+ ----- Method: CogObjectRepresentation>>genGetInstanceOf:into:initializingIf: (in category 'bytecode generator support') -----
+ genGetInstanceOf: classObj into: destReg initializingIf: initializeInstance
+ 	"Create an instance of classObj and assign it to destReg, initializing the instance
+ 	 if initializeInstance is true with nil or 0 as appropriate This is for inline primitives.
+ 	 Assume there is sufficient space in new space to complete the operation.
+ 	 Answer zero on success."
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentation>>isUnannotatableConstant: (in category 'compile abstract instructions') -----
  isUnannotatableConstant: simStackEntry
  	<inline: true>
  	<var: 'simStackEntry' type: #'CogSimStackEntry *'>
+ 	^simStackEntry type = SSConstant 
+ 	  and: [(objectMemory isImmediate: simStackEntry constant)
+ 		or: [(self shouldAnnotateObjectReference: simStackEntry constant) not]]!
- 	^ simStackEntry type = SSConstant 
- 		and: [(self shouldAnnotateObjectReference: simStackEntry constant) not ]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genGetInstanceOf:into:initializingIf: (in category 'bytecode generator support') -----
+ genGetInstanceOf: classObj into: destReg initializingIf: initializeInstance
+ 	"Create an instance of classObj and assign it to destReg, initializing the instance
+ 	 if initializeInstance is true with nil or 0 as appropriate This is for inline primitives.
+ 	 Assume there is sufficient space in new space to complete the operation.
+ 	 Answer zero on success."
+ 	| classIndex classFormat header slots |
+ 	((objectMemory isNonImmediate: classObj)
+ 	 and: [(coInterpreter objCouldBeClassObj: classObj)
+ 	 and: [(classIndex := objectMemory rawHashBitsOf: classObj) ~= 0
+ 	 and: [(objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClassFormat: (classFormat := objectMemory formatOfClass: classObj)))
+ 	 and: [(slots := objectMemory fixedFieldsOfClassFormat: classFormat) < objectMemory numSlotsMask]]]]) ifFalse:
+ 		[^UnimplementedOperation].
+ 
+ 	header := objectMemory
+ 					headerForSlots: slots
+ 					format: (objectMemory instSpecOfClassFormat: classFormat)
+ 					classIndex: classIndex.
+ 
+ 	cogit MoveAw: objectMemory freeStartAddress R: destReg.
+ 	self genStoreHeader: header intoNewInstance: destReg using: TempReg.
+ 	cogit
+ 		LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: slots) r: destReg R: TempReg;
+ 		MoveR: TempReg Aw: objectMemory freeStartAddress.
+ 	(initializeInstance and: [slots > 0]) ifTrue:
+ 		[cogit genMoveConstant: objectMemory nilObject R: TempReg.
+ 		 0 to: slots - 1 do:
+ 			[:i| cogit MoveR: TempReg
+ 					Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
+ 					r: destReg]].
+ 	^0!

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue expectedSends expecting'
+ 	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends'
- 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue'
- 	classVariableNames: 'ByteCountsPerMicrosecond'
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was added:
+ ----- Method: CogVMSimulator class>>expectedSends (in category 'debug support') -----
+ expectedSends
+ 	^ExpectedSends!

Item was added:
+ ----- Method: CogVMSimulator>>collectSends (in category 'debug support') -----
+ collectSends
+ 	expectedSends := WriteStream on: (Array new: 65536).
+ 	expecting := false!

Item was added:
+ ----- Method: CogVMSimulator>>expectSends: (in category 'debug support') -----
+ expectSends: anArray
+ 	expectedSends := ReadStream on: anArray.
+ 	expecting := true!

Item was changed:
+ ----- Method: CogVMSimulator>>recordTrace:thing:source: (in category 'debug support') -----
- ----- Method: CogVMSimulator>>recordTrace:thing:source: (in category 'multi-threading simulation switch') -----
  recordTrace: classOrInteger thing: selector source: source
  	"This method includes or excludes CoInterpreterMT methods as required.
+ 	 It used to be auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate.
+ 	 Now checks for or collects expectedSends."
+ 	(expectedSends == nil
+ 	 or: [objectMemory isIntegerObject: classOrInteger]) ifFalse:
+ 		[expecting
+ 			ifTrue:
+ 				[expectedSends peek ~~ selector ifTrue: [self halt].
+ 				 expectedSends next]
+ 			ifFalse:
+ 				[expectedSends nextPut: selector]].
+ 	
- 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
- 
  	^self perform: #recordTrace:thing:source:
  		withArguments: {classOrInteger. selector. source}
  		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>fixedFieldsOfClassFormat: (in category 'cog jit support') -----
+ fixedFieldsOfClassFormat: classFormat
+ 	^objectMemory fixedFieldsOfClassFormat: classFormat!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>freeObject: (in category 'accessing') -----
+ freeObject: anObj!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>objCouldBeClassObj: (in category 'cog jit support') -----
+ objCouldBeClassObj: obj
+ 	^(self objectForOop: obj) isBehavior!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>remoteIsInstVarAccess (in category 'cog jit support') -----
+ remoteIsInstVarAccess
+ 	^coInterpreter remoteIsInstVarAccess!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>formatOfClass: (in category 'accessing') -----
+ formatOfClass: classOop 
+ 	^(self objectForOop: classOop) format!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>instSpecOfClassFormat: (in category 'cog jit support') -----
+ instSpecOfClassFormat: classFormat
+ 	^objectMemory instSpecOfClassFormat: classFormat!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>isFixedSizePointerFormat: (in category 'cog jit support') -----
+ isFixedSizePointerFormat: formatOop
+ 	^objectMemory isFixedSizePointerFormat: formatOop!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>rawHashBitsOf: (in category 'accessing') -----
+ rawHashBitsOf: obj
+ 	^(self objectForOop: obj) identityHash!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ssStorePop:toPreferredReg: (in category 'simulation stack') -----
  ssStorePop: popBoolean toPreferredReg: preferredReg
  	"Store or pop the top simulated stack entry to a register.
  	 Use preferredReg if the entry is not itself a register.
  	 Answer the actual register the result ends up in."
  	| actualReg |
  	actualReg := preferredReg.
  	self ssTop type = SSRegister ifTrue: 
+ 		[self assert: (self ssTop liveRegister = NoReg
+ 					  or: [self ssTop liveRegister = self ssTop register]).
- 		[self assert: self ssTop liveRegister = self ssTop register.
  		self assert: self ssTop spilled not].
  	self ssTop liveRegister ~= NoReg ifTrue:
  		[actualReg := self ssTop liveRegister].
  	self ssStorePop: popBoolean toReg: actualReg. "generates nothing if ssTop is already in actualReg"
  	^ actualReg!

Item was changed:
  ----- Method: SistaCogit>>genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'bytecode generators') -----
  genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode
  	"SistaV1: *	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
  								
  	| reg literal distance targetFixUp |
  	
  	"We loose the information of in which register is stack top 
  	when jitting the branch target so we need to flush everything. 
  	We could use a fixed register here...."
  	reg := self allocateRegForStackEntryAt: 0.
  	self ssTop popToReg: reg.
  	self ssFlushTo: simStackPtr. "flushed but the value is still in reg"
+ 
+ 	self genPopStackBytecode.
  	
  	literal := self getLiteral: (extA * 256 + byte1).
  	extA := 0.
  	distance := extB * 256 + byte2.
  	extB := 0.
  	
  	targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'.
  		
  	(objectMemory isArrayNonImm: literal)
  		ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp]
  		ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp].
- 						
- 	self genPopStackBytecode.
  	
  	^0!

Item was changed:
  ----- Method: SpurMemoryManager>>fixedFieldsOfClassFormat: (in category 'object format') -----
  fixedFieldsOfClassFormat: classFormat
+ 	<api>
  	^classFormat bitAnd: self fixedFieldsOfClassFormatMask!

Item was changed:
  ----- Method: SpurMemoryManager>>instSpecOfClassFormat: (in category 'object format') -----
  instSpecOfClassFormat: classFormat
+ 	<api>
  	^classFormat >> self fixedFieldsFieldWidth bitAnd: self formatMask!

Item was changed:
  ----- Method: SpurMemoryManager>>isFixedSizePointerFormat: (in category 'header format') -----
  isFixedSizePointerFormat: format
+ 	<api>
  	^format <= self nonIndexablePointerFormat
  	  or: [format = self ephemeronFormat]!

Item was changed:
  ----- Method: SpurMemoryManager>>rawHashBitsOf: (in category 'header access') -----
  rawHashBitsOf: objOop
+ 	<api>
  	self flag: #endianness.
  	^(self long32At: objOop + 4) bitAnd: self identityHashHalfWordMask!

Item was changed:
  ----- Method: StackInterpreter class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"StackInterpreter initializeWithOptions: Dictionary new"
  
  	super initializeWithOptions: optionsDictionary.
+ 	(self primitivesClass withAllSuperclasses copyUpTo: StackInterpreter) do:
- 	(self primitivesClass withAllSuperclasses copyUpTo: self) do:
  		[:class| class initializationOptions: initializationOptions].
  	self initializeMiscConstants. "must precede other initialization."
  	self initializeAssociationIndex.
  	self initializeBytecodeTable.
  	self initializeCaches.
  	self initializeCharacterIndex.
  	self initializeCharacterScannerIndices.
  	self initializeClassIndices.
  	self initializeContextIndices.
  	self initializeDirectoryLookupResultCodes.
  	self initializeFrameIndices.
  	self initializeMessageIndices.
  	self initializeMethodIndices.
  	self initializePointIndices.
  	self initializePrimitiveTable.
  	self initializeSchedulerIndices.
  	self initializeSmallIntegers.
  	self initializeStreamIndices!

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 isNonImmediate: fieldOop)
  			and:[ (objectMemory isPointersNonImm: fieldOop)
  				or: [(objectMemory isOopForwarded: fieldOop)
  					and: [objectMemory isPointers: (objectMemory followForwarded: fieldOop)]]])
  	  and: [fieldOop := objectMemory fetchPointer: MethodDictionaryIndex ofObject: objOop.
  			((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>>unaryInlinePrimitive: (in category 'miscellaneous bytecodes') -----
  unaryInlinePrimitive: primIndex
  	"SistaV1:	248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
  	<option: #SistaVM>
  	| result |
  	primIndex caseOf: {
  		"1000	unchecked class"
  		[0]	->	[result := objectMemory fetchClassOf: self internalStackTop.
  				 self internalStackTopPut: result].
  		"1001	unchecked pointer numSlots"
  		[1]	->	[result := objectMemory numSlotsOf: self internalStackTop.
  				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
  		"1002	unchecked pointer basicSize"
  		[2]	->	[result := (objectMemory numSlotsOf: self internalStackTop)
  						- (objectMemory fixedFieldsOfClass: (objectMemory fetchClassOfNonImm: self internalStackTop)).
  				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
  		"1003	unchecked byte8Type format numBytes (includes CompiledMethod)"
  		[3]	->	[result := objectMemory numBytesOf: self internalStackTop.
  				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
  		"1004	unchecked short16Type format numShorts"
  		[4]	->	[result := objectMemory num16BitUnitsOf: self internalStackTop.
  				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
  		"1005	unchecked word32Type format numWords"
  		[5]	->	[result := objectMemory num32BitUnitsOf: self internalStackTop.
  				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
  		"1006	unchecked doubleWord64Type format numDoubleWords"
  		[6]	->	[result := objectMemory num64BitUnitsOf: self internalStackTop.
+ 				 self internalStackTopPut: (objectMemory integerObjectOf: result)].
+ 
+ 		"1011	unchecked fixed pointer basicNew"
+ 		[11] ->	[| classObj numSlots |
+ 				 classObj := self internalStackTop.
+ 				 numSlots := objectMemory instanceSizeOf: classObj.
+ 				 result := objectMemory eeInstantiateSmallClass: classObj numSlots: numSlots.
+ 				 (extB noMask: 1) ifTrue:
+ 					[0 to: numSlots - 1 do:
+ 						[:i| objectMemory storePointerUnchecked: i ofObject: result withValue: objectMemory nilObject]].
+ 				 extB := 0.
+ 				 self internalStackTopPut: result] }
- 				 self internalStackTopPut: (objectMemory integerObjectOf: result)] }
  	otherwise:
  		[localIP := localIP - 3.
  		 self respondToUnknownBytecode]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>extBSpecifiesInitializeInstance (in category 'bytecode generators') -----
+ extBSpecifiesInitializeInstance
+ 	"This is a negative; do not intialize if 1 is present in extB.  This is also the no-store-check bit."
+ 	<inline: true>
+ 	^ extB noMask: 1!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSistaExtStoreLiteralVariableBytecodePopBoolean: (in category 'bytecode generators') -----
  genSistaExtStoreLiteralVariableBytecodePopBoolean: boolean
  	<inline: true>
  	| index needsStoreCheck |
+ 	needsStoreCheck := self sistaNeedsStoreCheck and: [self ssTopNeedsStoreCheck].
- 	needsStoreCheck := self sistaNeedsStoreCheck.
- 	extB := 0.
  	index := byte1 + (extA << 8).
+ 	extA := extB := 0.
+ 	^self genStorePop: boolean LiteralVariable: index needsStoreCheck: needsStoreCheck!
- 	extA := 0.
- 	^ self genStorePop: boolean LiteralVariable: index needsStoreCheck: needsStoreCheck!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genUnaryInlinePrimitive: (in category 'inline primitive generators') -----
  genUnaryInlinePrimitive: prim
  	"Unary inline primitives."
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#unaryInlinePrimitive:"
  	<option: #SistaVM>
  	| rcvrReg resultReg |
  	rcvrReg := self allocateRegForStackEntryAt: 0.
  	resultReg := self allocateRegNotConflictingWith: (self registerMaskFor: rcvrReg).
- 	self ssTop popToReg: rcvrReg.
- 	self ssPop: 1.
  	prim
  		caseOf: {
  					"00		unchecked class"
  			[1] ->	"01		unchecked pointer numSlots"
+ 				[self ssTop popToReg: rcvrReg.
+ 				 self ssPop: 1.
+ 				 objectRepresentation
- 				[objectRepresentation
  					genGetNumSlotsOf: rcvrReg into: resultReg;
  					genConvertIntegerToSmallIntegerInReg: resultReg].
  					"02		unchecked pointer basicSize"
  			[3] ->	"03		unchecked byte numBytes"
  				[objectRepresentation
  					genGetNumBytesOf: rcvrReg into: resultReg;
  					genConvertIntegerToSmallIntegerInReg: resultReg].
  					"04		unchecked short16Type format numShorts"
  					"05		unchecked word32Type format numWords"
  					"06		unchecked doubleWord64Type format numDoubleWords"
+ 			[11] ->	"11		unchecked fixed pointer basicNew"
+ 				[self ssTop type ~= SSConstant ifTrue:
+ 					[^EncounteredUnknownBytecode].
+ 				 (objectRepresentation
+ 					genGetInstanceOf: self ssTop constant
+ 						into: resultReg
+ 							initializingIf: self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
+ 					[^ShouldNotJIT]. "e.g. bad class"
+ 				 self ssPop: 1]
  				  }
  		otherwise:
  			[^EncounteredUnknownBytecode].
+ 	extB := 0.
  	self ssPushRegister: resultReg.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaStorePop:MaybeContextSlotIndex:needsStoreCheck: (in category 'bytecode generator support') -----
  genVanillaStorePop: popBoolean MaybeContextSlotIndex: slotIndex needsStoreCheck: needsStoreCheck
  	<inline: true>
  	| jmpSingle jmpDone |
  	<var: #jmpSingle type: #'AbstractInstruction *'>
  	<var: #jmpDone type: #'AbstractInstruction *'>
  
+ 	self deny: (needsStoreCheck and: [self ssTopNeedsStoreCheck not]).
  	self ssPop: 1.
  	self ssAllocateCallReg: ClassReg and: SendNumArgsReg. "for ceStoreContextInstVarTrampoline"
  	self ssPush: 1.
  	objectRepresentation
  		genLoadSlot: SenderIndex
  		sourceReg: ReceiverResultReg
  		destReg: TempReg.
  	self ssStorePop: popBoolean toReg: ClassReg.
  	jmpSingle := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	self MoveCq: slotIndex R: SendNumArgsReg.
  	self CallRT: ceStoreContextInstVarTrampoline.
  	jmpDone := self Jump: 0.
  	jmpSingle jmpTarget: self Label.
  	objectRepresentation
  		genStoreSourceReg: ClassReg
  		slotIndex: slotIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: true
  		needsStoreCheck: needsStoreCheck.
  	jmpDone jmpTarget: self Label.
  	
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaStorePop:slotIndex:destReg:needsStoreCheck: (in category 'bytecode generator support') -----
  genVanillaStorePop: popBoolean slotIndex: slotIndex destReg: destReg needsStoreCheck: needsStoreCheck
  	<inline: true>
  	| topReg |
  
+ 	self deny: (needsStoreCheck and: [self ssTopNeedsStoreCheck not]).
  	self cppIf: IMMUTABILITY
  		ifTrue: []
  		ifFalse: "First path, receiver is in newSpace"
  			[(destReg = ReceiverResultReg and: [needsFrame not and: [useTwoPaths]]) ifTrue:
  				[topReg := self ssStorePop: popBoolean toPreferredReg: TempReg.
  				 self MoveR: topReg
  					Mw: slotIndex * objectMemory wordSize + objectMemory baseHeaderSize
  					r: ReceiverResultReg.
  				 traceStores > 0 ifTrue:
  					[topReg ~= TempReg ifTrue:
  						[self MoveR: topReg R: TempReg].
  					 self CallRT: ceTraceStoreTrampoline].
  				 ^0]].
- 
  	topReg := self 
+ 				allocateRegForStackEntryAt: 0 
+ 				notConflictingWith: (self registerMaskFor: destReg). 
- 		allocateRegForStackEntryAt: 0 
- 		notConflictingWith: (self registerMaskFor: destReg). 
  	self ssStorePop: popBoolean toReg: topReg.
  	objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: slotIndex
  		destReg: destReg
  		scratchReg: TempReg
  		inFrame: needsFrame
  		needsStoreCheck: needsStoreCheck!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssTopNeedsStoreCheck (in category 'bytecode generator support') -----
  ssTopNeedsStoreCheck
  	<inline: true>
+ 	^self ssTop type ~= SSConstant
+ 	  or: [(objectMemory isNonImmediate: self ssTop constant)
+ 		and: [objectRepresentation shouldAnnotateObjectReference:  self ssTop constant]]!
- 	^ (objectRepresentation isUnannotatableConstant: self ssTop) not!

Item was changed:
  ----- Method: VMMaker class>>initialize (in category 'initialisation') -----
  initialize
  	"VMMaker initialize"
  	DirNames := Dictionary new.
  	DirNames
  		at: #coreVMDir put: 'vm';
  		at: #platformsDir put: 'platforms';
  		at: #pluginsDir put: 'plugins';
  		at: #sourceDir put: 'src'.
  
  	"Try and decide where the Cog source tree is.  Two configurations are likely.
  	 One is that the VMMaker image is running in the image directory in the
  	 source tree and hence everything will be at '..'.
  	 Another is where the source tree is at the same level as the VMMaker image,
  	 in which case it is likely called oscogvm or Cog."
+ 	#('../platforms' 'oscogvm/platforms' 'Cog/platforms' '../oscogvm/platforms')
+ 		with: #('../' 'oscogvm' 'Cog' '../oscogvm')
- 	#('../platforms' 'oscogvm/platforms' 'Cog/platforms')
- 		with: #('../' 'oscogvm' 'Cog')
  		do: [:dir :path|
  			(FileDirectory default directoryExists: dir) ifTrue:
  				[DirNames at: #sourceTree put: path.
  				 ^self]]!



More information about the Vm-dev mailing list