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

commits at source.squeak.org commits at source.squeak.org
Sun May 10 15:05:23 UTC 2015


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

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

Name: VMMaker.oscog-eem.1295
Author: eem
Time: 10 May 2015, 8:03:05.615 am
UUID: d04946a6-67d1-4bcd-abcd-7475630de999
Ancestors: VMMaker.oscog-rmacnak.1294

Fix genInnerPrimitiveMirrorNewWithArg:.  Class's hash
was being accessed twice, reusing variable holding
jump instruction.

Fix primitiveClass and genPrimitiveClass for mirror
case (arg count = 1). Also fix Newspeak primitive
table to allow nargs > 0 for genPrimitiveClass.

Make sure CogObjectRepresentation has default
versions of new unforwarding routines.

Add missing accessors for in image compilation
found when compiling genInnerPrimitiveNewWithArg:

=============== Diff against VMMaker.oscog-rmacnak.1294 ===============

Item was added:
+ ----- Method: CogObjectRepresentation>>genEnsureObjInRegNotForwarded:scratchReg:updatingMw:r: (in category 'compile abstract instructions') -----
+ genEnsureObjInRegNotForwarded: reg scratchReg: scratch updatingMw: offset r: baseReg
+ 	"Make sure that the non-immediate oop in reg is not forwarded, updating the field
+ 	 at offset from baseReg.  By default there is nothing to do.  Subclasses for memory
+ 	 managers that forward will override."
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentation>>genEnsureOopInRegNotForwarded:scratchReg:ifForwarder:ifNotForwarder: (in category 'compile abstract instructions') -----
+ genEnsureOopInRegNotForwarded: reg scratchReg: scratch ifForwarder: fwdJumpTarget ifNotForwarder: nonFwdJumpTargetOrZero
+ 	"Make sure that the oop in reg is not forwarded.  By default there is
+ 	 nothing to do.  Subclasses for memory managers that forward will override."
+ 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveMirrorNewWithArg: (in category 'primitive generators') -----
  genInnerPrimitiveMirrorNewWithArg: retNoffset
  	"Implement instantiateVariableClass:withSize: for convenient cases:
  	- the class argument has a hash
  	- the class argument is variable and not compiled method
  	- single word header/num slots < numSlotsMask
  	- the result fits in eden
  	See superclass method for dynamic frequencies of formats.
  	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
  
  	<option: #NewspeakVM>
  	| halfHeaderReg fillReg instSpecReg byteSizeReg maxSlots
  	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
  	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
  	  jumpUnhashed jumpTooSmall jumpImmediate jumpNotFixedPointers
  	  jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |
  	<var: 'skip' type: #'AbstractInstruction *'>
  	<var: 'fillLoop' type: #'AbstractInstruction *'>	
  	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
  	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
  	<var: 'jumpTooSmall' type: #'AbstractInstruction *'>
  	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
  	<var: 'jumpImmediate' type: #'AbstractInstruction *'>
  	<var: 'jumpByteFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
  	<var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
  	<var: 'jumpNotFixedPointers' type: #'AbstractInstruction *'>
  
  	"half header will contain 1st half of header (classIndex/class's hash & format),
  	 then 2nd half of header (numSlots) and finally fill value (nilObject)."
  	halfHeaderReg := fillReg := SendNumArgsReg.
  	"inst spec will hold class's instance specification and then byte size and finally numSlots half of header"
  	instSpecReg := byteSizeReg := ClassReg.
  	"The max slots we'll allocate here are those for a single header"
  	maxSlots := objectMemory numSlotsMask - 1.
  
  	"check size and fail if not a +ve integer"
  	cogit MoveR: Arg1Reg R: TempReg.
  	jumpNElementsNonInt := self genJumpNotSmallIntegerInScratchReg: TempReg.
  
  	"Is the class arg pointers with at least 3 fields?"
  	cogit MoveR: Arg0Reg R: TempReg.
  	jumpImmediate := self genJumpImmediateInScratchReg: TempReg.
  
  	self genGetFormatOf: Arg0Reg
  		into: TempReg
  		leastSignificantHalfOfBaseHeaderIntoScratch: nil.
  	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
  	jumpNotFixedPointers := cogit JumpNonZero: 0.
  	
  	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
  	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
  	jumpTooSmall := cogit JumpLess: 0.
  
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: Arg0Reg into: halfHeaderReg.
  	jumpUnhashed := cogit JumpZero: 0.
  
