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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 28 21:55:42 UTC 2015


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

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

Name: VMMaker.oscog-eem.1269
Author: eem
Time: 28 April 2015, 2:52:00.14 pm
UUID: dfe19ffc-4c55-433c-a284-cf4696e6489b
Ancestors: VMMaker.oscog-cb.1268

Punctuation ( .. => . ).  Simplify C for jumpTargetPCAt:

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

Item was changed:
  ----- Method: CogARMCompiler>>jumpTargetPCAt: (in category 'disassembly') -----
  jumpTargetPCAt: pc
  	<returnTypeC: #usqInt>
  	| operand word |
  	word := objectMemory long32At: pc.
  	operand := word bitAnd: 16rFFFFFF.
  	(operand anyMask: 16r800000) ifTrue:
  		[operand := operand - 16r1000000].
+ 	^self
+ 		cCode: [operand * 4 + pc + 8]
+ 		inSmalltalk: [operand * 4 + pc + 8 bitAnd: cogit addressSpaceMask]!
- 	^operand * 4 + pc + 8 bitAnd: cogit addressSpaceMask!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>mixed:branchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
  mixed: numNonImmediates branchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
  	| jmpImmediate jumps label numCases classObj index |
  	<var: #label type: #'AbstractInstruction *'>
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jumps type: #'AbstractInstruction **'>
  	<var: #targetFixUp type: #'AbstractInstruction *'>
  	numCases := objectMemory numSlotsOf: arrayObj.
  	cogit MoveR: reg R: TempReg.
  	jmpImmediate := self genJumpImmediateInScratchReg: TempReg.
  	
  	"Rcvr is non immediate"
+ 	jumps := self alloca: numNonImmediates type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class]).
- 	jumps := self alloca: numNonImmediates type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class])..
  	self genGetClassIndexOfNonImm: reg into: TempReg.
  	index := 0.
  	0 to: numCases - 1 do:
  		[:i|
  			classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  			(objectMemory isImmediateClass: classObj) ifFalse: [
  				self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
  				jumps at: index put: (cogit JumpZero: 0).
  				index := index + 1 ] ].
  	cogit Jump: targetFixUp.
  	
  	"Rcvr is immediate"
  	jmpImmediate jmpTarget: cogit Label.
  	numCases - numNonImmediates "num Immediates allowed"
  		caseOf:
  		{[ 1 ] -> [ "1 immediate allowed. jump to targetFixUp if the rcvr is not this immediate"
  			0 to: numCases - 1 do:
  				[ :j |
  				classObj := objectMemory fetchPointer: j ofObject: arrayObj.
  				(objectMemory isImmediateClass: classObj) ifTrue: [
  					self branchIf: reg hasNotImmediateTag: (objectMemory classTagForClass: classObj) target: targetFixUp ] ] ] .
  		[ 2 ] -> [ "2 immediates allowed. On 32 bits nothing to do, all immediate are allowed, on 64 bits generates the jump to fixup for the third tag"
  				self branch2CasesIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp ] .
  		[ 3 ] -> [ "nothing to do, all immediates are allowed." ] }.
  	
  	label := self Label.
  	0 to: numNonImmediates - 1 do: [:i |
  		(jumps at: i) jmpTarget: label ].
  	
  	^ 0
  		!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>noneImmediateBranchIf:notInstanceOfBehaviors:target: (in category 'sista support') -----
  noneImmediateBranchIf: reg notInstanceOfBehaviors: arrayObj target: targetFixUp
  	"All classes in arrayObj are not immediate"
  	| label numJumps jumps classObj |
  	<var: #targetFixUp type: #'AbstractInstruction *'>
  	<var: #label type: #'AbstractInstruction *'>
  	<var: #jumps type: #'AbstractInstruction **'>
  	cogit MoveR: reg R: TempReg.
