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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 25 04:01:29 UTC 2013


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

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

Name: VMMaker.oscog-eem.569
Author: eem
Time: 24 December 2013, 7:56:53.833 pm
UUID: 84f8b41f-92bf-41d2-9927-6c7e3d3e4272
Ancestors: VMMaker.oscog-dtl.568

Fix Spur's machine-code identityHash primitive for Character
receivers.  Refactor into the conventional cogit/objRep split
genPrimitiveFoo/genInnerPrimitiveFoo.  Nuke the now-unused
isHashSetOnInstanceCreation.

Fix Spur's machine-code == & ~~ primitives for potentially
forwarded arguments.

Implement machine-code primitives for Character>>value and
SmallInteger>>asCharacter/Character class>>value:.

=============== Diff against VMMaker.oscog-dtl.568 ===============

Item was changed:
  ----- Method: CoInterpreter>>printPrimLogEntryAt: (in category 'debug support') -----
  printPrimLogEntryAt: i
  	<inline: false>
  	| intOrSelector |
  	intOrSelector := primTraceLog at: i.
  	(objectMemory isImmediate: intOrSelector)
  		ifTrue:
+ 			[intOrSelector = TraceIncrementalGC ifTrue:
- 			[ intOrSelector = TraceIncrementalGC ifTrue:
  				[self print: '**IncrementalGC**'. ^nil].
  			 intOrSelector = TraceFullGC ifTrue:
  				[self print: '**FullGC**'. ^nil].
  			 intOrSelector = TraceCodeCompaction ifTrue:
  				[self print: '**CompactCode**'. ^nil].
  			 self print: '???']
  		ifFalse:
  			[objectMemory safePrintStringOf: intOrSelector]!

Item was added:
+ ----- Method: CogObjectRepresentation>>genInnerPrimitiveAsCharacter:inReg: (in category 'primitive generators') -----
+ genInnerPrimitiveAsCharacter: retNOffset inReg: reg
+ 	"subclasses override if they can"
+ 	^cogit unimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentation>>genInnerPrimitiveCharacterValue: (in category 'primitive generators') -----
+ genInnerPrimitiveCharacterValue: retNOffset
+ 	"subclasses override if they can"
+ 	^cogit unimplementedPrimitive!

Item was removed:
- ----- Method: CogObjectRepresentation>>isHashSetOnInstanceCreation (in category 'testing') -----
- isHashSetOnInstanceCreation
- 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genConvertCharacterToSmallIntegerInReg: (in category 'compile abstract instructions') -----
+ genConvertCharacterToSmallIntegerInReg: reg
+ 	"Convert the SmallInteger in reg to a Character, assuming
+ 	 the SmallInteger's value is a valid character."
+ 	"self assume: objectMemory smallIntegerTag = 1"
+ 	self assert: (objectMemory characterTag = 2
+ 				 and: [self numCharacterBits + 1 = self numSmallIntegerBits]).
+ 	cogit LogicalShiftRightCq: 1 R: reg!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genConvertSmallIntegerToCharacterInReg: (in category 'compile abstract instructions') -----
+ genConvertSmallIntegerToCharacterInReg: reg
+ 	"Convert the SmallInteger in reg to a Character, assuming
+ 	 the SmallInteger's value is a valid character."
+ 	"self assume: objectMemory smallIntegerTag = 1"
+ 	self assert: (objectMemory characterTag = 2
+ 				 and: [self numCharacterBits + 1 = self numSmallIntegerBits]).
+ 	cogit LogicalShiftLeftCq: 1 R: reg!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>numCharacterBits (in category 'compile abstract instructions') -----
+ numCharacterBits
+ 	^30!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genConvertSmallIntegerToCharacterInReg: (in category 'compile abstract instructions') -----
+ genConvertSmallIntegerToCharacterInReg: reg
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveAsCharacter:inReg: (in category 'primitive generators') -----
+ genInnerPrimitiveAsCharacter: retNOffset inReg: reg
+ 	| jumpNotInt jumpOutOfRange |
+ 	<var: 'jumpNotInt' type: #'AbstractInstruction *'>
+ 	<var: 'jumpOutOfRange' type: #'AbstractInstruction *'>
+ 	reg ~= ReceiverResultReg ifTrue:
+ 		[cogit MoveR: reg R: TempReg.
+ 		 jumpNotInt := self genJumpNotSmallIntegerInScratchReg: TempReg].
+ 	cogit MoveR: reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit CmpCq: (1 << 30) - 1 R: TempReg.
+ 	jumpOutOfRange := cogit JumpAbove: 0.
+ 	self genConvertSmallIntegerToCharacterInReg: reg.
+ 	reg ~= ReceiverResultReg ifTrue:
+ 		[cogit MoveR: reg R: ReceiverResultReg].
+ 	cogit RetN: retNOffset.
+ 	jumpOutOfRange jmpTarget: cogit Label.
+ 	reg ~= ReceiverResultReg ifTrue:
+ 		[jumpNotInt jmpTarget: jumpOutOfRange getJmpTarget].
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveCharacterValue: (in category 'primitive generators') -----
+ genInnerPrimitiveCharacterValue: retNOffset
+ 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit RetN: retNOffset.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveIdentical:orNotIf: (in category 'primitive generators') -----
+ genInnerPrimitiveIdentical: retNoffset orNotIf: orNot
+ 	| jumpImmediate jumpCmp |
+ 	<var: #jumpCmp type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	cogit MoveR: Arg0Reg R: TempReg.
+ 	jumpImmediate := self genJumpImmediateInScratchReg: TempReg.
+ 	self genEnsureObjInRegRegNotForwarded: Arg0Reg scratchReg: TempReg.
+ 	jumpImmediate jmpTarget:
+ 		(cogit CmpR: Arg0Reg R: ReceiverResultReg).
+ 	jumpCmp := orNot
+ 					ifTrue: [cogit JumpZero: 0]
+ 					ifFalse: [cogit JumpNonZero: 0].
+ 	cogit annotate: (cogit MoveCw: objectMemory trueObject R: ReceiverResultReg)
+ 		objRef: objectMemory trueObject.
+ 	cogit RetN: retNoffset.
+ 	jumpCmp jmpTarget: (cogit annotate: (cogit MoveCw: objectMemory falseObject R: ReceiverResultReg)
+ 								objRef: objectMemory falseObject).
+ 	cogit RetN: retNoffset.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
+ genInnerPrimitiveIdentityHash: retNoffset
+ 	| jumpImm jumpSI jumpNotSet ret |
+ 	<var: #jumpSI type: #'AbstractInstruction *'>
+ 	<var: #jumpImm type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSet type: #'AbstractInstruction *'>
+ 	cogit MoveR: ReceiverResultReg R: ClassReg.
+ 	jumpImm := self genJumpImmediateInScratchReg: ClassReg.
+ 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
+ 	cogit CmpCq: ConstZero R: TempReg.
+ 	jumpNotSet := cogit JumpZero: 0.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	ret := cogit RetN: 0.
+ 	cogit MoveR: ReceiverResultReg R: ClassReg.
+ 	jumpSI := self genJumpSmallIntegerInScratchReg: ClassReg.
+ 	jumpSI jmpTarget: ret.
+ 	jumpImm jmpTarget: cogit Label.
+ 	self genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
+ 	self genSetCharacterTagsIn: ReceiverResultReg.
+ 	cogit Jump: ret.
+ 	jumpNotSet jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genRemoveCharacterTagsInScratchReg: (in category 'compile abstract instructions') -----
+ genRemoveCharacterTagsInScratchReg: scratchReg
+ 	cogit SubCq: objectMemory characterTag R: scratchReg!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genSetCharacterTagsIn: (in category 'compile abstract instructions') -----
+ genSetCharacterTagsIn: reg
+ 	cogit OrCq: objectMemory characterTag R: reg!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>isHashSetOnInstanceCreation (in category 'testing') -----
- isHashSetOnInstanceCreation
- 	^false!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveIdentical:orNotIf: (in category 'primitive generators') -----
+ genInnerPrimitiveIdentical: retNoffset orNotIf: orNot
+ 	| jumpCmp |
+ 	<var: #jumpCmp type: #'AbstractInstruction *'>
+ 	cogit CmpR: Arg0Reg R: ReceiverResultReg.
+ 	jumpCmp := orNot
+ 					ifTrue: [cogit JumpZero: 0]
+ 					ifFalse: [cogit JumpNonZero: 0].
+ 	cogit annotate: (cogit MoveCw: objectMemory trueObject R: ReceiverResultReg)
+ 		objRef: objectMemory trueObject.
+ 	cogit RetN: retNoffset.
+ 	jumpCmp jmpTarget: (cogit annotate: (cogit MoveCw: objectMemory falseObject R: ReceiverResultReg)
+ 								objRef: objectMemory falseObject).
+ 	cogit RetN: retNoffset.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
+ genInnerPrimitiveIdentityHash: retNOffset
+ 	| jumpSI |
+ 	<var: #jumpSI type: #'AbstractInstruction *'>
+ 	cogit MoveR: ReceiverResultReg R: ClassReg.
+ 	jumpSI := self genJumpSmallIntegerInScratchReg: ClassReg.
+ 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit RetN: retNOffset.
+ 	jumpSI jmpTarget: cogit Label.
+ 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>isHashSetOnInstanceCreation (in category 'testing') -----
- isHashSetOnInstanceCreation
- 	^true!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulation;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'print mc/cog frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  		add: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'short print mc/cog frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  		add: 'long print ext frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'long print mc/cog frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
+ 		add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
  		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor eip.
  											self writeBackHeadFramePointers];
  		addLine;
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action: [cogit disassembleCodeAt: cogit processor pc];
  		add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect.
  	self isThreadedVM ifTrue:
  		[aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  	aMenuMorph
  		addLine;
  		add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
  		add: 'print cog methods with prim...' action: [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  		add: 'print trampoline table' target: cogit action: #printTrampolineTable;
  		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  		add: 'set break pc (', (cogit breakPC isInteger ifTrue: [cogit breakPC hex] ifFalse: [cogit breakPC printString]), ')...' action: [(self promptHex: 'break pc') ifNotNil: [:bpc| cogit breakPC: bpc]];
  		add: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: (cogit printRegisters
  				ifTrue: ['no print registers each instruction']
  				ifFalse: ['print registers each instruction'])
  			action: [cogit printRegisters: cogit printRegisters not];
  		add: (cogit printInstructions
  				ifTrue: ['no print instructions each instruction']
  				ifFalse: ['print instructions each instruction'])
  			action: [cogit printInstructions: cogit printInstructions not];
  		addLine;
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
  											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: 'set break block...' action: [|s| s := UIManager default request: 'break block'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueakV3 (in category 'class initialization') -----
  initializePrimitiveTableForSqueakV3
  	"Initialize the table of primitive generators.  This does not include normal primitives implemened 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)
  		(2 genPrimitiveSubtract			1)
  		(3 genPrimitiveLessThan		1)
  		(4 genPrimitiveGreaterThan		1)
  		(5 genPrimitiveLessOrEqual		1)
  		(6 genPrimitiveGreaterOrEqual	1)
  		(7 genPrimitiveEqual			1)
  		(8 genPrimitiveNotEqual		1)
  		(9 genPrimitiveMultiply			1	processorHasMultiply:)
  		(10 genPrimitiveDivide			1	processorHasDivQuoRem:)
  		(11 genPrimitiveMod			1	processorHasDivQuoRem:)
  		(12 genPrimitiveDiv				1	processorHasDivQuoRem:)
  		(13 genPrimitiveQuo			1	processorHasDivQuoRem:)
  		(14 genPrimitiveBitAnd			1)
  		(15 genPrimitiveBitOr			1)
  		(16 genPrimitiveBitXor			1)
  		(17 genPrimitiveBitShift			1)
  		"(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			0)
  		(71 genPrimitiveNewWithArg	1)
  		"(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)
  		"(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 added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveAsCharacter (in category 'primitive generators') -----
+ genPrimitiveAsCharacter
+ 	| na r |
+ 	na := coInterpreter argumentCountOf: methodObj.
+ 	na <= 1 ifTrue:
+ 		[na = 1 ifTrue:
+ 			[self MoveMw: BytesPerWord r: SPReg R: Arg0Reg].
+ 		 (r := objectRepresentation
+ 				genInnerPrimitiveAsCharacter: 0
+ 				inReg: (na = 0 ifTrue: [ReceiverResultReg] ifFalse: [Arg0Reg])) < 0 ifTrue:
+ 			[^r]].
+ 	^self compileFallbackToInterpreterPrimitive!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveCharacterValue (in category 'primitive generators') -----
+ genPrimitiveCharacterValue
+ 	| r |
+ 	(r := objectRepresentation genInnerPrimitiveCharacterValue: BytesPerWord) < 0 ifTrue:
+ 		[^r].
+ 	^self compileFallbackToInterpreterPrimitive!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveIdentical (in category 'primitive generators') -----
  genPrimitiveIdentical
  	"Stack looks like
  		receiver (also in ResultReceiverReg)
  		arg
  		return address"
- 	| jumpFalse |
- 	<var: #jumpFalse type: #'AbstractInstruction *'>
  	self MoveMw: BytesPerWord r: SPReg R: TempReg.
+ 	^objectRepresentation
+ 		genInnerPrimitiveIdentical: BytesPerWord * 2
+ 		orNotIf: false!
- 	self CmpR: TempReg R: ReceiverResultReg.
- 	jumpFalse := self JumpNonZero: 0.
- 	self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 		objRef: objectMemory trueObject.
- 	self flag: 'currently caller pushes result'.
- 	self RetN: BytesPerWord * 2.
- 	jumpFalse jmpTarget: (self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 								objRef: objectMemory falseObject).
- 	self RetN: BytesPerWord * 2.
- 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveIdentityHash (in category 'primitive generators') -----
  genPrimitiveIdentityHash
+ 	| r |
+ 	(r := objectRepresentation genInnerPrimitiveIdentityHash: BytesPerWord) < 0 ifTrue:
+ 		[^r].
+ 	^self compileFallbackToInterpreterPrimitive!
- 	| jumpSI jumpNotSet |
- 	<var: #jumpSI type: #'AbstractInstruction *'>
- 	<var: #jumpNotSet type: #'AbstractInstruction *'>
- 	self MoveR: ReceiverResultReg R: ClassReg.
- 	jumpSI := objectRepresentation genJumpSmallIntegerInScratchReg: ClassReg.
- 	objectRepresentation genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
- 	objectRepresentation isHashSetOnInstanceCreation ifFalse:
- 		[self CmpCq: ConstZero R: TempReg.
- 		 jumpNotSet := self JumpZero: 0].
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self flag: 'currently caller pushes result'.
- 	self RetN: BytesPerWord.
- 	objectRepresentation isHashSetOnInstanceCreation ifFalse:
- 		[jumpNotSet jmpTarget: self Label.
- 		 self compileFallbackToInterpreterPrimitive].
- 	jumpSI jmpTarget: self Label.
- 	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveNotIdentical (in category 'primitive generators') -----
  genPrimitiveNotIdentical
  	"Stack looks like
  		receiver (also in ResultReceiverReg)
  		arg
  		return address"
- 	| jumpFalse |
- 	<var: #jumpFalse type: #'AbstractInstruction *'>
  	self MoveMw: BytesPerWord r: SPReg R: TempReg.
+ 	^objectRepresentation
+ 		genInnerPrimitiveIdentical: BytesPerWord * 2
+ 		orNotIf: true!
- 	self CmpR: TempReg R: ReceiverResultReg.
- 	jumpFalse := self JumpZero: 0.
- 	self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 		objRef: objectMemory trueObject.
- 	self flag: 'currently caller pushes result'.
- 	self RetN: BytesPerWord * 2.
- 	jumpFalse jmpTarget: (self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 								objRef: objectMemory falseObject).
- 	self RetN: BytesPerWord * 2.
- 	^0!

Item was changed:
  ----- Method: SpurMemoryManager>>isInRangeCharacterCode: (in category 'immediates') -----
  isInRangeCharacterCode: characterCode
+ 	^characterCode between: 0 and: (1 << 30) - 1!
- 	^characterCode >= 0 and: [characterCode < (2 raisedTo: 30)]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPrimitiveAsCharacter (in category 'primitive generators') -----
+ genPrimitiveAsCharacter
+ 	| na r |
+ 	na := coInterpreter argumentCountOf: methodObj.
+ 	na <= 1 ifTrue:
+ 		[(r := objectRepresentation
+ 				genInnerPrimitiveAsCharacter: 0
+ 				inReg: (na = 0 ifTrue: [ReceiverResultReg] ifFalse: [Arg0Reg])) < 0 ifTrue:
+ 			[^r]].
+ 	^self compileFallbackToInterpreterPrimitive!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPrimitiveCharacterValue (in category 'primitive generators') -----
+ genPrimitiveCharacterValue
+ 	| r |
+ 	(r := objectRepresentation genInnerPrimitiveCharacterValue: 0) < 0 ifTrue:
+ 		[^r].
+ 	^self compileFallbackToInterpreterPrimitive!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveIdentical (in category 'primitive generators') -----
  genPrimitiveIdentical
  	"Receiver and arg in registers.
  	 Stack looks like
  		return address"
+ 	^objectRepresentation
+ 		genInnerPrimitiveIdentical: 0
+ 		orNotIf: false!
- 	| jumpFalse |
- 	<var: #jumpFalse type: #'AbstractInstruction *'>
- 	self CmpR: Arg0Reg R: ReceiverResultReg.
- 	jumpFalse := self JumpNonZero: 0.
- 	self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 		objRef: objectMemory trueObject.
- 	self RetN: 0.
- 	jumpFalse jmpTarget: (self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 								objRef: objectMemory falseObject).
- 	self RetN: 0.
- 	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveIdentityHash (in category 'primitive generators') -----
  genPrimitiveIdentityHash
+ 	| r |
+ 	(r := objectRepresentation genInnerPrimitiveIdentityHash: 0) < 0 ifTrue:
+ 		[^r].
+ 	^self compileFallbackToInterpreterPrimitive!
- 	| jumpSI jumpNotSet |
- 	<var: #jumpSI type: #'AbstractInstruction *'>
- 	<var: #jumpNotSet type: #'AbstractInstruction *'>
- 	self MoveR: ReceiverResultReg R: ClassReg.
- 	jumpSI := objectRepresentation genJumpSmallIntegerInScratchReg: ClassReg.
- 	objectRepresentation genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
- 	objectRepresentation isHashSetOnInstanceCreation ifFalse:
- 		[self CmpCq: ConstZero R: TempReg.
- 		 jumpNotSet := self JumpZero: 0].
- 	self MoveR: TempReg R: ReceiverResultReg.
- 	self RetN: 0.
- 	objectRepresentation isHashSetOnInstanceCreation ifFalse:
- 		[jumpNotSet jmpTarget: self Label.
- 		 self compileFallbackToInterpreterPrimitive].
- 	jumpSI jmpTarget: self Label.
- 	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveNotIdentical (in category 'primitive generators') -----
  genPrimitiveNotIdentical
  	"Receiver and arg in registers.
  	 Stack looks like
  		return address"
+ 	^objectRepresentation
+ 		genInnerPrimitiveIdentical: 0
+ 		orNotIf: true!
- 	| jumpFalse |
- 	<var: #jumpFalse type: #'AbstractInstruction *'>
- 	self CmpR: Arg0Reg R: ReceiverResultReg.
- 	jumpFalse := self JumpZero: 0.
- 	self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
- 		objRef: objectMemory trueObject.
- 	self RetN: 0.
- 	jumpFalse jmpTarget: (self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
- 								objRef: objectMemory falseObject).
- 	self RetN: 0.
- 	^0!



More information about the Vm-dev mailing list