+ 	"The basicNew: code below (copied from genInnerPrimitiveNewWithArg:) expects class
+ 	 in ReceiverResultReg and size in Arg0Reg.  Shuffle args to match, undoing on failure."
- 	"The basicNew: code (genInnerPrimitiveNewWithArg:) expects class in ReceiverResultReg
- 	 and size in Arg0Reg.  Shuffle args to match, undoing on failure."
  	cogit
  		PushR: ReceiverResultReg;
  		MoveR: Arg0Reg R: ReceiverResultReg;
  		MoveR: Arg1Reg R: Arg0Reg.
  
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
- 	"get class's hash & fail if 0"
- 	self genGetHashFieldNonImmOf: ReceiverResultReg into: halfHeaderReg.
- 	jumpUnhashed := cogit JumpZero: 0.
  	"get class's format inst var for inst spec (format field)"
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
  	cogit AndCq: objectMemory formatMask R: instSpecReg.
  	"Add format to classIndex/format half header now"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: halfHeaderReg.
  	"get integer value of num fields in TempReg now"
  	cogit MoveR: Arg0Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	"dispatch on format, failing if not variable or if compiled method"
  	cogit CmpCq: objectMemory arrayFormat R: instSpecReg.
  	jumpArrayFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
  	jumpByteFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
  	jumpFailCuzFixed := cogit JumpNonZero: 0.
  
  	cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg.
  	jumpLongTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"push fill value"
  	cogit PushCq: 0.
  	jumpLongPrepDone := cogit Jump: 0. "go allocate"
  
  	jumpByteFormat jmpTarget:
  	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
  	jumpByteTooBig := cogit JumpAbove: 0.
  	"save num elements to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"compute odd bits and add into halfHeaderReg; oddBits := 4 - nElements bitAnd: 3"
  	cogit MoveCq: objectMemory wordSize R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: halfHeaderReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
  	"push fill value"
  	cogit PushCq: 0.
  	jumpBytePrepDone := cogit Jump: 0. "go allocate"
  
  	jumpArrayFormat jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
  	jumpArrayTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"push fill value"
  	cogit PushCw: objectMemory nilObject.
  	"fall through to allocate"
  
  	jumpBytePrepDone jmpTarget:
  	(jumpLongPrepDone jmpTarget: cogit Label).
  
  	"write half header now; it frees halfHeaderReg"
  	cogit MoveR: halfHeaderReg Mw: 0 r: Arg1Reg.
  	"save numSlots to halfHeaderReg"
  	cogit MoveR: instSpecReg R: halfHeaderReg.
  	"compute byte size; remember 0-sized objects still need 1 slot & allocation is
  	 rounded up to 8 bytes."
  	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
  	jumpHasSlots := cogit JumpNonZero: 0.
  	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
  	skip := cogit Jump: 0.
  	"round up to allocationUnit"
  	jumpHasSlots jmpTarget:
  	(cogit MoveR: byteSizeReg R: TempReg).
  	cogit AndCq: 1 R: TempReg.
  	cogit AddR: TempReg R: byteSizeReg.
  	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
  	skip jmpTarget:
  	"shift halfHeaderReg to put numSlots in correct place"
  	(cogit LogicalShiftLeftCq: objectMemory numSlotsHalfShift R: halfHeaderReg).
  	"check if allocation fits"
  	cogit AddR: Arg1Reg R: byteSizeReg.
  	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
  	"write other half of header (numSlots/0 identityHash)"
  	cogit MoveR: halfHeaderReg Mw: 4 r: ReceiverResultReg.
  	"now fill"
  	cogit PopR: fillReg.
  	cogit PopR: TempReg. "discard pushed receiver"
  	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
  	"at least two words; so can make this a [fill 2 words. reached limit?] whileFalse"
  	fillLoop := 
  	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
  	cogit MoveR: fillReg Mw: 4 r: Arg1Reg.
  	cogit AddCq: 8 R: Arg1Reg.
  	cogit CmpR: Arg1Reg R: byteSizeReg.
  	cogit JumpAbove: fillLoop.
  	cogit RetN: retNoffset.
  
  	"pop discarded fill value & fall through to failure"
  	jumpNoSpace jmpTarget: (cogit PopR: TempReg).
  
  	jumpFailCuzFixed jmpTarget:
  	(jumpArrayTooBig jmpTarget:
  	(jumpByteTooBig jmpTarget:
  	(jumpLongTooBig jmpTarget: cogit Label))).
  
  	"unshuffle arguments"
  	cogit
  		MoveR: Arg0Reg R: Arg1Reg;
  		MoveR: ReceiverResultReg R: Arg0Reg;
  		PopR: ReceiverResultReg.
  
  	jumpUnhashed jmpTarget:
  	(jumpImmediate jmpTarget:
  	(jumpNotFixedPointers jmpTarget:
  	(jumpTooSmall jmpTarget:
  	(jumpNElementsNonInt jmpTarget: cogit Label)))).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureObjInRegNotForwarded:scratchReg:updatingMw:r: (in category 'compile abstract instructions') -----
  genEnsureObjInRegNotForwarded: reg scratchReg: scratch updatingMw: offset r: baseReg