+ 	jumps := self alloca: (objectMemory numSlotsOf: arrayObj) type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class]).
- 	jumps := self alloca: (objectMemory numSlotsOf: arrayObj) type: (self cCode: [#'AbstractInstruction *'] inSmalltalk: [cogit backEnd class])..
  	(self genJumpImmediateInScratchReg: TempReg) jmpTarget: targetFixUp.
  	self genGetClassIndexOfNonImm: reg into: TempReg.
  	0 to: (numJumps := objectMemory numSlotsOf: arrayObj) - 1 do:
  		[:i|
  		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
  		 self genCmpClassIndex: (objectMemory classTagForClass: classObj) R: TempReg.
  		jumps at: i put: (cogit JumpZero: 0) ].
  	cogit Jump: targetFixUp.
  	label := self Label.
  	0 to: numJumps do: [:i |
  		(jumps at: i) jmpTarget: label ].
  	^0!

Item was changed:
  ----- Method: Cogit>>generateMapAt:start: (in category 'method map') -----
  generateMapAt: addressOrNull start: startAddress
  	"Generate the method map at addressrNull (or compute it if addressOrNull is null).
  	 Answer the length of the map in byes.  Each entry in the map is in two parts.  In the
  	 least signficant bits are a displacement of how far from the start or previous entry,
  	 unless it is an IsAnnotationExtension byte, in which case those bits are the extension.
  	 In the most signficant bits are the type of annotation at the point reached.  A null
  	 byte ends the map."
  	| length location |
  	<var: #annotation type: #'InstructionAnnotation *'>
  	length := 0.
  	location := startAddress.
  	0 to: annotationIndex - 1 do:
  		[:i| | annotation mcpc delta maxDelta mapEntry |
  		 annotation := self addressOf: (annotations at: i).
  		 mcpc := annotation instruction address + annotation instruction machineCodeSize.
  		 [(delta := mcpc - location / backEnd codeGranularity) > DisplacementMask] whileTrue:
  			[maxDelta := (delta min: MaxX2NDisplacement) bitClear: DisplacementMask.
  			 self assert: maxDelta >> AnnotationShift <= DisplacementMask.
  			 addressOrNull ifNotNil:
  				[objectMemory
  					byteAt: addressOrNull - length
  					put: maxDelta >> AnnotationShift + DisplacementX2N.
  				 self traceMap: IsDisplacementX2N
  					  byte: maxDelta >> AnnotationShift + DisplacementX2N
  					  at: addressOrNull - length
  					  for: mcpc].
  			 location := location + (maxDelta * backEnd codeGranularity).
  			 length := length + 1].
  		 addressOrNull ifNotNil:
  			[mapEntry := delta + ((annotation annotation min: IsSendCall) << AnnotationShift).
  			 objectMemory byteAt: addressOrNull - length put: mapEntry.
  			 self traceMap: annotation
  				  byte: mapEntry
  				  at: addressOrNull - length
  				  for: mcpc].
+ 		 location := location + (delta * backEnd codeGranularity).
- 		 location := location + (delta * backEnd codeGranularity)..
  		 length := length + 1.
  		 annotation annotation > IsSendCall ifTrue: "Add the necessary IsAnnotationExtension"
  			[addressOrNull ifNotNil:
  				[mapEntry := IsAnnotationExtension << AnnotationShift + (annotation annotation - IsSendCall).
  				 objectMemory byteAt: addressOrNull - length put: mapEntry.
  				 self traceMap: annotation
  					  byte: mapEntry
  					  at: addressOrNull - length
  					  for: mcpc].
  			 length := length + 1]].
  	addressOrNull ifNotNil:
  		[objectMemory byteAt: addressOrNull - length put: MapEnd.
  		 self traceMap: MapEnd
  			  byte: MapEnd
  			  at: addressOrNull - length
  			  for: 0].
  	^length + 1!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveShortAt (in category 'sound primitives') -----
  primitiveShortAt
  	"Treat the receiver, which can be indexible by either bytes or words, as
  	 an array of signed 16-bit values. Answer the contents of the given index.
  	 Note that the index specifies the i-th 16-bit entry, not the i-th byte or word."
  
  	| index rcvr value |
+ 	index := self stackTop.
- 	index := self stackTop..
  	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackValue: 1.
  	(objectMemory isWordsOrBytes: rcvr) ifFalse:
  		[^self primitiveFailFor: PrimErrInappropriate].
  	index := objectMemory integerValueOf: index.
  	((index >= 1) and: [index <= (objectMemory num16BitUnitsOf: rcvr)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	value := objectMemory fetchShort16: index - 1 ofObject: rcvr.
  	self cCode: []
  		inSmalltalk: [value > 32767 ifTrue: [value := value - 65536]].
  	self pop: 2 thenPushInteger: value!

Item was changed:
  ----- Method: NewCoObjectMemory>>methodHeaderOf: (in category 'memory access') -----
  methodHeaderOf: methodObj
  	"Answer the method header of a CompiledMethod object.
  	 If the method has been cogged then the header is a pointer to
  	 the CogMethod and the real header will be stored in the CogMethod."
  	<api>
  	<inline: true>
  	| header |
  	self assert: (self isCompiledMethod: methodObj).
  	header := self fetchPointer: HeaderIndex ofObject: methodObj.
  	^(self isIntegerObject: header)
  		ifTrue: [header]
  		ifFalse:
  			[self assert: header asUnsignedInteger < coInterpreter heapBase.
  			 self assert: (coInterpreter cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod.
- 						= self nullHeaderForMachineCodeMethod..
  			(coInterpreter cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was changed:
  ----- Method: NewCoObjectMemory>>noCheckMethodHeaderOf: (in category 'memory access') -----
  noCheckMethodHeaderOf: methodObj
  	"Answer the method header of a CompiledMethod object.
  	 If the method has been cogged then the header is a pointer to
  	 the CogMethod and the real header will be stored in the CogMethod."
  	<inline: true>
  	| header |
  	header := self fetchPointer: HeaderIndex ofObject: methodObj.
  	^(self isIntegerObject: header)
  		ifTrue: [header]
  		ifFalse:
  			[self assert: header asUnsignedInteger < coInterpreter heapBase.
  			 self assert: (coInterpreter cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod.
- 						= self nullHeaderForMachineCodeMethod..
  			(coInterpreter cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>generateMissAbortTrampolines (in category 'initialization') -----
  generateMissAbortTrampolines
+ 	"Generate the run-time entries for the various method and PIC entry misses and aborts.
- 	"Generate the run-time entries for the various method and PIC entry misses and aborts..
  	 Read the class-side method trampolines for documentation on the various trampolines"
  
  	ceMethodAbortTrampoline := self genMethodAbortTrampoline.
  	cePICAbortTrampoline := self genPICAbortTrampoline.
  	ceCPICMissTrampoline := self genTrampolineFor: #ceCPICMiss:receiver:
  								called: 'ceCPICMissTrampoline'
  								arg: ClassReg
  								arg: ReceiverResultReg!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>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"
  	
  	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 *'.
- 	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: Spur32BitCoMemoryManager>>methodHeaderOf: (in category 'growing/shrinking memory') -----
  methodHeaderOf: methodObj
  	"Answer the method header of a CompiledMethod object.
  	 If the method has been cogged then the header is a pointer to
  	 the CogMethod and the real header will be stored in the CogMethod."
  	<api>
  	<inline: true>
  	| header |
  	self assert: (self isCompiledMethod: methodObj).
  	header := self fetchPointer: HeaderIndex ofObject: methodObj.
  	^(self isIntegerObject: header)
  		ifTrue: [header]
  		ifFalse:
  			[self assert: header asUnsignedInteger < newSpaceStart.
  			 self assert: (coInterpreter cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod.
- 						= self nullHeaderForMachineCodeMethod..
  			(coInterpreter cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was changed:
  ----- Method: Spur64BitCoMemoryManager>>methodHeaderOf: (in category 'growing/shrinking memory') -----
  methodHeaderOf: methodObj
  	"Answer the method header of a CompiledMethod object.
  	 If the method has been cogged then the header is a pointer to
  	 the CogMethod and the real header will be stored in the CogMethod."
  	<api>
  	<inline: true>
  	| header |
  	self assert: (self isCompiledMethod: methodObj).
  	header := self fetchPointer: HeaderIndex ofObject: methodObj.
  	^(self isIntegerObject: header)
  		ifTrue: [header]
  		ifFalse:
  			[self assert: header asUnsignedInteger < newSpaceStart.
  			 self assert: (coInterpreter cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod.
- 						= self nullHeaderForMachineCodeMethod..
  			(coInterpreter cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was changed:
  ----- Method: SpurGenerationScavenger>>processWeakSurvivor: (in category 'weakness and ephemerality') -----
  processWeakSurvivor: weakObj
  	"Process a weak survivor on the weakList.  Those of its fields
  	 which have not survived the scavenge should be nilled, and if any
+ 	 are, the coInterpreter should be informed via signalFinalization:.
- 	 are, the coInterpreter should be informed via signalFinalization:..
  	 Answer if the weakObj has any young referents."
  	| weakObjShouldMourn hasYoungReferents numStrongSlots  |
  	weakObjShouldMourn := hasYoungReferents := false.
  	"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
  	numStrongSlots := manager numFixedSlotsOf: weakObj.
  	0 to: numStrongSlots - 1 do:
  		[:i| | referent |
  		 referent := manager fetchPointer: i ofObject: weakObj.
  		 ((manager isNonImmediate: referent)
  		  and: [manager isYoungObject: referent]) ifTrue:
  			[hasYoungReferents := true]].
  	numStrongSlots
  		to: (manager numSlotsOf: weakObj) - 1
  		do: [:i| | referent |
  			referent := manager fetchPointer: i ofObject: weakObj.
  			"Referent could be forwarded due to scavenging or a become:, don't assume."
  			(manager isNonImmediate: referent) ifTrue:
  				[(manager isForwarded: referent) ifTrue:
  					[referent := manager followForwarded: referent.
  					 "weakObj is either young or already in remembered table; no need to check"
  					 self assert: ((manager isReallyYoungObject: weakObj)
+ 								or: [manager isRemembered: weakObj]).
- 								or: [manager isRemembered: weakObj])..
  					 manager storePointerUnchecked: i ofObject: weakObj withValue: referent].
  				(self isMaybeOldScavengeSurvivor: referent)
  					ifTrue:
  						[(manager isYoungObject: referent) ifTrue:
  							[hasYoungReferents := true]]
  					ifFalse:
  						[weakObjShouldMourn := true.
  						 manager
  							storePointerUnchecked: i
  							ofObject: weakObj
  							withValue: manager nilObject]]].
  	weakObjShouldMourn ifTrue:
  		[coInterpreter signalFinalization: weakObj].
  	^hasYoungReferents!

Item was changed:
  ----- Method: SpurMemoryManager>>ensureRoomOnObjStackAt: (in category 'obj stacks') -----
  ensureRoomOnObjStackAt: objStackRootIndex
  	"An obj stack is a stack of objects stored in a hidden root slot, such as
  	 the markStack or the ephemeronQueue.  It is a linked list of segments,
  	 with the hot end at the head of the list.  It is a word object.  The stack
  	 pointer is in ObjStackTopx and 0 means empty.  The list goes through
  	 ObjStackNextx. We don't want to shrink objStacks, since they're used
  	 in GC and its good to keep their memory around.  So unused pages
  	 created by popping emptying pages are kept on the ObjStackFreex list."
  	| stackOrNil freeOrNewPage |
  	stackOrNil := self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj.
  	(stackOrNil = nilObj
  	 or: [(self fetchPointer: ObjStackTopx ofObject: stackOrNil) >= ObjStackLimit]) ifTrue:
  		[freeOrNewPage := stackOrNil = nilObj
  								ifTrue: [0]
  								ifFalse: [self fetchPointer: ObjStackFreex ofObject: stackOrNil].
  		 freeOrNewPage ~= 0
  			ifTrue: "the free page list is always on the new page."
  				[self storePointer: ObjStackFreex ofObjStack: stackOrNil withValue: 0.
  				 self assert: (marking not or: [self isMarked: freeOrNewPage])]
  			ifFalse:
  				[freeOrNewPage := self allocateSlotsInOldSpace: ObjStackPageSlots
  										format: self wordIndexableFormat
  										classIndex: self wordSizeClassIndexPun.
  				 freeOrNewPage ifNil: [self error: 'no memory to allocate or extend obj stack'].
+ 				 self storePointer: ObjStackFreex ofObjStack: freeOrNewPage withValue: 0.
- 				 self storePointer: ObjStackFreex ofObjStack: freeOrNewPage withValue: 0..
  				 marking ifTrue: [self setIsMarkedOf: freeOrNewPage to: true]].
  		 self storePointer: ObjStackMyx ofObjStack: freeOrNewPage withValue: objStackRootIndex;
  			  storePointer: ObjStackNextx ofObjStack: freeOrNewPage withValue: (stackOrNil = nilObj ifTrue: [0] ifFalse: [stackOrNil]);
  			  storePointer: ObjStackTopx ofObjStack: freeOrNewPage withValue: 0;
  			  storePointer: objStackRootIndex ofObject: hiddenRootsObj withValue: freeOrNewPage.
  		 self assert: (self isValidObjStackAt: objStackRootIndex).
  		 "Added a new page; now update and answer the relevant cached first page."
  		 stackOrNil := self updateRootOfObjStackAt: objStackRootIndex with: freeOrNewPage].
  	self assert: (self isValidObjStackAt: objStackRootIndex).
  	^stackOrNil!

Item was changed:
  ----- Method: SpurMemoryManager>>enterIntoClassTable: (in category 'class table') -----
  enterIntoClassTable: aBehavior
  	"Enter aBehavior into the class table and answer 0.  Otherwise answer a primitive failure code."
  	<inline: false>
  	| initialMajorIndex majorIndex minorIndex page |
  	majorIndex := classTableIndex >> self classTableMajorIndexShift.
  	initialMajorIndex := majorIndex.
  	"classTableIndex should never index the first page; it's reserved for known classes"
  	self assert: initialMajorIndex > 0.
  	minorIndex := classTableIndex bitAnd: self classTableMinorIndexMask.
  
  	[page := self fetchPointer: majorIndex ofObject: hiddenRootsObj.
  	 page = nilObj ifTrue:
  		[page := self allocateSlotsInOldSpace: self classTablePageSize
  					format: self arrayFormat
  					classIndex: self arrayClassIndexPun.
  		 page ifNil:
  			[^PrimErrNoMemory].
  		 self fillObj: page numSlots: self classTablePageSize with: nilObj.
  		 self storePointer: majorIndex
  			ofObject: hiddenRootsObj
  			withValue: page.
  		 numClassTablePages := numClassTablePages + 1.
  		 minorIndex := 0].
  	 minorIndex to: self classTablePageSize - 1 do:
  		[:i|
  		(self fetchPointer: i ofObject: page) = nilObj ifTrue:
+ 			[classTableIndex := majorIndex << self classTableMajorIndexShift + i.
- 			[classTableIndex := majorIndex << self classTableMajorIndexShift + i..
  			 "classTableIndex must never index the first page, which is reserved for classes known to the VM."
  			 self assert: classTableIndex >= (1 << self classTableMajorIndexShift).
  			 self storePointer: i
  				ofObject: page
  				withValue: aBehavior.
  			 self setHashBitsOf: aBehavior to: classTableIndex.
  			 self assert: (self classAtIndex: (self rawHashBitsOf: aBehavior)) = aBehavior.
  			 ^0]].
  	 majorIndex := (majorIndex + 1 bitAnd: self classIndexMask) max: 1.
  	 majorIndex = initialMajorIndex ifTrue: "wrapped; table full"
  		[^PrimErrLimitExceeded]] repeat!

Item was changed:
  ----- Method: SpurMemoryManager>>numSlotsOf: (in category 'object access') -----
  numSlotsOf: objOop
  	<returnTypeC: #usqInt>
  	<api>
  	| numSlots |
  	self flag: #endianness.
  	"numSlotsOf: should not be applied to free or forwarded objects."
  	self assert: (self classIndexOf: objOop) > self isForwardedObjectClassIndexPun.
+ 	numSlots := self rawNumSlotsOf: objOop.
- 	numSlots := self rawNumSlotsOf: objOop..
  	^numSlots = self numSlotsMask	"overflow slots; (2^32)-1 slots are plenty"
  		ifTrue: [self rawOverflowSlotsOf: objOop]
  		ifFalse: [numSlots]!

Item was changed:
  ----- Method: SpurMemoryManager>>numSlotsOfAny: (in category 'object access') -----
  numSlotsOfAny: objOop
  	"A private internal version of numSlotsOf: that is happy to be applied to free or forwarded objects."
  	<returnTypeC: #usqInt>
  	| numSlots |
+ 	numSlots := self rawNumSlotsOf: objOop.
- 	numSlots := self rawNumSlotsOf: objOop..
  	^numSlots = self numSlotsMask
  		ifTrue: [self rawOverflowSlotsOf: objOop] "overflow slots; (2^32)-1 slots are plenty"
  		ifFalse: [numSlots]!

Item was changed:
  ----- Method: SpurMemoryManager>>setHiddenRootsObj: (in category 'class table') -----
  setHiddenRootsObj: anOop
  	hiddenRootsObj := anOop.
  	self cCode: [self assert: self validClassTableRootPages]
  		inSmalltalk: [numClassTablePages ifNotNil:
+ 						[self assert: self validClassTableRootPages]].
- 						[self assert: self validClassTableRootPages]]..
  	classTableFirstPage := self fetchPointer: 0 ofObject: hiddenRootsObj.
  	self assert: (self numSlotsOf: classTableFirstPage) - 1 = self classTableMinorIndexMask.
  	"Set classTableIndex to the start of the last used page (excepting first page).
  	 Set numClassTablePages to the number of used pages."
  	numClassTablePages := self classTableRootSlots.
  	2 to: numClassTablePages - 1 do:
  		[:i|
  		(self fetchPointer: i ofObject: hiddenRootsObj) = nilObj ifTrue:
  			[numClassTablePages := i.
  			 classTableIndex := (numClassTablePages - 1 max: 1) << self classTableMajorIndexShift.
  			 ^self]].
  	"no unused pages; set it to the start of the second page."
  	classTableIndex := 1 << self classTableMajorIndexShift!

Item was changed:
  ----- Method: StackInterpreterSimulatorMorph>>displayViewLayoutFrame (in category 'submorphs - simulator display view') -----
  displayViewLayoutFrame 
  	| squeakJSFrame buttonFrame simulatorFrame|
  	"if any Morphic guru's understand layouts and offsets, please fix this. tty"
  	buttonFrame := self buttonRowLayoutFrame.
  	squeakJSFrame := self squeakJSRowLayoutFrame.
+ 	simulatorFrame := self simulatorLayoutFrame.
- 	simulatorFrame := self simulatorLayoutFrame..
  	^LayoutFrame fractions: (0 at 0 corner: 1 at 1) 
  				    offsets: (0@(buttonFrame bottomOffset) corner: simulatorFrame leftOffset at squeakJSFrame topOffset)!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid
  	"SimpleStackBasedCogit initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid"
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid"
  
+ 	super initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid.
- 	super initializeBytecodeTableForSqueakV3PlusClosuresNewspeakV4Hybrid..
  	numPushNilsFunction := #v3or4:Num:Push:Nils:.
  	pushNilSizeFunction := #v3or4PushNilSize:numInitialNils:!

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:"
  	| 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"
  				[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"
  				  }
  		otherwise:
+ 			[^EncounteredUnknownBytecode].
- 			[^EncounteredUnknownBytecode]..
  	self ssPushRegister: resultReg.
  	^0!

Item was changed:
  ----- Method: TSwitchStmtNode>>nodesDo:parent: (in category 'enumerating') -----
  nodesDo: aBlock parent: parent
  	"Apply aBlock to all nodes in the receiver with each node's parent.
  	 N.B. This is assumed to be bottom-up, leaves first."
+ 	expression nodesDo: aBlock parent: self.
- 	expression nodesDo: aBlock parent: self..
  	cases do:
  		[:pair|
  		pair first do: [:node| node nodesDo: aBlock parent: self.].
  		pair last nodesDo: aBlock parent: self.].
  	otherwiseOrNil ifNotNil:
  		[otherwiseOrNil nodesDo: aBlock parent: self].
  	aBlock value: self value: parent!



More information about the Vm-dev mailing list