+ 	"Make sure that the object in reg is not forwarded, and the field reg[offset] is updated
+ 	 if the object in reg is forwarded. Use the fact that isForwardedObjectClassIndexPun is
+ 	 a power of two to save an instruction."
- 	"Make sure that the object in reg is not forwarded, and update the field reg[offset] is
- 	 updated if the object in reg is forwarded.
- 	 Use the fact that isForwardedObjectClassIndexPun is a power of two to save an instruction."
  	| loop imm ok |
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #imm type: #'AbstractInstruction *'>
  	<var: #loop type: #'AbstractInstruction *'>
  	self assert: reg ~= scratch.
  	loop := cogit Label.
  	cogit MoveR: reg R: scratch.
  	imm := self genJumpImmediateInScratchReg: scratch.
  	"notionally
  		self genGetClassIndexOfNonImm: reg into: scratch.
  		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: TempReg.
  	 but the following is an instruction shorter:"
  	cogit MoveMw: 0 r: reg R: scratch.
  	cogit
  		AndCq: objectMemory classIndexMask - objectMemory isForwardedObjectClassIndexPun
  		R: scratch.
  	ok := cogit JumpNonZero:  0.
  	self genLoadSlot: 0 sourceReg: reg destReg: reg.
  	cogit MoveR: reg Mw: offset r: baseReg.
  	cogit Jump: loop.
  	ok jmpTarget: (imm jmpTarget: cogit Label).
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetClassObjectOf:into:scratchReg:instRegIsReceiver: (in category 'compile abstract instructions') -----
  genGetClassObjectOf: instReg into: destReg scratchReg: scratchReg instRegIsReceiver: instRegIsReceiver
+ 	"Fetch the instance's class into destReg.  If the instance is not the receiver and is forwarded, follow forwarding."
- 	"Fetch the instance's class into destReg.  If the instance is forwarded, follow forwarding."
  	| jumpIsImm jumpNotForwarded loop |
  	<var: #jumpIsImm type: #'AbstractInstruction *'>
  	<var: #jumpNotForwarded type: #'AbstractInstruction *'>
  	<var: #loop type: #'AbstractInstruction *'>
  	instReg = destReg ifTrue:
  		[^BadRegisterSet].
  	loop := cogit MoveR: instReg R: scratchReg.
  	cogit AndCq: objectMemory tagMask R: scratchReg.
  	jumpIsImm := cogit JumpNonZero: 0.
  	self flag: #endianness.
  	"Get least significant half of header word in destReg"
  	cogit MoveMw: 0 r: instReg R: scratchReg.
  	"mask off class index"
  	cogit AndCq: objectMemory classIndexMask R: scratchReg.
  	instRegIsReceiver ifFalse:
  		["if it is forwarded..."
  		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: scratchReg.
  		jumpNotForwarded := cogit JumpNonZero: 0.
  		"...follow the forwarding pointer and loop to fetch its classIndex"
  		cogit MoveMw: objectMemory baseHeaderSize r: instReg R: instReg.
  		cogit Jump: loop.
  		jumpNotForwarded jmpTarget: cogit Label].
  	jumpIsImm jmpTarget:
  	(cogit MoveR: scratchReg R: destReg).
  	cogit PushR: instReg.
  	self genGetClassObjectOfClassIndex: destReg into: instReg scratchReg: TempReg.
  	cogit MoveR: instReg R: destReg.
  	cogit PopR: instReg.
  	^0!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>fixedFieldsFieldWidth (in category 'accessing') -----
+ fixedFieldsFieldWidth
+ 	^objectMemory fixedFieldsFieldWidth!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>identityHashHalfWordMask (in category 'accessing') -----
+ identityHashHalfWordMask
+ 	^objectMemory identityHashHalfWordMask!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>nonIndexablePointerFormat (in category 'accessing') -----
+ nonIndexablePointerFormat
+ 	^objectMemory nonIndexablePointerFormat!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>numSlotsHalfShift (in category 'accessing') -----
+ numSlotsHalfShift
+ 	^objectMemory numSlotsHalfShift!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveClass (in category 'object access primitives') -----
  primitiveClass
  	| instance |
  	instance := self stackTop.
+ 	NewspeakVM
+ 		ifTrue:
+ 			[argumentCount > 0 ifTrue:
+ 				[instance := objectMemory followMaybeForwarded: instance].
+ 			 self pop: argumentCount+1 thenPush: (objectMemory fetchClassOf: instance)]
+ 		ifFalse:
+ 			[self assert argumentCount = 0.
+ 			 self pop: 1 thenPush: (objectMemory fetchClassOf: instance)]!
- 	self pop: argumentCount+1 thenPush: (objectMemory fetchClassOf: instance)!

Item was added:
+ VMClass subclass: #NullLiteralsManager
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForNewsqueak (in category 'class initialization') -----
  initializePrimitiveTableForNewsqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter."
  	"SimpleStackBasedCogit initializePrimitiveTableForSqueakV3"
  	MaxCompiledPrimitiveIndex := 222.
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1	mclassIsSmallInteger:)
  		(2 genPrimitiveSubtract			1	mclassIsSmallInteger:)
  		(3 genPrimitiveLessThan		1	mclassIsSmallInteger:)
  		(4 genPrimitiveGreaterThan		1	mclassIsSmallInteger:)
  		(5 genPrimitiveLessOrEqual		1	mclassIsSmallInteger:)
  		(6 genPrimitiveGreaterOrEqual	1	mclassIsSmallInteger:)
  		(7 genPrimitiveEqual			1	mclassIsSmallInteger:)
  		(8 genPrimitiveNotEqual		1	mclassIsSmallInteger:)
  		(9 genPrimitiveMultiply			1	processorHasMultiplyAndMClassIsSmallInteger:)
  		(10 genPrimitiveDivide			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(11 genPrimitiveMod			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(12 genPrimitiveDiv				1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(13 genPrimitiveQuo			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(14 genPrimitiveBitAnd			1	mclassIsSmallInteger:)
  		(15 genPrimitiveBitOr			1	mclassIsSmallInteger:)
  		(16 genPrimitiveBitXor			1	mclassIsSmallInteger:)
  		(17 genPrimitiveBitShift			1	mclassIsSmallInteger:)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 primitiveFloatAt)"
  		"(39 primitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0	processorHasDoublePrecisionFloatingPointSupport:)
  		(41 genPrimitiveFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(42 genPrimitiveFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(43 genPrimitiveFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(44 genPrimitiveFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(45 genPrimitiveFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(46 genPrimitiveFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)
  		(47 genPrimitiveFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(48 genPrimitiveFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(49 genPrimitiveFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(50 genPrimitiveFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
  		"(51 primitiveTruncated)"
  		"(52 primitiveFractionalPart)"
  		"(53 primitiveExponent)"
  		"(54 primitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)
  		"(56 primitiveSine)"
  		"(57 primitiveArctan)"
  		"(58 primitiveLogN)"
  		"(59 primitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut		2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		"(65 primitiveFail)""was primitiveNext"
  		"(66 primitiveFail)" "was primitiveNextPut"
  		"(67 primitiveFail)" "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		"(68 primitiveObjectAt)"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew			-1)			"For VMMirror support 1 argument instantiateFixedClass: as well as baiscNew"
  		(71 genPrimitiveNewWithArg	-1)			"For VMMirror support 2 argument instantiateVariableClass:withSize: as well as baiscNew:"
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		"(83 primitivePerform)"
  		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"Input/Output Primitives (90-109); We won't compile any of these"
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
+ 		(111 genPrimitiveClass -1)			"For VMMirror support 1 argument classOf: as well as class"
- 		(111 genPrimitiveClass)
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  			"Squeak 2.2 and earlier use 119.  Squeak 2.3 and later use 116.
  			Both are supported for backward compatibility."
  
  		"Miscellaneous Primitives (120-127); We won't compile any of these"
  
  		"Squeak Primitives Start Here"
  
  		"Squeak Miscellaneous Primitives (128-149); We won't compile any of these"
  
  		"File Primitives (150-169) - NO LONGER INDEXED; We won't compile any of these"
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)			"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveCharacterValue 0)	"Character>>value"
  		"Sound Primitives (170-199) - NO LONGER INDEXED; We won't compile any of these"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  		"Sound Primitives (170-199) - NO LONGER INDEXED; We won't compile any of these"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Sound Primitives (continued) - NO LONGER INDEXED; We won't compile any of these"
  		"(190 194 primitiveFail)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives (were Networking primitives)"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		"(207 209 primitiveFail)"	"reserved for Cog primitives"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  		"(213 217 primitiveFail)"	"reserved for Cog primitives"
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
  		"(223 229 primitiveFail)"	"reserved for Cog primitives"
  	)!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveClass (in category 'primitive generators') -----
  genPrimitiveClass
+ 	NewspeakVM
+ 		ifTrue:
+ 			[methodOrBlockNumArgs > 0 ifTrue:
+ 				[methodOrBlockNumArgs > 1 ifTrue:
+ 					[^self compileFallbackToInterpreterPrimitive].
+ 			 self genLoadArgAtDepth: 0 into: ReceiverResultReg]]
+ 		ifFalse:
+ 			[self assert: methodOrBlockNumArgs = 0].
- 	"Stack looks like
- 		receiver (also in ReceiverResultReg)
- 		return address"
  	(objectRepresentation
  			genGetClassObjectOf: ReceiverResultReg
  			into: ReceiverResultReg
  			scratchReg: TempReg
+ 			instRegIsReceiver: (NewspeakVM ifTrue: [methodOrBlockNumArgs = 0] ifFalse: [true])) = BadRegisterSet ifTrue:
- 			instRegIsReceiver: methodOrBlockNumArgs = 0) = BadRegisterSet ifTrue:
  		[objectRepresentation
  			genGetClassObjectOf: ReceiverResultReg
  			into: ClassReg
  			scratchReg: TempReg
+ 			instRegIsReceiver: (NewspeakVM ifTrue: [methodOrBlockNumArgs = 0] ifFalse: [true]).
- 			instRegIsReceiver: methodOrBlockNumArgs = 0.
  		 self MoveR: ClassReg R: ReceiverResultReg].
+ 	self RetN: (self primRetNOffsetFor: methodOrBlockNumArgs).
- 	self RetN: (self primRetNOffsetFor: 0).
  	^0!

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>setRememberedSetRedZone (in category 'remembered set') -----
+ setRememberedSetRedZone
+ 	self halt.
+ 	^super setRememberedSetRedZone!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveClass (in category 'primitive generators') -----
  genPrimitiveClass
- 	"Depending on argument count the argument is either
- 		0 args: ReceiverResultReg
- 		1 args: Arg0Reg
- 		N args: top of stack (assuming 1 reg arg for now)"
  	| reg |
+ 	reg := ReceiverResultReg.
+ 	NewspeakVM
- 	methodOrBlockNumArgs = 1
  		ifTrue:
- 			[reg := Arg0Reg]
- 		ifFalse:
  			[methodOrBlockNumArgs > 0 ifTrue:
+ 				[methodOrBlockNumArgs > 1 ifTrue:
+ 					[^self compileFallbackToInterpreterPrimitive].
+ 				 reg := Arg0Reg]]
+ 		ifFalse:
+ 			[self assert: methodOrBlockNumArgs = 0].
- 				[self MoveMw: objectMemory wordSize r: SPReg R: ReceiverResultReg].
- 			reg := ReceiverResultReg].
  	(objectRepresentation
  			genGetClassObjectOf: reg
  			into: ReceiverResultReg
  			scratchReg: TempReg
+ 			instRegIsReceiver: (NewspeakVM ifTrue: [methodOrBlockNumArgs = 0] ifFalse: [true])) = BadRegisterSet ifTrue:
- 			instRegIsReceiver: methodOrBlockNumArgs = 0) = BadRegisterSet ifTrue:
  		[objectRepresentation
  			genGetClassObjectOf: reg
  			into: ClassReg
  			scratchReg: TempReg
+ 			instRegIsReceiver: (NewspeakVM ifTrue: [methodOrBlockNumArgs = 0] ifFalse: [true]).
- 			instRegIsReceiver: methodOrBlockNumArgs = 0.
  		 self MoveR: ClassReg R: ReceiverResultReg].
  	self RetN: 0.
  	^0!



More information about the Vm-dev mailing list