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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 14 18:14:33 UTC 2016


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

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

Name: VMMaker.oscog-eem.1631
Author: eem
Time: 13 January 2016, 10:12:40.901306 am
UUID: 310ad568-2096-4840-bd31-2f7b6eb06a55
Ancestors: VMMaker.oscog-eem.1630

StackInteerpreter:
Fix a simulation-time error in signed64BitIntegerFor:

CoInterpreter:
ceSend: et al need to add looked up methods to the method cache, otherwise methods only found through machine code sends will not be jitted.
Push ObjectMemory's freeStart: down to NewCoObjectMemory.  It's used only from Cogit.

Spur Cogits:
Add 16-bit accessing to Object & String at:[put:].  Ryan, Tim, can you check the MoveM16rR and MoveM16rR code for MIPSEL and ARM?  I think the ARM code is there, and the MIPSEL code looks to be nearly there also.

Add missing machine code primitives to 64-bit Spur.  Move "Spur"'s primitiveStringAt down to "32BitSpur".

Make the MirrorNewWithArg primitive do the class size check before accessing the format field.

Cogit:
Eliminate the bogus min/maxAbstractGeneralPurposeReg thang and use a register mask as Ryan suggested.

Fix debug printing of CogSimStackEntry.

Fix bugs in X64's MoveRMbr, MoveRXbrR.  SImplify rexw:r:x:b:.

Replace use of decorateDisassembly:for: with decorateDisassembly:for:fromAddress: in report recent intructions.

Worry:
Earlier the 64-bit Spur Cogit simulator was not working, then I ran the 64-bit Spur interpretersimulator, which worked, and then tried the 64-bit Spur Cogit, which miraculously started working again.  So there may be a misinitialization issue with the COgits which is fixed by first running the interpreter simulators. :-(.

=============== Diff against VMMaker.oscog-eem.1630 ===============

Item was changed:
  ----- Method: CoInterpreter>>ceCounterTripped: (in category 'cog jit support') -----
  ceCounterTripped: condition
  	"Two things are going on here.  The main one is catching a counter trip and attempting
  	 to send the SelectorCounterTripped selector.  In this case we would like to back-up
  	 the pc to the return address of the send that yields the boolean to be tested, so that
  	 after potential optimization, computation proceeds by retrying the jump.  But we cannot,
  	 since there may be no send, just a pop (as in and: [] and or: [] chains).  In this case we also
  	 want to prevent further callbacks until optimization is complete.  So we nil-out the
  	 SelectorCounterTripped entry in the specialSelectorArray.
  
  	 The minor case is that there is an unlikely  possibility that the cointer tripped but condition
  	 is not a boolean, in which case a mustBeBoolean response should occur."
  	<api>
  	<option: #SistaStackToRegisterMappingCogit>
  	"Send e.g. thisContext conditionalBranchCounterTrippedOn: boolean."
+ 	| context counterTrippedSelector classTag classObj |
- 	| context counterTrippedSelector classTag |
  	(condition = objectMemory falseObject
  	or: [condition = objectMemory trueObject]) ifFalse:
  		[^self ceSendMustBeBoolean: condition].
  
  	counterTrippedSelector := objectMemory maybeSplObj: SelectorCounterTripped.
  	(counterTrippedSelector isNil
  	or: [counterTrippedSelector = objectMemory nilObject]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
  	classTag := objectMemory
  					classTagForSpecialObjectsIndex: ClassMethodContext
  					compactClassIndex: ClassMethodContextCompactIndex.
  	(self lookupInMethodCacheSel: counterTrippedSelector classTag: classTag) ifFalse:
  	 	[messageSelector := counterTrippedSelector.
+ 		 classObj := objectMemory classForClassTag: classTag.
+ 		 (self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
- 		 (self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
+ 			 ^condition].
+ 		 self addNewMethodToCache: classObj].
- 			 ^condition]].
  
  	(primitiveFunctionPointer ~= 0
  	or: [(self argumentCountOf: newMethod) ~= 1]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
  	objectMemory splObj: SelectorCounterTripped put: objectMemory nilObject.
  	instructionPointer := self popStack.
  	context := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	self push: context.
  	self push: condition.
  	self ifAppropriateCompileToNativeCode: newMethod selector: counterTrippedSelector.
  	self activateNewMethod.
  	"not reached"
  	^true!

Item was changed:
  ----- Method: CoInterpreter>>ceSend:above:to:numArgs: (in category 'trampolines') -----
  ceSend: selector above: startAssociationArg to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked directed super send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  	startAssociation is an association whose value is the class above which to start the lookup.
  
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	<option: #BytecodeSetHasDirectedSuperSend>
+ 	| startAssociation classTag classObj errSelIdx cogMethod |
- 	| startAssociation classTag errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	startAssociation := objectMemory followMaybeForwarded: startAssociationArg.
  	classTag := objectMemory classTagForClass: (self superclassOf: (objectMemory fetchPointer: ValueIndex ofObject: startAssociation)).
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[self deny: (objectMemory isForwardedClassTag: classTag).
  			 (objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					above: startAssociation
  					to: rcvr
  					numArgs: numArgs].
  			 messageSelector := selector.
+ 			 classObj := objectMemory classForClassTag: classTag.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
- 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[(errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											receiver: rcvr
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: cogit noCheckEntryOffset
  							receiver: rcvr].
  				self handleMNU: errSelIdx
  					InMachineCodeTo: rcvr
+ 					classForMessage: classObj.
+ 				self assert: false "NOTREACHED"].
+ 			 self addNewMethodToCache: classObj].
- 					classForMessage: (objectMemory classForClassTag: classTag).
- 				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
  				  correct selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 cogMethod selector = selector
  			ifTrue:
  				[cogit
  					linkSendAt: (stackPages longAt: stackPointer)
  					in: (self mframeHomeMethod: framePointer)
  					to: cogMethod
  					offset: cogit noCheckEntryOffset
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSend:super:to:numArgs: (in category 'trampolines') -----
  ceSend: selector super: superNormalBar to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
+ 	| classTag classObj errSelIdx cogMethod |
- 	| classTag errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	superNormalBar = 0
  		ifTrue: [classTag := objectMemory fetchClassTagOf: rcvr]
  		ifFalse: [classTag := objectMemory classTagForClass: (self superclassOf: (self methodClassOf: (self frameMethodObject: framePointer)))].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceSend: (self handleForwardedSelectorFaultFor: selector)
  					super: superNormalBar
  					to: rcvr
  					numArgs: numArgs].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self assert: superNormalBar = 0.
  				^self
  					ceSend: selector
  					super: superNormalBar
  					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
  					numArgs: numArgs].
  			 messageSelector := selector.
+ 			 classObj := objectMemory classForClassTag: classTag.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
- 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[(errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											receiver: rcvr
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: (superNormalBar = 0
  									ifTrue: [cogit entryOffset]
  									ifFalse: [cogit noCheckEntryOffset])
  							receiver: rcvr].
+ 				self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: classObj.
+ 				self assert: false "NOTREACHED"].
+ 			 self addNewMethodToCache: classObj].
- 				self handleMNU: errSelIdx
- 					InMachineCodeTo: rcvr
- 					classForMessage: (objectMemory classForClassTag: classTag).
- 				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
  				  correct selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 cogMethod selector = selector
  			ifTrue:
  				[cogit
  					linkSendAt: (stackPages longAt: stackPointer)
  					in: (self mframeHomeMethod: framePointer)
  					to: cogMethod
  					offset: (superNormalBar = 0
  								ifTrue: [cogit entryOffset]
  								ifFalse: [cogit noCheckEntryOffset])
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSendAbort:to:numArgs: (in category 'trampolines') -----
  ceSendAbort: selector to: rcvr numArgs: numArgs
  	"Entry-point for an abort send in a CogMethod (aboutToReturn:through:, cannotReturn: et al).
  	 Try and dispatch the send, but the send may turn into an MNU in which case defer to
  	 handleMNUInMachineCodeTo:... which will dispatch the MNU.
  
  	 Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	 depending on whether the target method is cogged or not."
  	<api>
+ 	| classTag classObj errSelIdx |
- 	| classTag errSelIdx |
  	<inline: false>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	argumentCount := numArgs.
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[messageSelector := selector.
+ 			 classObj := objectMemory classForClassTag: classTag.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
+ 				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: classObj.
- 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
  				"NOTREACHED"
+ 				self assert: false].
+ 			 self addNewMethodToCache: classObj].
- 				self assert: false]].
  	instructionPointer := self popStack.
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[self executeNewMethod.
  		 self assert: false
  		 "NOTREACHED"].
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSendFromInLineCacheMiss: (in category 'trampolines') -----
  ceSendFromInLineCacheMiss: cogMethodOrPIC
  	"Send from an Open PIC when the first-level method lookup probe has failed,
  	 or to continue when PIC creation has failed (e.g. because we're out of code space),
  	 or when a send has failed due to a forwarded receiver."
  	<api>
  	<var: #cogMethodOrPIC type: #'CogMethod *'>
+ 	| numArgs rcvr classTag classObj errSelIdx |
- 	| numArgs rcvr classTag errSelIdx |
  	"self printFrame: stackPage headFP WithSP: stackPage headSP"
  	"self printStringOf: selector"
  	numArgs := cogMethodOrPIC cmNumArgs.
  	rcvr := self stackValue: numArgs + 1. "skip return pc"
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: cogMethodOrPIC selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: cogMethodOrPIC selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: cogMethodOrPIC selector) ifTrue:
  				[self handleForwardedSelectorFaultFor: cogMethodOrPIC selector.
  				 ^self ceSendFromInLineCacheMiss: cogMethodOrPIC].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc".
  				 ^self ceSendFromInLineCacheMiss: cogMethodOrPIC].
  			 messageSelector := cogMethodOrPIC selector.
+ 			 classObj := objectMemory classForClassTag: classTag.
+ 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
+ 				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: classObj.
- 			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
- 				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
  				"NOTREACHED"
+ 				self assert: false].
+ 			 self addNewMethodToCache: classObj].
- 				self assert: false]].
  	instructionPointer := self popStack.
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[self executeNewMethod.
  		 self assert: false
  		 "NOTREACHED"].
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was removed:
- ----- Method: CogARMCompiler>>minAbstractGeneralPurposeReg (in category 'accessing') -----
- minAbstractGeneralPurposeReg
- 	"Answer the smallest index of an abstract general-purpose register used by this compiler.
- 	 N.B.  Abstract registers are negative numbers."
- 	<inline: true>
- 	^Scratch0Reg!

Item was added:
+ ----- Method: CogARMCompiler>>strh:rn:rm: (in category 'ARM convenience instructions') -----
+ strh: srcReg rn: baseReg rm: offsetReg
+ "	STRH srcReg, [baseReg, +offsetReg]"
+ 	^self memM16xr: AL reg: srcReg base: baseReg p: 1 u: 1 w: 0 l: 0 rm: offsetReg!

Item was removed:
- ----- Method: CogAbstractInstruction>>minAbstractGeneralPurposeReg (in category 'accessing') -----
- minAbstractGeneralPurposeReg
- 	"Answer the smallest index of an abstract general-purpose register used by this compiler.
- 	 N.B.  Abstract registers are negative numbers."
- 	<inline: true>
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: CogIA32Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^N forms are to get around the bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^0].
  		[AlignmentNops]		-> [^(operands at: 0) - 1].
  		[Fill32]					-> [^4].
  		[Nop]					-> [^1].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^1].
  		[IDIVR]					-> [^2].
  		[IMULRR]				-> [^3].
  		[CPUID]					-> [^2].
  		[CMPXCHGAwR]			-> [^7].
  		[CMPXCHGMwrR]		-> [^(operands at: 1) = ESP
  										ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
  										ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
  		[LFENCE]				-> [^3].
  		[MFENCE]				-> [^3].
  		[SFENCE]				-> [^3].
  		[LOCK]					-> [^1].
  		[XCHGAwR]				-> [^6].
  		[XCHGMwrR]			-> [^(operands at: 1) = ESP
  										ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]
  										ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [3] ifFalse: [6]]].
  		[XCHGRR]				-> [^((operands at: 0) = EAX
  									   or: [(operands at: 1) = EAX])
  										ifTrue: [1]
  										ifFalse: [2]].
  		"Control"
  		[CallFull]					-> [^5].
  		[Call]						-> [^5].
  		[JumpR]						-> [^2].
  		[JumpFull]					-> [self resolveJumpTarget. ^5].
  		[JumpLong]					-> [self resolveJumpTarget. ^5].
  		[Jump]						-> [self resolveJumpTarget. ^5].
  		[JumpZero]					-> [self resolveJumpTarget. ^6].
  		[JumpNonZero]				-> [self resolveJumpTarget. ^6].
  		[JumpNegative]				-> [self resolveJumpTarget. ^6].
  		[JumpNonNegative]			-> [self resolveJumpTarget. ^6].
  		[JumpOverflow]				-> [self resolveJumpTarget. ^6].
  		[JumpNoOverflow]			-> [self resolveJumpTarget. ^6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpNoCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpLess]					-> [self resolveJumpTarget. ^6].
  		[JumpGreaterOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpGreater]				-> [self resolveJumpTarget. ^6].
  		[JumpLessOrEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpAbove]				-> [self resolveJumpTarget. ^6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^6].
  		[JumpFPEqual]				-> [self resolveJumpTarget. ^6].
  		[JumpFPNotEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLess]				-> [self resolveJumpTarget. ^6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLessOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpFPOrdered]			-> [self resolveJumpTarget. ^6].
  		[JumpFPUnordered]			-> [self resolveJumpTarget. ^6].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [1] ifFalse: [3]].
  		[Stop]						-> [^1].
  
  		"Arithmetic"
  		[AddCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(operands at: 1) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AndCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(operands at: 1) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[CmpCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(operands at: 1) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[OrCqR]			-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(operands at: 1) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[SubCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(operands at: 1) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[TstCqR]		-> [^((self isQuick: (operands at: 0)) and: [(operands at: 1) < 4])
  											ifTrue: [3]
  											ifFalse: [(operands at: 1) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AddCwR]		-> [^(operands at: 1) = EAX ifTrue: [5] ifFalse: [6]].
  		[AndCwR]		-> [^(operands at: 1) = EAX ifTrue: [5] ifFalse: [6]].
  		[CmpCwR]		-> [^(operands at: 1) = EAX ifTrue: [5] ifFalse: [6]].
  		[OrCwR]		-> [^(operands at: 1) = EAX ifTrue: [5] ifFalse: [6]].
  		[SubCwR]		-> [^(operands at: 1) = EAX ifTrue: [5] ifFalse: [6]].
  		[XorCwR]		-> [^(operands at: 1) = EAX ifTrue: [5] ifFalse: [6]].
  		[AddRR]			-> [^2].
  		[AndRR]			-> [^2].
  		[CmpRR]		-> [^2].
  		[OrRR]			-> [^2].
  		[XorRR]			-> [^2].
  		[SubRR]			-> [^2].
  		[NegateR]		-> [^2].
  		[LoadEffectiveAddressMwrR]
  						-> [^((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((operands at: 1) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[LogicalShiftLeftCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[LogicalShiftRightCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[ArithmeticShiftRightCqR]	-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[LogicalShiftLeftRR]			-> [^self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [^self computeShiftRRSize].
  		[ArithmeticShiftRightRR]		-> [^self computeShiftRRSize].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		"Data Movement"
  		[MoveCqR]		-> [^(operands at: 0) = 0 ifTrue: [2] ifFalse: [5]].
  		[MoveCwR]		-> [^5].
  		[MoveRR]		-> [^2].
  		[MoveRdRd]		-> [^4].
  		[MoveAwR]		-> [^(operands at: 1) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRAw]		-> [^(operands at: 0) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveAbR]		-> [^7].
  		[MoveRAb]		-> [^(operands at: 0) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRMwr]	-> [^((self isQuick: (operands at: 1))
  									ifTrue: [((operands at: 1) = 0
  											and: [(operands at: 2) ~= EBP])
  												ifTrue: [2]
  												ifFalse: [3]]
  									ifFalse: [6])
  								+ ((operands at: 2) = ESP
  									ifTrue: [1]
  									ifFalse: [0])].
  		[MoveRdM64r]	-> [^((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((operands at: 2) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMbrR]		-> [^(operands at: 1) = ESP
  								ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
  								ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
  		[MoveRMbr]		-> [^(operands at: 2) = ESP
  								ifTrue: [7]
  								ifFalse: [(self isQuick: (operands at: 1)) ifTrue: [3] ifFalse: [6]]].
  		[MoveM16rR]	-> [^(operands at: 1) = ESP
  								ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
  								ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
+ 		[MoveRM16r]	-> [^(operands at: 2) = ESP
+ 								ifTrue: [8]
+ 								ifFalse: [(self isQuick: (operands at: 1)) ifTrue: [4] ifFalse: [7]]].
  		[MoveM64rRd]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((operands at: 1) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMwrR]		-> [^((self isQuick: (operands at: 0))
  									ifTrue: [((operands at: 0) = 0
  											and: [(operands at: 1) ~= EBP])
  												ifTrue: [2]
  												ifFalse: [3]]
  									ifFalse: [6])
  								+ ((operands at: 1) = ESP
  									ifTrue: [1]
  									ifFalse: [0])].
  		[MoveXbrRR]	-> [self assert: (operands at: 0) ~= ESP.
  							^(operands at: 1) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (operands at: 1) ~= ESP.
  							^((operands at: 2) = EBP
  											ifTrue: [4]
  											ifFalse: [3])
  										+ ((operands at: 0) >= 4
  											ifTrue: [2]
  											ifFalse: [0])].
  		[MoveXwrRR]	-> [self assert: (operands at: 0) ~= ESP.
  							^(operands at: 1) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (operands at: 1) ~= ESP.
  							^(operands at: 2) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[PopR]			-> [^1].
  		[PushR]			-> [^1].
  		[PushCq]		-> [^(self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^5].
  		[PrefetchAw]	-> [^self hasSSEInstructions ifTrue: [7] ifFalse: [0]].
  		"Conversion"
  		[ConvertRRd]	-> [^4] }.
  	^0 "to keep C compiler quiet"!

Item was added:
+ ----- Method: CogIA32Compiler>>concretizeMoveRM16r (in category 'generate machine code') -----
+ concretizeMoveRM16r
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg offset destReg |
+ 	offset := operands at: 1.
+ 	srcReg := operands at: 0.
+ 	destReg := operands at: 2.
+ 	destReg ~= ESP ifTrue:
+ 		[(self isQuick: offset) ifTrue:
+ 			[machineCode
+ 				at: 0 put: 16r66;
+ 				at: 1 put: 16r89;
+ 				at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
+ 				at: 3 put: (offset bitAnd: 16rFF).
+ 			 ^machineCodeSize := 4].
+ 		machineCode
+ 			at: 0 put: 16r66;
+ 			at: 1 put: 16r89;
+ 			at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
+ 			at: 3 put: (offset bitAnd: 16rFF);
+ 			at: 4 put: (offset >> 8 bitAnd: 16rFF);
+ 			at: 5 put: (offset >> 16 bitAnd: 16rFF);
+ 			at: 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^machineCodeSize := 7].
+ 	machineCode
+ 		at: 0 put: 16r66;
+ 		at: 1 put: 16r89;
+ 		at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
+ 		at: 3 put: (self s: SIB1 i: 4 b: destReg);
+ 		at: 4 put: (offset bitAnd: 16rFF);
+ 		at: 5 put: (offset >> 8 bitAnd: 16rFF);
+ 		at: 6 put: (offset >> 16 bitAnd: 16rFF);
+ 		at: 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogIA32Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	<returnTypeC: #void>
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill32]				-> [^self concretizeFill32].
  		[Nop]				-> [^self concretizeNop].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
  		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
  		[LFENCE]				-> [^self concretizeFENCE: 5].
  		[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7].
  		[LOCK]					-> [^self concretizeLOCK].
  		[XCHGAwR]				-> [^self concretizeXCHGAwR].
  		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallFull]				-> [^self concretizeCall].
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpLong].
  		[JumpLong]				-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeAddCwR].
  		[AddRR]						-> [^self concretizeOpRR: 16r03].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[AndRR]						-> [^self concretizeOpRR: 16r23].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[CmpRR]					-> [^self concretizeReverseOpRR: 16r39].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[OrCqR]						-> [^self concretizeOrCqR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[OrRR]						-> [^self concretizeOpRR: 16r0B].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[SubRR]						-> [^self concretizeOpRR: 16r2B].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[XorCwR]						-> [^self concretizeXorCwR].
  		[XorRR]							-> [^self concretizeOpRR: 16r33].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeReverseOpRR: 16r89].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
+ 		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd] }!

Item was removed:
- ----- Method: CogIA32Compiler>>minAbstractGeneralPurposeReg (in category 'accessing') -----
- minAbstractGeneralPurposeReg
- 	"Answer the smallest index of an abstract general-purpose register used by this compiler.
- 	 N.B.  Abstract registers are negative numbers."
- 	<inline: true>
- 	^Arg1Reg!

Item was added:
+ ----- Method: CogIA32CompilerTests>>testMoveM16rR (in category 'tests') -----
+ testMoveM16rR
+ 	"self new testMoveM16rR"
+ 	CogIA32CompilerForTests registersWithNamesDo:
+ 		[:sreg :srname|
+ 		CogIA32CompilerForTests registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveM16rR operand: offset operand: sreg operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'movzwl 0x', (offset hex allButFirst: 3), '(', srname, '), ', drname.
+ 						self assert: herIntended equals: plainJane.
+ 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogIA32CompilerTests>>testMoveRM16r (in category 'tests') -----
+ testMoveRM16r
+ 	"self new testMoveRM16r"
+ 	CogIA32CompilerForTests registersWithNamesDo:
+ 		[:sreg :srname|
+ 		CogIA32CompilerForTests registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveRM16r operand: sreg operand: offset operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'movw ', (srname copyWithout: $e), ', 0x', (offset hex allButFirst: 3), '(', drname, ')'.
+ 						self assert: herIntended equals: plainJane.
+ 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogIA32CompilerTests>>testMoveRXbrR (in category 'tests') -----
+ testMoveRXbrR
+ 	"self new testMoveRXbrR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:idxreg :irname|
+ 		irname ~= '%esp' ifTrue:
+ 			[self concreteCompilerClass registersWithNamesDo:
+ 				[:basereg :brname|
+ 				self concreteCompilerClass byteRegistersWithNamesDo:
+ 					[:sreg :srname| | inst len |
+ 					inst := self gen: MoveRXbrR operand: sreg operand: idxreg operand: basereg.
+ 					len := inst concretizeAt: 0.
+ 					self processor
+ 						disassembleInstructionAt: 0
+ 						In: inst machineCode object
+ 						into: [:str :sz| | plainJane herIntended |
+ 							plainJane := self strip: str.
+ 							herIntended := 'movb ', srname, ', (', brname, ',', irname, ',1)'.
+ 							self assert: herIntended equals: plainJane.
+ 							self assert: len = sz]]]]]!

Item was added:
+ ----- Method: CogIA32CompilerTests>>testMoveRXwrR (in category 'tests') -----
+ testMoveRXwrR
+ 	"self new testMoveRXwrR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:idxreg :irname|
+ 		irname ~= '%esp' ifTrue:
+ 			[self concreteCompilerClass registersWithNamesDo:
+ 				[:basereg :brname|
+ 				self concreteCompilerClass registersWithNamesDo:
+ 					[:sreg :srname| | inst len |
+ 					inst := self gen: MoveRXwrR operand: sreg operand: idxreg operand: basereg.
+ 					len := inst concretizeAt: 0.
+ 					self processor
+ 						disassembleInstructionAt: 0
+ 						In: inst machineCode object
+ 						into: [:str :sz| | plainJane herIntended |
+ 							plainJane := self strip: str.
+ 							herIntended := 'movl ', srname, ', (', brname, ',', irname, ',4)'.
+ 							self assert: herIntended equals: plainJane.
+ 							self assert: len = sz]]]]]!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveXbrRR (in category 'tests') -----
  testMoveXbrRR
  	"self new testMoveXbrRR"
  	CogIA32CompilerForTests registersWithNamesDo:
  		[:idxreg :irname|
  		irname ~= '%esp' ifTrue:
  			[CogIA32CompilerForTests registersWithNamesDo:
  				[:basereg :brname|
  				CogIA32CompilerForTests registersWithNamesDo:
+ 					[:dreg :drname| | inst len |
+ 					inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
+ 					len := inst concretizeAt: 0.
+ 					self processor
+ 						disassembleInstructionAt: 0
+ 						In: inst machineCode object
+ 						into: [:str :sz| | plainJane herIntended |
+ 							"Convert e.g. '00000000: movzbl %ds:(%eax,%eax,1), %eax : 0F B6 04 00 ' to  'movzbl (%eax,%eax,1)'"
+ 							plainJane := self strip: str.
+ 							herIntended := 'movzbl (', brname, ',', irname, ',1), ',drname.
+ 							self assert: herIntended equals: plainJane.
+ 							self assert: len = sz]]]]]!
- 					[:dreg :drname|
- 					((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 						[:offset| | inst len |
- 						inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
- 						len := inst concretizeAt: 0.
- 						self processor
- 							disassembleInstructionAt: 0
- 							In: inst machineCode object
- 							into: [:str :sz| | plainJane herIntended |
- 								"Convert e.g. '00000000: movzbl %ds:(%eax,%eax,1), %eax : 0F B6 04 00 ' to  'movzbl (%eax,%eax,1)'"
- 								plainJane := self strip: str.
- 								herIntended := 'movzbl (', brname, ',', irname, ',1), ',drname.
- 								self assert: herIntended equals: plainJane.
- 								self assert: len = sz]]]]]]!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveXwrRR (in category 'tests') -----
  testMoveXwrRR
  	"self new testMoveXwrRR"
  	CogIA32CompilerForTests registersWithNamesDo:
  		[:idxreg :irname|
  			irname ~= '%esp' ifTrue:
  				[CogIA32CompilerForTests registersWithNamesDo:
  					[:basereg :brname|
  					CogIA32CompilerForTests registersWithNamesDo:
+ 						[:dreg :drname| | inst len |
+ 						inst := self gen: MoveXwrRR operand: idxreg operand: basereg operand: dreg.
+ 						len := inst concretizeAt: 0.
+ 						self processor
+ 							disassembleInstructionAt: 0
+ 							In: inst machineCode object
+ 							into: [:str :sz| | plainJane herIntended |
+ 								"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 								plainJane := self strip: str.
+ 								herIntended := 'movl (', brname, ',', irname, ',4), ',drname.
+ 								self assert: herIntended equals: plainJane.
+ 								self assert: len = sz]]]]]!
- 						[:dreg :drname|
- 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 							[:offset| | inst len |
- 							inst := self gen: MoveXwrRR operand: idxreg operand: basereg operand: dreg.
- 							len := inst concretizeAt: 0.
- 							self processor
- 								disassembleInstructionAt: 0
- 								In: inst machineCode object
- 								into: [:str :sz| | plainJane herIntended |
- 									"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
- 									plainJane := self strip: str.
- 									herIntended := 'movl (', brname, ',', irname, ',4), ',drname.
- 									self assert: herIntended equals: plainJane.
- 									self assert: len = sz]]]]]]!

Item was removed:
- ----- Method: CogMIPSELCompiler>>minAbstractGeneralPurposeReg (in category 'accessing') -----
- minAbstractGeneralPurposeReg
- 	"Answer the smallest index of an abstract general-purpose register used by this compiler.
- 	 N.B.  Abstract registers are negative numbers."
- 	<inline: true>
- 	self flag: #bogus. "The caller should ask for a register mask, not a range."
- 	^TempReg!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genConvertCharacterToSmallIntegerInReg: (in category 'compile abstract instructions') -----
  genConvertCharacterToSmallIntegerInReg: reg
+ 	"Convert the Character in reg to a SmallInteger, assuming
+ 	 the Character's value is a valid character."
- 	"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 changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveAt (in category 'primitive generators') -----
  genPrimitiveAt
- 	"Implement the guts of primitiveAt"
  	| formatReg convertToIntAndReturn
  	  jumpNotIndexable jumpImmediate jumpBadIndex
  	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig jumpIsArray jumpHasFixedFields jumpIsContext
  	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds |
- 	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #convertToIntAndReturn type: #'AbstractInstruction *'>
  	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpFixedFieldsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
  	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpIsArray := cogit JumpZero: 0.
  	jumpNotIndexable := cogit JumpBelow: 0.
  					cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpHasFixedFields := cogit JumpBelowOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jumpIsWords := cogit JumpAboveOrEqual: 0.
  	"For now ignore 64-bit indexability."
  	jumpNotIndexable jmpTarget: cogit Label.
  	jumpNotIndexable := cogit Jump: 0.
  
  	jumpIsBytes jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
  		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
  	cogit backEnd byteReadsZeroExtend
  		ifTrue:
  			[cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg]
  		ifFalse:
  			[cogit "formatReg already contains a value <= 16r1f, so no need to zero it"
  				MoveXbr: Arg1Reg R: ReceiverResultReg R: formatReg;
  				MoveR: formatReg R: ReceiverResultReg].
  	convertToIntAndReturn := cogit Label.
  	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsShorts jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg).
  		cogit AndCq: 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
  	cogit Jump: convertToIntAndReturn.
  
  	jumpIsWords jmpTarget:
  		(cogit CmpR: Arg1Reg R: ClassReg).
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: TempReg.
  	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	jumpWordTooBig := self jumpNotSmallIntegerUnsignedValueInRegister: TempReg.
  	cogit MoveR: TempReg R: ReceiverResultReg.
  	cogit Jump: convertToIntAndReturn.
  
  	jumpHasFixedFields jmpTarget:
  		(cogit AndCq: objectMemory classIndexMask R: TempReg).
  	cogit MoveR: TempReg R: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: TempReg.
  	jumpIsContext := cogit JumpZero: 0.
  	cogit PushR: ClassReg.
  	self genGetClassObjectOfClassIndex: formatReg into: ClassReg scratchReg: TempReg.
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ClassReg destReg: formatReg.
  	cogit PopR: ClassReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit
  		AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg;
  		SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpFixedFieldsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	"index is (formatReg (fixed fields) + Arg1Reg (0-rel index)) * wordSize + baseHeaderSize"
  	cogit AddR: formatReg R: Arg1Reg.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsArray jmpTarget:
  		(cogit CmpR: Arg1Reg R: ClassReg).
  	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.	
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpFixedFieldsOutOfBounds jmpTarget:
  	(jumpArrayOutOfBounds jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsOutOfBounds jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpWordTooBig jmpTarget:
  	(jumpNotIndexable jmpTarget:
  	(jumpIsContext jmpTarget:
  	(jumpBadIndex jmpTarget:
  	(jumpImmediate jmpTarget: cogit Label))))))))).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveAtPut (in category 'primitive generators') -----
  genPrimitiveAtPut
- 	"Implement the guts of primitiveAtPut"
  	| formatReg jumpImmediate jumpBadIndex jumpImmutable
  	  jumpNotIndexablePointers jumpNotIndexableBits
  	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpHasFixedFields
  	  jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
  	  jumpWordsOutOfBounds jumpBytesOutOfBounds jumpBytesOutOfRange
  	  jumpNonSmallIntegerValue jumpNegative jumpShortsUnsupported jumpNotPointers
  	  |
- 	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpNegative type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexableBits type: #'AbstractInstruction *'>
  	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexablePointers type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
  	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
  	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self cppIf: IMMUTABILITY
  		ifTrue:
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  		jumpImmutable := self genJumpBaseHeaderImmutable: TempReg ]
  		ifFalse: 
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: NoReg ].
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpNotPointers := cogit JumpAbove: 0.
  	"optimistic store check; assume index in range (almost always is)."
  	self genStoreCheckReceiverReg: ReceiverResultReg
  		valueReg: Arg1Reg
  		scratchReg: TempReg
  		inFrame: false.
  
  	cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpNotIndexablePointers := cogit JumpBelow: 0.
  	jumpHasFixedFields := cogit JumpNonZero: 0.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
  	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpHasFixedFields jmpTarget: cogit Label.
  	self genGetClassIndexOfNonImm: ReceiverResultReg into: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: formatReg.
  	jumpIsContext := cogit JumpZero: 0.
  	"get # fixed fields in formatReg"
  	cogit PushR: ClassReg.
  	self genGetClassObjectOfClassIndex: formatReg into: ClassReg scratchReg: TempReg.
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ClassReg destReg: formatReg.
  	cogit PopR: ClassReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg.
  	cogit SubR: formatReg R: ClassReg.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: formatReg.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpFixedFieldsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddR: formatReg R: Arg0Reg.
  	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpNotPointers jmpTarget:
  		(cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg).
  	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
  	jumpNonSmallIntegerValue := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
  					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpShortsUnsupported := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	"For now ignore 64-bit indexability."
  	jumpNotIndexableBits := cogit JumpBelow: 0.
  
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	(cogit lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
  		[self CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
  	jumpNegative := cogit JumpNegative: 0.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
  	cogit MoveR: TempReg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsBytes jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: 255) R: Arg1Reg).
  	jumpBytesOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
  	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg;
  	CmpR: Arg0Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
  	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	"there are no shorts as yet.  so this is dead code:
  	jumpIsShorts jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
  	jumpShortsOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
  	cogit AndCq: 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg;
  	CmpR: Arg0Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	cogit genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddR: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	jumpShortsDone := cogit Jump: 0."
  
  	jumpIsContext jmpTarget: 
  	(jumpNegative jmpTarget:
  	(jumpNotIndexableBits jmpTarget:
  	(jumpBytesOutOfRange jmpTarget:
  	(jumpIsCompiledMethod jmpTarget:
  	(jumpArrayOutOfBounds jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsUnsupported jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpNotIndexablePointers jmpTarget:
  	(jumpNonSmallIntegerValue jmpTarget:
  	(jumpFixedFieldsOutOfBounds jmpTarget: cogit Label))))))))))).
  	
  	self cppIf: IMMUTABILITY ifTrue: [ jumpImmutable jmpTarget: cogit Label ].
  
  	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
  	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
  
  	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
  
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveMirrorNewWithArg (in category 'primitive generators') -----
  genPrimitiveMirrorNewWithArg
  	"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 *'>
  
  	self assert: cogit methodNumArgs = 2.
  	cogit genLoadArgAtDepth: 1 into: Arg0Reg. "class arg"
  	cogit genLoadArgAtDepth: 0 into: Arg1Reg. "num indexable slots arg"
  
  	"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"
  	jumpNElementsNonInt := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
  
  	"Is the class arg pointers with at least 3 fields?"
  	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
+ 	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
+ 	jumpTooSmall := cogit JumpLess: 0.
  
+ 	"fail if not indexable class"
  	self genGetFormatOf: Arg0Reg
  		into: TempReg
  		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
  	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 genPrimitiveNewWithArg) expects class
- 	"The basicNew: code below (copied from 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 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 genPrimReturn.
  
  	"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 added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveStringAt (in category 'primitive generators') -----
+ genPrimitiveStringAt
+ 	| formatReg jumpNotIndexable jumpBadIndex done
+ 	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig
+ 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds |
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	<var: #done type: #'AbstractInstruction *'>
+ 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpIsShorts type: #'AbstractInstruction *'>
+ 	<var: #jumpIsWords type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
+ 
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: Arg1Reg.
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
+ 	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
+ 
+ 	self genGetFormatOf: ReceiverResultReg
+ 		into: (formatReg := SendNumArgsReg)
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
+ 
+ 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
+ 
+ 	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
+ 		  0 = 0 sized objects (UndefinedObject True False et al)
+ 		  1 = non-indexable objects with inst vars (Point et al)
+ 		  2 = indexable objects with no inst vars (Array et al)
+ 		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		  4 = weak indexable objects with inst vars (WeakArray et al)
+ 		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		  6 unused, reserved for exotic pointer objects?
+ 		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 		  8 unused, reserved for exotic non-pointer objects?
+ 		  9 (?) 64-bit indexable
+ 		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable
+ 		16 - 23 byte indexable
+ 		24 - 31 compiled method"
+ 	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	jumpIsWords := cogit JumpGreaterOrEqual: 0.
+ 	jumpNotIndexable := cogit Jump: 0.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
+ 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
+ 	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
+ 	cogit backEnd byteReadsZeroExtend ifFalse:
+ 			[cogit AndCq: 255 R: ReceiverResultReg].
+ 	done := cogit Label.
+ 	self genConvertIntegerToCharacterInReg: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsShorts jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg).
+ 		cogit AndCq: 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddR: Arg1Reg R: ReceiverResultReg.
+ 	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
+ 	cogit Jump: done.
+ 
+ 	jumpIsWords jmpTarget:
+ 		(cogit CmpR: Arg1Reg R: ClassReg).
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: TempReg.
+ 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	jumpWordTooBig := self jumpNotCharacterUnsignedValueInRegister: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit Jump: done.
+ 
+ 	jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpWordTooBig jmpTarget:
+ 	(jumpNotIndexable jmpTarget: 
+ 	(jumpBadIndex jmpTarget: cogit Label))))).
+ 
+ 	^CompletePrimitive!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>genPrimitiveStringAtPut (in category 'primitive generators') -----
  genPrimitiveStringAtPut
+ 	| formatReg jumpBadIndex jumpBadArg jumpShortsDone jumpWordsDone
+ 	  jumpBytesOutOfRange jumpShortsOutOfRange jumpWordsOutOfRange
+ 	  jumpIsBytes jumpIsShorts jumpNotString jumpIsCompiledMethod jumpImmutable
+ 	  jumpBytesOutOfBounds jumpWordsOutOfBounds jumpShortsOutOfBounds |
- 	"Implement the guts of primitiveStringAtPut"
- 	| formatReg jumpBadIndex jumpBadArg jumpWordsDone jumpBytesOutOfRange
- 	  jumpIsBytes jumpNotString jumpIsCompiledMethod jumpImmutable
- 	  jumpBytesOutOfBounds jumpWordsOutOfBounds jumpShortsUnsupported |
- 	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpBadArg type: #'AbstractInstruction *'>
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsDone type: #'AbstractInstruction *'>
  	<var: #jumpWordsDone type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpShortsUnsupported type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
  	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
  
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg.
  	cogit MoveR: Arg1Reg R: TempReg.
  	jumpBadArg := self genJumpNotCharacterInScratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
  	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self cppIf: IMMUTABILITY
  		ifTrue:
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  		jumpImmutable := self genJumpBaseHeaderImmutable: TempReg ]
  		ifFalse: 
  		[ self genGetFormatOf: ReceiverResultReg
  			into: (formatReg := SendNumArgsReg)
  			leastSignificantHalfOfBaseHeaderIntoScratch: NoReg ].
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format; words and/or bytes.
  		  0 to 8 = pointer objects, forwarders, reserved.
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable
- 		12 - 15 16-bit indexable (but unused)
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jumpNotString := cogit JumpBelowOrEqual: 0.
  					cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
  	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
- 	jumpShortsUnsupported := cogit JumpGreaterOrEqual: 0.
  
+ 	cogit CmpCq: 0 R: Arg1Reg.
+ 	jumpWordsOutOfRange := cogit JumpLess: 0.
  	cogit CmpR: Arg0Reg R: ClassReg.
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
  	cogit MoveR: TempReg Xwr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	jumpWordsDone := cogit Jump: 0.
  
- 	"there are no shorts as yet.  so this is dead code:
  	jumpIsShorts jmpTarget:
+ 		(cogit CmpCq: (objectMemory characterObjectOf: 65535) R: Arg1Reg).
- 		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
  	jumpShortsOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
  	cogit AndCq: 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg;
  	CmpR: Arg0Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
- 	cogit genConvertSmallIntegerToIntegerInReg: TempReg.
  	cogit AddR: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	jumpShortsDone := cogit Jump: 0.
- 	jumpShortsDone := cogit Jump: 0."
  
  	jumpIsBytes jmpTarget:
  		(cogit CmpCq: (objectMemory characterObjectOf: 255) R: Arg1Reg).
  	jumpBytesOutOfRange := cogit JumpAbove: 0.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
  	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  	cogit SubR: formatReg R: ClassReg;
  	CmpR: Arg0Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit MoveR: Arg1Reg R: TempReg.
  	self genConvertCharacterToCodeInReg: TempReg.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
  	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  
+ 	jumpShortsDone jmpTarget:
+ 	(jumpWordsDone jmpTarget: cogit genPrimReturn).
- 	jumpWordsDone jmpTarget: cogit genPrimReturn.
  
+ 	jumpNotString jmpTarget:
- 	jumpBadArg jmpTarget:
- 	(jumpNotString jmpTarget:
  	(jumpBytesOutOfRange jmpTarget:
+ 	(jumpShortsOutOfRange jmpTarget:
+ 	(jumpWordsOutOfRange jmpTarget:
  	(jumpIsCompiledMethod jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget: cogit Label))))))).
- 	(jumpShortsUnsupported jmpTarget:
- 	(jumpWordsOutOfBounds jmpTarget: cogit Label)))))).
  
  	self cppIf: IMMUTABILITY
  		ifTrue: [jumpImmutable jmpTarget: cogit Label].
  
  	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
  	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
  
+ 	jumpBadArg jmpTarget:
+ 	(jumpBadIndex jmpTarget: cogit Label).
- 	jumpBadIndex jmpTarget: cogit Label.
  
+ 	^CompletePrimitive!
- 	^0!

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

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genConvertCharacterToSmallIntegerInReg: (in category 'compile abstract instructions') -----
  genConvertCharacterToSmallIntegerInReg: reg
+ 	"Convert the Character in reg to a SmallInteger, assuming
+ 	 the Character's value is a valid character."
- 	"Convert the SmallInteger in reg to a Character, assuming
- 	 the SmallInteger's value is a valid character."
  	cogit SubCq: objectMemory characterTag - objectMemory smallIntegerTag R: reg!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>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."
+ 	cogit AddCq: objectMemory characterTag - objectMemory smallIntegerTag R: reg!
- 	self assert: (objectMemory characterTag = 2 and: [objectMemory smallIntegerTag = 1]).
- 	cogit AddCq: 1 R: reg!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpCharacter:scratchReg: (in category 'compile abstract instructions') -----
+ genJumpCharacter: reg scratchReg: scratch
+ 	"Generate a compare and branch to test if aRegister contains a Character.
+ 	 Answer the jump.  Override since scratch is needed."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit
+ 		AndCq: objectMemory tagMask R: reg R: scratch;
+ 		CmpCq: objectMemory characterTag R: scratch;
+ 		JumpZero: 0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpNotCharacter:scratchReg: (in category 'compile abstract instructions') -----
+ genJumpNotCharacter: reg scratchReg: scratch
+ 	"Generate a compare and branch to test if aRegister contains other than a Character.
+ 	 Answer the jump.  Override since scratch is needed."
+ 	^cogit
+ 		AndCq: objectMemory tagMask R: reg R: scratch;
+ 		CmpCq: objectMemory characterTag R: scratch;
+ 		JumpNonZero: 0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveAt (in category 'primitive generators') -----
  genPrimitiveAt
  	| formatReg convertToIntAndReturn
  	  jumpNotIndexable jumpImmediate jumpBadIndex
  	  jumpIsBytes jumpIsShorts jumpIsWords jumpIsArray jumpHasFixedFields jumpIsContext
  	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds |
- 	<inline: true>
  	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
  	<var: #jumpIsBytes type: #'AbstractInstruction *'>
  	<var: #jumpIsShorts type: #'AbstractInstruction *'>
  	<var: #jumpBadIndex type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
  	<var: #convertToIntAndReturn type: #'AbstractInstruction *'>
  	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
  	<var: #jumpFixedFieldsOutOfBounds type: #'AbstractInstruction *'>
  
  	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
  	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
  
  	"formatReg := self formatOf: ReceiverResultReg"
  	self genGetFormatOf: ReceiverResultReg
  		into: (formatReg := SendNumArgsReg)
  		leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
  
  	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
  
  	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
  		  0 = 0 sized objects (UndefinedObject True False et al)
  		  1 = non-indexable objects with inst vars (Point et al)
  		  2 = indexable objects with no inst vars (Array et al)
  		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		  4 = weak indexable objects with inst vars (WeakArray et al)
  		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		  6 unused, reserved for exotic pointer objects?
  		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
  		  8 unused, reserved for exotic non-pointer objects?
  		  9 (?) 64-bit indexable
  		10 - 11 32-bit indexable
  		12 - 15 16-bit indexable
  		16 - 23 byte indexable
  		24 - 31 compiled method"
  	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
  	jumpIsBytes := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory arrayFormat R: formatReg.
  	jumpIsArray := cogit JumpZero: 0.
  	jumpNotIndexable := cogit JumpBelow: 0.
  					cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
  	jumpHasFixedFields := cogit JumpBelowOrEqual: 0.
  					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
  	jumpIsShorts := cogit JumpAboveOrEqual: 0.
  					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
  	jumpIsWords := cogit JumpAboveOrEqual: 0.
  	"For now ignore 64-bit indexability."
  	jumpNotIndexable jmpTarget: cogit Label.
  	jumpNotIndexable := cogit Jump: 0.
  
  	jumpIsBytes jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
  		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
  	cogit backEnd byteReadsZeroExtend
  		ifTrue:
  			[cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg]
  		ifFalse:
  			[cogit "formatReg already contains a value <= 16r1f, so no need to zero it"
  				MoveXbr: Arg1Reg R: ReceiverResultReg R: formatReg;
  				MoveR: formatReg R: ReceiverResultReg].
  	convertToIntAndReturn := cogit Label.
  	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsShorts jmpTarget:
  		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg).
  		cogit AndCq: 1 R: formatReg.
  		cogit SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
  	cogit Jump: convertToIntAndReturn.
  
  	jumpIsWords jmpTarget:
  		(cogit CmpR: Arg1Reg R: ClassReg).
  	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	cogit AddCq: objectMemory baseHeaderSize >>  (objectMemory shiftForWord - 1) R: Arg1Reg.
  	cogit MoveX32r: Arg1Reg R: ReceiverResultReg R: TempReg.
  	cogit MoveR: TempReg R: ReceiverResultReg.
  	cogit Jump: convertToIntAndReturn.
  
  	jumpHasFixedFields jmpTarget:
  		(cogit AndCq: objectMemory classIndexMask R: TempReg).
  	cogit MoveR: TempReg R: formatReg.
  	cogit CmpCq: ClassMethodContextCompactIndex R: TempReg.
  	jumpIsContext := cogit JumpZero: 0.
  	self genGetClassObjectOfClassIndex: formatReg into: Scratch0Reg scratchReg: TempReg.
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: Scratch0Reg destReg: formatReg.
  	self genConvertSmallIntegerToIntegerInReg: formatReg.
  	cogit
  		AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg;
  		SubR: formatReg R: ClassReg;
  		CmpR: Arg1Reg R: ClassReg.
  	jumpFixedFieldsOutOfBounds := cogit JumpBelowOrEqual: 0.
  	"index is (formatReg (fixed fields) + Arg1Reg (0-rel index)) * wordSize + baseHeaderSize"
  	cogit AddR: formatReg R: Arg1Reg.
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpIsArray jmpTarget:
  		(cogit CmpR: Arg1Reg R: ClassReg).
  	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.	
  	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
  	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	cogit genPrimReturn.
  
  	jumpFixedFieldsOutOfBounds jmpTarget:
  	(jumpArrayOutOfBounds jmpTarget:
  	(jumpBytesOutOfBounds jmpTarget:
  	(jumpShortsOutOfBounds jmpTarget:
  	(jumpWordsOutOfBounds jmpTarget:
  	(jumpNotIndexable jmpTarget:
  	(jumpIsContext jmpTarget:
  	(jumpBadIndex jmpTarget:
  	(jumpImmediate jmpTarget: cogit Label)))))))).
  
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveAtPut (in category 'primitive generators') -----
+ genPrimitiveAtPut
+ 	| formatReg jumpImmediate jumpBadIndex jumpImmutable
+ 	  jumpNotIndexablePointers jumpNotIndexableBits
+ 	  jumpIsContext jumpIsCompiledMethod jumpIsBytes jumpIsShorts jumpHasFixedFields
+ 	  jumpArrayOutOfBounds jumpFixedFieldsOutOfBounds
+ 	  jumpWordsOutOfBounds jumpShortsOutOfBounds jumpBytesOutOfBounds
+ 	  jumpShortsOutOfRange jumpWordsOutOfRange jumpBytesOutOfRange
+ 	  jumpNonSmallIntegerValue jumpNegative jumpNotPointers
+ 	  |
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpIsShorts type: #'AbstractInstruction *'>
+ 	<var: #jumpNegative type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpIsContext type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpHasFixedFields type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexableBits type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfRange type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfRange type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfRange type: #'AbstractInstruction *'>
+ 	<var: #jumpArrayOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexablePointers type: #'AbstractInstruction *'>
+ 
+ 	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
+ 	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
+ 	jumpImmediate := self genJumpImmediate: ReceiverResultReg.
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
+ 	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
+ 
+ 	"formatReg := self formatOf: ReceiverResultReg"
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue:
+ 		[ self genGetFormatOf: ReceiverResultReg
+ 			into: (formatReg := SendNumArgsReg)
+ 			leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
+ 		jumpImmutable := self genJumpBaseHeaderImmutable: TempReg ]
+ 		ifFalse: 
+ 		[ self genGetFormatOf: ReceiverResultReg
+ 			into: (formatReg := SendNumArgsReg)
+ 			leastSignificantHalfOfBaseHeaderIntoScratch: NoReg ].
+ 
+ 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
+ 
+ 	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
+ 		  0 = 0 sized objects (UndefinedObject True False et al)
+ 		  1 = non-indexable objects with inst vars (Point et al)
+ 		  2 = indexable objects with no inst vars (Array et al)
+ 		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		  4 = weak indexable objects with inst vars (WeakArray et al)
+ 		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		  6 unused, reserved for exotic pointer objects?
+ 		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 		  8 unused, reserved for exotic non-pointer objects?
+ 		  9 (?) 64-bit indexable
+ 		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable
+ 		16 - 23 byte indexable
+ 		24 - 31 compiled method"
+ 	cogit CmpCq: objectMemory weakArrayFormat R: formatReg.
+ 	jumpNotPointers := cogit JumpAbove: 0.
+ 	"optimistic store check; assume index in range (almost always is)."
+ 	self genStoreCheckReceiverReg: ReceiverResultReg
+ 		valueReg: Arg1Reg
+ 		scratchReg: TempReg
+ 		inFrame: false.
+ 
+ 	cogit CmpCq: objectMemory arrayFormat R: formatReg.
+ 	jumpNotIndexablePointers := cogit JumpBelow: 0.
+ 	jumpHasFixedFields := cogit JumpNonZero: 0.
+ 	cogit CmpR: Arg0Reg R: ClassReg.
+ 	jumpArrayOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
+ 	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpHasFixedFields jmpTarget: cogit Label.
+ 	self genGetClassIndexOfNonImm: ReceiverResultReg into: formatReg.
+ 	cogit CmpCq: ClassMethodContextCompactIndex R: formatReg.
+ 	jumpIsContext := cogit JumpZero: 0.
+ 	"get # fixed fields in formatReg"
+ 	self genGetClassObjectOfClassIndex: formatReg into: Scratch0Reg scratchReg: TempReg.
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Scratch0Reg destReg: formatReg.
+ 	self genConvertSmallIntegerToIntegerInReg: formatReg.
+ 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: formatReg.
+ 	cogit CmpR: Arg0Reg R: ClassReg.
+ 	jumpFixedFieldsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddR: formatReg R: Arg0Reg.
+ 	cogit MoveR: Arg1Reg Xwr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpNotPointers jmpTarget:
+ 		(cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg).
+ 	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
+ 	jumpNonSmallIntegerValue := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
+ 					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	"For now ignore 64-bit indexability."
+ 	jumpNotIndexableBits := cogit JumpBelow: 0.
+ 
+ 	"fall through to words"
+ 	cogit CmpCq: (objectMemory integerObjectOf: 16rFFFFFFFF) R: Arg1Reg.
+ 	jumpWordsOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: ClassReg.
+ 	cogit AndCq: objectMemory wordSize / 4 - 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	(cogit lastOpcode setsConditionCodesFor: JumpNegative) ifFalse:
+ 		[self CmpCq: 0 R: ClassReg]. "N.B. FLAGS := ClassReg - 0"
+ 	jumpNegative := cogit JumpNegative: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
+ 	cogit MoveR: TempReg X32r: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit CmpCq: (objectMemory integerObjectOf: 255) R: Arg1Reg).
+ 	jumpBytesOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
+ 	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
+ 	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsShorts jmpTarget:
+ 		(cogit CmpCq: (objectMemory integerObjectOf: 65535) R: Arg1Reg).
+ 	jumpShortsOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
+ 	cogit AndCq: objectMemory wordSize / 2 - 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddR: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsContext jmpTarget: 
+ 	(jumpNegative jmpTarget:
+ 	(jumpNotIndexableBits jmpTarget:
+ 	(jumpBytesOutOfRange jmpTarget:
+ 	(jumpShortsOutOfRange jmpTarget:
+ 	(jumpWordsOutOfRange jmpTarget:
+ 	(jumpIsCompiledMethod jmpTarget:
+ 	(jumpArrayOutOfBounds jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpNotIndexablePointers jmpTarget:
+ 	(jumpNonSmallIntegerValue jmpTarget:
+ 	(jumpFixedFieldsOutOfBounds jmpTarget: cogit Label))))))))))))).
+ 	
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue: [jumpImmutable jmpTarget: jumpIsContext jumpTarget].
+ 
+ 	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
+ 	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
+ 
+ 	jumpBadIndex jmpTarget: (jumpImmediate jmpTarget: cogit Label).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveMirrorNew (in category 'primitive generators') -----
+ genPrimitiveMirrorNew
+ 	"Implement 1-arg (instantiateFixedClass:) primitiveNew for convenient cases:
+ 	- the class argument has a hash
+ 	- the class argument is fixed size (excluding ephemerons to save instructions & miniscule time)
+ 	- single word header/num slots < numSlotsMask
+ 	- the result fits in eden (actually below scavengeThreshold)"
+ 
+ 	<option: #NewspeakVM>
+ 	| headerReg fillReg instSpecReg byteSizeReg
+ 	  jumpImmediate jumpUnhashed jumpNotFixedPointers jumpTooSmall jumpBadFormat
+ 	  jumpNoSpace jumpTooBig jumpHasSlots jumpVariableOrEphemeron
+ 	  fillLoop skip |
+ 	<var: 'skip' type: #'AbstractInstruction *'>
+ 	<var: 'fillLoop' type: #'AbstractInstruction *'>
+ 	<var: 'jumpTooBig' type: #'AbstractInstruction *'>
+ 	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
+ 	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
+ 	<var: 'jumpTooSmall' type: #'AbstractInstruction *'>
+ 	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
+ 	<var: 'jumpImmediate' type: #'AbstractInstruction *'>
+ 	<var: 'jumpBadFormat' type: #'AbstractInstruction *'>
+ 	<var: 'jumpNotFixedPointers' type: #'AbstractInstruction *'>
+ 	<var: 'jumpVariableOrEphemeron' type: #'AbstractInstruction *'>
+ 
+ 	self assert: cogit methodNumArgs = 1.
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 
+ 	"header will contain classIndex/class's hash & format & numSlots/fixed size and finally fill value (nilObject)."
+ 	headerReg := fillReg := SendNumArgsReg.
+ 	"inst spec will hold class's instance specification, then byte size and finally end of new object."
+ 	instSpecReg := byteSizeReg := ClassReg.
+ 
+ 	"get freeStart as early as possible so as not to wait later..."
+ 	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
+ 
+ 	"validate class arg; sigh, this mirror crap hobbles unfairly; there is a better way with selector namespaces..."
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 
+ 	"Is the class arg pointers with at least 3 fields?"
+ 	self genGetFormatOf: Arg0Reg
+ 		into: TempReg
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
+ 	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: headerReg.
+ 	jumpUnhashed := cogit JumpZero: 0.
+ 
+ 	"get class's format inst var for both inst spec (format field) and num fixed fields"
+ 	self genLoadSlot: InstanceSpecificationIndex sourceReg: Arg0Reg destReg: instSpecReg.
+ 	jumpBadFormat := self genJumpNotSmallInteger: instSpecReg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: instSpecReg.
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth R: TempReg.
+ 	cogit AndCq: objectMemory formatMask R: TempReg.
+ 	cogit AndCq: objectMemory fixedFieldsOfClassFormatMask R: instSpecReg.
+ 	"fail if not fixed or if ephemeron (rare beasts so save the cycles)"
+ 	cogit CmpCq: objectMemory nonIndexablePointerFormat R: TempReg.
+ 	jumpVariableOrEphemeron := cogit JumpAbove: 0.
+ 	cogit CmpCq: objectMemory numSlotsMask R: instSpecReg.
+ 	jumpTooBig := cogit JumpAboveOrEqual: 0.
+ 	"Add format to classIndex/format in header; then add in numSlots"
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"compute byte size; remember 0-sized objects still need 1 slot."
+ 	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 AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"check if allocation fits (freeSize + byteSize < scavengeThreshold); scavengeThreshold is constant."
+ 	(cogit AddR: Arg1Reg R: byteSizeReg).
+ 	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
+ 	jumpNoSpace := cogit JumpAboveOrEqual: 0.
+ 	"write back new freeStart; get result. byteSizeReg holds new freeStart, the limit of the object"
+ 	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	"write header"
+ 	cogit MoveR: headerReg Mw: 0 r: Arg1Reg.
+ 	"now fill"
+ 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
+ 	cogit MoveCq: objectMemory nilObject R: fillReg.
+ 	fillLoop := 
+ 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
+ 	cogit AddCq: 8 R: Arg1Reg.
+ 	cogit CmpR: Arg1Reg R: byteSizeReg.
+ 	cogit JumpAbove: fillLoop.
+ 	cogit genPrimReturn.
+ 
+ 	jumpNotFixedPointers jmpTarget:
+ 	(jumpBadFormat jmpTarget:
+ 	(jumpTooSmall jmpTarget:
+ 	(jumpImmediate jmpTarget:
+ 	(jumpUnhashed jmpTarget:
+ 	(jumpVariableOrEphemeron jmpTarget:
+ 	(jumpTooBig jmpTarget:
+ 	(jumpNoSpace jmpTarget: cogit Label))))))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveMirrorNewWithArg (in category 'primitive generators') -----
+ genPrimitiveMirrorNewWithArg
+ 	"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>
+ 	| headerReg fillReg instSpecReg byteSizeReg maxSlots
+ 	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
+ 	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
+ 	  jumpUnhashed jumpTooSmall jumpImmediate
+ 	  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 *'>
+ 
+ 	self assert: cogit methodNumArgs = 2.
+ 	cogit genLoadArgAtDepth: 1 into: Arg0Reg. "class arg"
+ 	cogit genLoadArgAtDepth: 0 into: Arg1Reg. "num indexable slots arg"
+ 	"header will contain classIndex/class's hash & format & numSlots/fixed size"
+ 	headerReg := SendNumArgsReg.
+ 	"Assume there's an available scratch register on 64-bit machines.  This holds the saved numFixedFields and then the value to fill with"
+ 	fillReg := Scratch0Reg.
+ 	self assert: fillReg > 0.
+ 	"inst spec will hold class's instance specification and then byte size"
+ 	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"
+ 	jumpNElementsNonInt := self genJumpNotSmallInteger: Arg1Reg scratchReg: TempReg.
+ 
+ 	"Is the class arg pointers with at least 3 fields?"
+ 	jumpImmediate := self genJumpImmediate: Arg0Reg.
+ 	self genGetRawSlotSizeOfNonImm: Arg0Reg into: TempReg.
+ 	cogit CmpCq: InstanceSpecificationIndex + 1 R: TempReg.
+ 	jumpTooSmall := cogit JumpLess: 0.
+ 
+ 	"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: headerReg.
+ 	jumpUnhashed := cogit JumpZero: 0.
+ 
+ 	"The basicNew: code below (copied from genPrimitiveNewWithArg) 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 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 header now"
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"get integer value of num fields in fillReg now"
+ 	cogit MoveR: Arg0Reg R: fillReg.
+ 	self genConvertSmallIntegerToIntegerInReg: fillReg.
+ 	"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: fillReg R: instSpecReg.
+ 	"compute odd bits and add into headerReg; oddBits := 2 - nElements bitAnd: 1"
+ 	cogit MoveCq: objectMemory wordSize / 4 R: TempReg.
+ 	cogit SubR: instSpecReg R: TempReg.
+ 	cogit AndCq: objectMemory wordSize / 4 - 1 R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"round up num elements to numSlots in instSpecReg"
+ 	cogit AddCq: objectMemory wordSize / 4 - 1 R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory shiftForWord - 2 R: instSpecReg.
+ 	cogit MoveCq: 0 R: fillReg.
+ 	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: fillReg R: instSpecReg.
+ 	"compute odd bits and add into headerReg; 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: headerReg.
+ 	"round up num elements to numSlots in instSpecReg"
+ 	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
+ 	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
+ 	cogit MoveCq: 0 R: fillReg.
+ 	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: fillReg R: instSpecReg.
+ 	cogit MoveCq: objectMemory nilObject R: fillReg.
+ 	"fall through to allocate"
+ 
+ 	jumpBytePrepDone jmpTarget:
+ 	(jumpLongPrepDone jmpTarget: cogit Label).
+ 
+ 	"store numSlots to headerReg"
+ 	cogit MoveR: instSpecReg R: TempReg.
+ 	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
+ 	cogit AddR: TempReg R: headerReg.
+ 	"compute byte size; remember 0-sized objects still need 1 slot."
+ 	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
+ 	jumpHasSlots := cogit JumpNonZero: 0.
+ 	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
+ 	skip := cogit Jump: 0.
+ 	jumpHasSlots jmpTarget:
+ 	(cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg).
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
+ 	skip jmpTarget:
+ 	"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: headerReg Mw: 0 r: ReceiverResultReg.
+ 	"now fill"
+ 	cogit PopR: TempReg. "discard pushed receiver"
+ 	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
+ 	fillLoop := 
+ 	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
+ 	cogit AddCq: 8 R: Arg1Reg.
+ 	cogit CmpR: Arg1Reg R: byteSizeReg.
+ 	cogit JumpAbove: fillLoop.
+ 	cogit genPrimReturn.
+ 
+ 	jumpFailCuzFixed jmpTarget:
+ 	(jumpArrayTooBig jmpTarget:
+ 	(jumpByteTooBig jmpTarget:
+ 	(jumpLongTooBig jmpTarget:
+ 	(jumpNoSpace jmpTarget:  cogit Label)))).
+ 
+ 	"unshuffle arguments"
+ 	cogit
+ 		MoveR: Arg0Reg R: Arg1Reg;
+ 		MoveR: ReceiverResultReg R: Arg0Reg;
+ 		PopR: ReceiverResultReg.
+ 
+ 	jumpUnhashed jmpTarget:
+ 	(jumpImmediate jmpTarget:
+ 	(jumpTooSmall jmpTarget:
+ 	(jumpNElementsNonInt jmpTarget: cogit Label))).
+ 
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveStringAt (in category 'primitive generators') -----
+ genPrimitiveStringAt
+ 	| formatReg jumpNotIndexable jumpBadIndex done
+ 	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig
+ 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds |
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	<var: #done type: #'AbstractInstruction *'>
+ 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpIsShorts type: #'AbstractInstruction *'>
+ 	<var: #jumpIsWords type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
+ 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
+ 
+ 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
+ 	cogit MoveR: Arg0Reg R: Arg1Reg.
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
+ 	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
+ 
+ 	self genGetFormatOf: ReceiverResultReg
+ 		into: (formatReg := SendNumArgsReg)
+ 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
+ 
+ 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
+ 
+ 	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
+ 		  0 = 0 sized objects (UndefinedObject True False et al)
+ 		  1 = non-indexable objects with inst vars (Point et al)
+ 		  2 = indexable objects with no inst vars (Array et al)
+ 		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		  4 = weak indexable objects with inst vars (WeakArray et al)
+ 		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		  6 unused, reserved for exotic pointer objects?
+ 		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 		  8 unused, reserved for exotic non-pointer objects?
+ 		  9 (?) 64-bit indexable
+ 		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable
+ 		16 - 23 byte indexable
+ 		24 - 31 compiled method"
+ 	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	jumpIsWords := cogit JumpGreaterOrEqual: 0.
+ 	jumpNotIndexable := cogit Jump: 0.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
+ 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
+ 	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
+ 	cogit backEnd byteReadsZeroExtend ifFalse:
+ 			[cogit AndCq: 255 R: ReceiverResultReg].
+ 	done := cogit Label.
+ 	self genConvertIntegerToCharacterInReg: ReceiverResultReg.
+ 	cogit genPrimReturn.
+ 
+ 	jumpIsShorts jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg).
+ 		cogit AndCq: objectMemory wordSize / 2 - 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddR: Arg1Reg R: ReceiverResultReg.
+ 	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
+ 	cogit Jump: done.
+ 
+ 	jumpIsWords jmpTarget:
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: ClassReg).
+ 		cogit AndCq: objectMemory wordSize / 4 - 1 R: formatReg.
+ 		cogit SubR: formatReg R: ClassReg;
+ 		CmpR: Arg1Reg R: ClassReg.
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	cogit MoveX32r: Arg1Reg R: ReceiverResultReg R: TempReg.
+ 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
+ 	jumpWordTooBig := self jumpNotCharacterUnsignedValueInRegister: TempReg.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	cogit Jump: done.
+ 
+ 	jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget:
+ 	(jumpWordTooBig jmpTarget:
+ 	(jumpNotIndexable jmpTarget: 
+ 	(jumpBadIndex jmpTarget: cogit Label))))).
+ 
+ 	^CompletePrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveStringAtPut (in category 'primitive generators') -----
+ genPrimitiveStringAtPut
+ 	| formatReg jumpBadIndex jumpBadArg jumpShortsDone jumpWordsDone
+ 	  jumpBytesOutOfRange jumpShortsOutOfRange jumpWordsOutOfRange
+ 	  jumpIsBytes jumpIsShorts jumpNotString jumpIsCompiledMethod jumpImmutable
+ 	  jumpBytesOutOfBounds jumpWordsOutOfBounds jumpShortsOutOfBounds |
+ 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
+ 	<var: #jumpBadArg type: #'AbstractInstruction *'>
+ 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
+ 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsDone type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsDone type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfRange type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfRange type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfRange type: #'AbstractInstruction *'>
+ 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
+ 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
+ 
+ 	cogit genLoadArgAtDepth: 1 into: Arg0Reg.
+ 	cogit genLoadArgAtDepth: 0 into: Arg1Reg.
+ 
+ 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
+ 	jumpBadArg := self genJumpNotCharacter: Arg1Reg scratchReg: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
+ 	cogit SubCq: 1 R: Arg0Reg. "1-rel => 0-rel"
+ 
+ 	"formatReg := self formatOf: ReceiverResultReg"
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue:
+ 		[ self genGetFormatOf: ReceiverResultReg
+ 			into: (formatReg := SendNumArgsReg)
+ 			leastSignificantHalfOfBaseHeaderIntoScratch: TempReg.
+ 		jumpImmutable := self genJumpBaseHeaderImmutable: TempReg ]
+ 		ifFalse: 
+ 		[ self genGetFormatOf: ReceiverResultReg
+ 			into: (formatReg := SendNumArgsReg)
+ 			leastSignificantHalfOfBaseHeaderIntoScratch: NoReg ].
+ 
+ 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
+ 
+ 	"dispatch on format; words and/or bytes.
+ 		  0 to 8 = pointer objects, forwarders, reserved.
+ 		  9 (?) 64-bit indexable
+ 		10 - 11 32-bit indexable
+ 		12 - 15 16-bit indexable (but unused)
+ 		16 - 23 byte indexable
+ 		24 - 31 compiled method"
+ 	cogit CmpCq: objectMemory firstLongFormat R: formatReg.
+ 	jumpNotString := cogit JumpBelowOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstCompiledMethodFormat R: formatReg.
+ 	jumpIsCompiledMethod := cogit JumpAboveOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstByteFormat R: formatReg.
+ 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
+ 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
+ 	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
+ 
+ 	cogit CmpCq: (objectMemory characterObjectOf: 1 << self numCharacterBits - 1) R: Arg1Reg.
+ 	jumpWordsOutOfRange := cogit JumpAbove: Arg1Reg.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 2 R: ClassReg.
+ 	cogit AndCq: objectMemory wordSize / 4 - 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg0Reg.
+ 	cogit MoveR: TempReg X32r: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	jumpWordsDone := cogit Jump: 0.
+ 
+ 	jumpIsShorts jmpTarget:
+ 		(cogit CmpCq: (objectMemory characterObjectOf: 65535) R: Arg1Reg).
+ 	jumpShortsOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg.
+ 	cogit AndCq: objectMemory wordSize / 2 - 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	cogit AddR: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: TempReg M16: objectMemory baseHeaderSize r: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 	jumpShortsDone := cogit Jump: 0.
+ 
+ 	jumpIsBytes jmpTarget:
+ 		(cogit CmpCq: (objectMemory characterObjectOf: 255) R: Arg1Reg).
+ 	jumpBytesOutOfRange := cogit JumpAbove: 0.
+ 	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg.
+ 	cogit AndCq: objectMemory wordSize - 1 R: formatReg.
+ 	cogit SubR: formatReg R: ClassReg;
+ 	CmpR: Arg0Reg R: ClassReg.
+ 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
+ 	cogit MoveR: Arg1Reg R: TempReg.
+ 	self genConvertCharacterToCodeInReg: TempReg.
+ 	cogit AddCq: objectMemory baseHeaderSize R: Arg0Reg.
+ 	cogit MoveR: TempReg Xbr: Arg0Reg R: ReceiverResultReg.
+ 	cogit MoveR: Arg1Reg R: ReceiverResultReg.
+ 
+ 	jumpWordsDone jmpTarget:
+ 	(jumpShortsDone jmpTarget: cogit genPrimReturn).
+ 
+ 	jumpNotString jmpTarget:
+ 	(jumpBytesOutOfRange jmpTarget:
+ 	(jumpShortsOutOfRange jmpTarget:
+ 	(jumpWordsOutOfRange jmpTarget:
+ 	(jumpIsCompiledMethod jmpTarget:
+ 	(jumpBytesOutOfBounds jmpTarget:
+ 	(jumpShortsOutOfBounds jmpTarget:
+ 	(jumpWordsOutOfBounds jmpTarget: cogit Label))))))).
+ 
+ 	self cppIf: IMMUTABILITY
+ 		ifTrue: [jumpImmutable jmpTarget: jumpNotString jumpTarget].
+ 
+ 	cogit AddCq: 1 R: Arg0Reg. "0-rel => 1-rel"
+ 	self genConvertIntegerToSmallIntegerInReg: Arg0Reg.
+ 
+ 	jumpBadArg jmpTarget:
+ 	(jumpBadIndex jmpTarget: cogit Label).
+ 
+ 	^CompletePrimitive!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genSmallFloatComparison:invert: (in category 'primitive generators') -----
  genSmallFloatComparison: jumpOpcodeGenerator invert: invertComparison
- 	"Receiver and arg in registers.
- 	 Stack looks like
- 		return address"
  	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
  	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpNonInt type: #'AbstractInstruction *'>
  	<var: #jumpCond type: #'AbstractInstruction *'>
  	<var: #compare type: #'AbstractInstruction *'>
  	<var: #jumpFail type: #'AbstractInstruction *'>
  	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  	self genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
  	jumpImmediate := self genJumpImmediate: Arg0Reg.
  	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
  	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
  	jumpFail := cogit JumpNonZero: 0.
  	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  	invertComparison "May need to invert for NaNs"
  		ifTrue: [compare := cogit CmpRd: DPFPReg0 Rd: DPFPReg1]
  		ifFalse: [compare := cogit CmpRd: DPFPReg1 Rd: DPFPReg0].
  	jumpCond := cogit perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
  	cogit genMoveFalseR: ReceiverResultReg.
  	cogit genPrimReturn.
  	jumpCond jmpTarget: (cogit genMoveTrueR: ReceiverResultReg).
  	cogit genPrimReturn.
  	jumpImmediate jmpTarget: cogit Label.
  	self maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
  	jumpNonInt := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: Arg0Reg.
  	cogit ConvertR: Arg0Reg Rd: DPFPReg1.
  	cogit Jump: compare.
  	jumpNonInt jmpTarget:  (jumpFail jmpTarget: cogit Label).
  	^CompletePrimitive!

Item was removed:
- ----- Method: CogObjectRepresentationFor64BitSpur>>numCharacterBits (in category 'compile abstract instructions') -----
- numCharacterBits
- 	^61!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genPrimitiveAsCharacter (in category 'primitive generators') -----
  genPrimitiveAsCharacter
  	| reg jumpNotInt jumpOutOfRange |
  	<var: 'jumpNotInt' type: #'AbstractInstruction *'>
  	<var: 'jumpOutOfRange' type: #'AbstractInstruction *'>
  	cogit methodNumArgs = 0
  		ifTrue: [reg := ReceiverResultReg]
  		ifFalse:
  			[cogit methodNumArgs > 1 ifTrue:
  				[^UnimplementedPrimitive].
  			 reg := Arg0Reg.
  			 cogit genLoadArgAtDepth: 0 into: Arg0Reg.
  			 jumpNotInt := self genJumpNotSmallInteger: reg scratchReg: TempReg].
  	cogit MoveR: reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
+ 	jumpOutOfRange := self jumpNotCharacterUnsignedValueInRegister: TempReg.
- 	cogit CmpCq: 1 << 30 - 1 R: TempReg.
- 	jumpOutOfRange := cogit JumpAbove: 0.
  	self genConvertSmallIntegerToCharacterInReg: reg.
  	reg ~= ReceiverResultReg ifTrue:
  		[cogit MoveR: reg R: ReceiverResultReg].
  	cogit genPrimReturn.
  	jumpOutOfRange jmpTarget: cogit Label.
  	reg ~= ReceiverResultReg ifTrue:
  		[jumpNotInt jmpTarget: jumpOutOfRange getJmpTarget].
  	^CompletePrimitive!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>genPrimitiveStringAt (in category 'primitive generators') -----
- genPrimitiveStringAt
- 	"Implement the guts of primitiveStringAt; dispatch on size"
- 	| formatReg jumpNotIndexable jumpBadIndex done
- 	  jumpIsBytes jumpIsShorts jumpIsWords jumpWordTooBig
- 	  jumpBytesOutOfBounds jumpShortsOutOfBounds jumpWordsOutOfBounds |
- 	<inline: true>
- 	"c.f. StackInterpreter>>stSizeOf: SpurMemoryManager>>lengthOf:format: fixedFieldsOf:format:length:"
- 	<var: #done type: #'AbstractInstruction *'>
- 	<var: #jumpIsBytes type: #'AbstractInstruction *'>
- 	<var: #jumpIsShorts type: #'AbstractInstruction *'>
- 	<var: #jumpIsWords type: #'AbstractInstruction *'>
- 	<var: #jumpBadIndex type: #'AbstractInstruction *'>
- 	<var: #jumpWordTooBig type: #'AbstractInstruction *'>
- 	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
- 	<var: #jumpBytesOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpShortsOutOfBounds type: #'AbstractInstruction *'>
- 	<var: #jumpWordsOutOfBounds type: #'AbstractInstruction *'>
- 
- 	cogit genLoadArgAtDepth: 0 into: Arg0Reg.
- 	cogit MoveR: Arg0Reg R: Arg1Reg.
- 	jumpBadIndex := self genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
- 	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
- 	cogit SubCq: 1 R: Arg1Reg. "1-rel => 0-rel"
- 
- 	self genGetFormatOf: ReceiverResultReg
- 		into: (formatReg := SendNumArgsReg)
- 		leastSignificantHalfOfBaseHeaderIntoScratch: NoReg.
- 
- 	self genGetNumSlotsOf: ReceiverResultReg into: ClassReg.
- 
- 	"dispatch on format in a combination of highest dynamic frequency order first and convenience.
- 		  0 = 0 sized objects (UndefinedObject True False et al)
- 		  1 = non-indexable objects with inst vars (Point et al)
- 		  2 = indexable objects with no inst vars (Array et al)
- 		  3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
- 		  4 = weak indexable objects with inst vars (WeakArray et al)
- 		  5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
- 		  6 unused, reserved for exotic pointer objects?
- 		  7 Forwarded Object, 1st field is pointer, rest of fields are ignored
- 		  8 unused, reserved for exotic non-pointer objects?
- 		  9 (?) 64-bit indexable
- 		10 - 11 32-bit indexable
- 		12 - 15 16-bit indexable
- 		16 - 23 byte indexable
- 		24 - 31 compiled method"
- 	cogit CmpCq: objectMemory firstByteFormat R: formatReg.
- 	jumpIsBytes := cogit JumpGreaterOrEqual: 0.
- 					cogit CmpCq: objectMemory firstShortFormat R: formatReg.
- 	jumpIsShorts := cogit JumpGreaterOrEqual: 0.
- 					cogit CmpCq: objectMemory firstLongFormat R: formatReg.
- 	jumpIsWords := cogit JumpGreaterOrEqual: 0.
- 	jumpNotIndexable := cogit Jump: 0.
- 
- 	jumpIsBytes jmpTarget:
- 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: ClassReg).
- 		cogit AndCq: objectMemory wordSize - 1 R: formatReg.
- 		cogit SubR: formatReg R: ClassReg;
- 		CmpR: Arg1Reg R: ClassReg.
- 	jumpBytesOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit AddCq: objectMemory baseHeaderSize R: Arg1Reg.
- 	cogit MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
- 	cogit backEnd byteReadsZeroExtend ifFalse:
- 			[cogit AndCq: 255 R: ReceiverResultReg].
- 	done := cogit Label.
- 	self genConvertIntegerToCharacterInReg: ReceiverResultReg.
- 	cogit genPrimReturn.
- 
- 	jumpIsShorts jmpTarget:
- 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord - 1 R: ClassReg).
- 		cogit AndCq: 1 R: formatReg.
- 		cogit SubR: formatReg R: ClassReg;
- 		CmpR: Arg1Reg R: ClassReg.
- 	jumpShortsOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit AddR: Arg1Reg R: ReceiverResultReg.
- 	cogit MoveM16: objectMemory baseHeaderSize r: ReceiverResultReg R: ReceiverResultReg.
- 	cogit Jump: done.
- 
- 	jumpIsWords jmpTarget:
- 		(cogit CmpR: Arg1Reg R: ClassReg).
- 	jumpWordsOutOfBounds := cogit JumpBelowOrEqual: 0.
- 	cogit AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
- 	cogit MoveXwr: Arg1Reg R: ReceiverResultReg R: TempReg.
- 	cogit SubCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: Arg1Reg.
- 	jumpWordTooBig := self jumpNotCharacterUnsignedValueInRegister: TempReg.
- 	cogit MoveR: TempReg R: ReceiverResultReg.
- 	cogit Jump: done.
- 
- 	jumpBytesOutOfBounds jmpTarget:
- 	(jumpShortsOutOfBounds jmpTarget:
- 	(jumpWordsOutOfBounds jmpTarget:
- 	(jumpWordTooBig jmpTarget:
- 	(jumpNotIndexable jmpTarget: 
- 	(jumpBadIndex jmpTarget: cogit Label))))).
- 
- 	^CompletePrimitive!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreCheckReceiverReg:valueReg:scratchReg:inFrame: (in category 'compile abstract instructions') -----
  genStoreCheckReceiverReg: destReg valueReg: valueReg scratchReg: scratchReg inFrame: inFrame
  	"Generate the code for a store check of valueReg into destReg."
  	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered mask rememberedBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  	"Is value stored an integer?  If so we're done"
  	cogit MoveR: valueReg R: scratchReg.
  	cogit AndCq: objectMemory tagMask R: scratchReg.
  	jmpImmediate := cogit JumpNonZero: 0.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpBelow: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: valueReg. "N.B. FLAGS := valueReg - scratchReg"
  	jmpSourceOld := cogit JumpAboveOrEqual: 0.
  	"value is young and target is old.
  	 Need to remember this only if the remembered bit is not already set.
  	 Test the remembered bit.  Only need to fetch the byte containing it,
  	 which reduces the size of the mask constant."
  	rememberedBitByteOffset := jmpSourceOld isBigEndian
  									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
  									ifFalse:[objectMemory rememberedBitShift // 8].
  	mask := 1 << (objectMemory rememberedBitShift \\ 8).
  	cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
  	cogit AndCq: mask R: scratchReg.
  	jmpAlreadyRemembered := cogit JumpNonZero: 0.
  	"Remembered bit is not set.  Call store check to insert dest into remembered table."
  	self assert: destReg == ReceiverResultReg.
  	cogit 
  		evaluateTrampolineCallBlock:
  			[cogit
  				CallRT: ceStoreCheckTrampoline
  				registersToBeSavedMask: (((cogit registerMaskFor: valueReg)
  												bitOr: cogit callerSavedRegMask)
+ 												bitClear: (cogit registerMaskFor: ReceiverResultReg and: scratchReg))]
- 												bitClear: (cogit registerMaskFor: ReceiverResultReg))]
  		protectLinkRegIfNot: inFrame.
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  	(jmpAlreadyRemembered jmpTarget:
  		cogit Label))).
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>jumpNotCharacterUnsignedValueInRegister: (in category 'compile abstract instructions') -----
  jumpNotCharacterUnsignedValueInRegister: reg
+ 	cogit CmpCq: 1 << self numCharacterBits - 1 R: reg.
- 	cogit CmpCq: 16r3FFFFFFF R: reg.
  	^cogit JumpAbove: 0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>numCharacterBits (in category 'primitive generators') -----
+ numCharacterBits
+ 	^30!

Item was changed:
  ----- Method: CogSimStackEntry>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	<doNotGenerate> "Smalltalk-side only"
  	type isInteger ifFalse: [^self].
  	aStream nextPut: $(.
  	type caseOf: {
  		[SSBaseOffset]	-> [aStream
  								nextPutAll: 'bo ';
+ 								nextPutAll: (cogit backEnd nameForRegister: register).
- 								nextPutAll: (CogRTLOpcodes nameForRegister: register).
  							offset negative ifFalse: [aStream nextPut: $+].
  							aStream print: offset].
  		[SSConstant]	-> [aStream
  								nextPutAll: 'const ';
  								print: constant].
  		[SSRegister]	-> [aStream
  								nextPutAll: 'reg ';
+ 								nextPutAll: (cogit backEnd nameForRegister: register)].
- 								nextPutAll: (CogRTLOpcodes nameForRegister: register)].
  		[SSSpill]		-> [aStream
  								nextPutAll: 'spill @ ';
+ 								nextPutAll: (cogit backEnd nameForRegister: register).
- 								nextPutAll: (CogRTLOpcodes nameForRegister: register).
  							offset negative ifFalse: [aStream nextPut: $+].
  							aStream print: offset] }.
  	(spilled and: [type ~= SSSpill]) ifTrue:
  		[aStream nextPutAll: ' (spilled)'].
  	annotateUse ifTrue:
  		[aStream nextPutAll: ' (ANNOTATED)'].
  	bcptr ifNotNil:
  		[aStream space; nextPut: ${; print: bcptr; nextPut: $}].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
(excessive size, no diff calculated)

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveRM16r (in category 'generate machine code') -----
+ concretizeMoveRM16r
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg offset destReg skip |
+ 	srcReg := operands at: 0.
+ 	offset := operands at: 1.
+ 	destReg := operands at: 2.
+ 	machineCode at: 0 put: 16r66.
+ 	(srcReg > 7 or: [destReg > 7])
+ 		ifTrue:
+ 			[machineCode at: 1 put: (self rexw: false r: srcReg x: 0 b: destReg).
+ 			 skip := 1]
+ 		ifFalse:
+ 			[skip := 0].
+ 	(destReg bitAnd: 7) ~= RSP ifTrue:
+ 		[(self isQuick: offset) ifTrue:
+ 			[machineCode
+ 				at: skip + 1 put: 16r89;
+ 				at: skip + 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
+ 				at: skip + 3 put: (offset bitAnd: 16rFF).
+ 			 ^machineCodeSize := skip + 4].
+ 		machineCode
+ 			at: skip + 1 put: 16r89;
+ 			at: skip + 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
+ 			at: skip + 3 put: (offset bitAnd: 16rFF);
+ 			at: skip + 4 put: (offset >> 8 bitAnd: 16rFF);
+ 			at: skip + 5 put: (offset >> 16 bitAnd: 16rFF);
+ 			at: skip + 6 put: (offset >> 24 bitAnd: 16rFF).
+ 		^machineCodeSize := skip + 7].
+ 	"RSP:"
+ 	(self isQuick: offset) ifTrue:
+ 		[machineCode
+ 			at: skip + 1 put: 16r89;
+ 			at: skip + 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
+ 			at: skip + 3 put: (self s: SIB1 i: 4 b: destReg);
+ 			at: skip + 4 put: (offset bitAnd: 16rFF).
+ 		 ^machineCodeSize := skip + 5].
+ 	machineCode
+ 		at: skip + 1 put: 16r89;
+ 		at: skip + 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
+ 		at: skip + 3 put: (self s: SIB1 i: 4 b: destReg);
+ 		at: skip + 4 put: (offset bitAnd: 16rFF);
+ 		at: skip + 5 put: (offset >> 8 bitAnd: 16rFF);
+ 		at: skip + 6 put: (offset >> 16 bitAnd: 16rFF);
+ 		at: skip + 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := skip + 8!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRMbr (in category 'generate machine code') -----
  concretizeMoveRMbr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| srcReg offset baseReg |
- 	| srcReg offset destReg |
  	srcReg := operands at: 0.
  	offset := operands at: 1.
+ 	baseReg := operands at: 2.
- 	destReg := operands at: 2.
  	machineCode
+ 		at: 0 put: (self rexR: srcReg x: 0 b: baseReg);
- 		at: 0 put: (self rexR: srcReg x: 0 b: destReg);
  		at: 1 put: 16r88.
+ 	(baseReg ~= RSP and: [baseReg ~= R12]) ifTrue:
+ 		[(offset = 0 and: [baseReg ~= RBP and: [baseReg ~= R13]]) ifTrue:
- 	(destReg ~= RSP and: [destReg ~= R12]) ifTrue:
- 		[(offset = 0 and: [destReg ~= RBP and: [destReg ~= R13]]) ifTrue:
  			[machineCode
+ 				at: 2 put: (self mod: ModRegInd RM: baseReg RO: srcReg).
- 				at: 2 put: (self mod: ModRegInd RM: destReg RO: srcReg).
  			 ^machineCodeSize := 3].
  		 (self isQuick: offset) ifTrue:
  			[machineCode
+ 				at: 2 put: (self mod: ModRegRegDisp8 RM: baseReg RO: srcReg);
- 				at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 3 put: (offset bitAnd: 16rFF).
  			 ^machineCodeSize := 4].
  		machineCode
+ 			at: 2 put: (self mod: ModRegRegDisp32 RM: baseReg RO: srcReg);
- 			at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
  		^machineCodeSize := 7].
  	"RSP:"
  	offset = 0 ifTrue:
  		[machineCode
+ 			at: 2 put: (self mod: ModRegInd RM: baseReg RO: srcReg);
+ 			at: 3 put: (self s: SIB1 i: 4 b: baseReg).
- 			at: 2 put: (self mod: ModRegInd RM: destReg RO: srcReg);
- 			at: 3 put: (self s: SIB1 i: 4 b: destReg).
  		 ^machineCodeSize := 4].
  	(self isQuick: offset) ifTrue:
  		[machineCode
+ 			at: 2 put: (self mod: ModRegRegDisp8 RM: baseReg RO: srcReg);
+ 			at: 3 put: (self s: SIB1 i: 4 b: baseReg);
- 			at: 2 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
- 			at: 3 put: (self s: SIB1 i: 4 b: destReg);
  			at: 4 put: (offset bitAnd: 16rFF).
  		 ^machineCodeSize := 5].
  	machineCode
+ 		at: 2 put: (self mod: ModRegRegDisp32 RM: baseReg RO: srcReg);
+ 		at: 3 put: (self s: SIB1 i: 4 b: baseReg);
- 		at: 2 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
- 		at: 3 put: (self s: SIB1 i: 4 b: destReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
  	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveRX32rR (in category 'generate machine code') -----
+ concretizeMoveRX32rR
+ 	| index base src offset |
+ 	src := operands at: 0.
+ 	index := operands at: 1.
+ 	base := operands at: 2.
+ 	(index > 7 or: [base > 7 or: [src > 7]])
+ 		ifTrue:
+ 			[machineCode at: 0 put: (self rexw: false r: src x: index b: base).
+ 			 offset := 1]
+ 		ifFalse:
+ 			[offset := 0].
+ 	(base bitAnd: 7) ~= RBP ifTrue:
+ 		[machineCode
+ 			at: offset + 0 put: 16r89;
+ 			at: offset + 1 put: (self mod: ModRegInd RM: 4 RO: src);
+ 			at: offset + 2 put: (self s: SIB4 i: index b: base).
+ 		 ^machineCodeSize := offset + 3].
+ 	machineCode
+ 		at: offset + 0 put: 16r89;
+ 		at: offset + 1 put: (self mod: ModRegRegDisp8 RM: 4 RO: src);
+ 		at: offset + 2 put: (self s: SIB4 i: index b: base);
+ 		at: offset + 3 put: 0.
+ 	 ^machineCodeSize := offset + 4!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMoveRXbrR (in category 'generate machine code') -----
  concretizeMoveRXbrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| src index base offset |
+ 	src := operands at: 0.
+ 	index := operands at: 1.
+ 	base := operands at: 2.
- 	| index base dest offset |
- 	index := operands at: 0.
- 	base := operands at: 1.
- 	dest := operands at: 2.
  	offset := 0.
+ 	(src > 3 or: [base > 7 or: [index > 7]]) ifTrue:
+ 		[machineCode at: 0 put: (self rexR: src x: index b: base).
- 	(dest >= 8 or: [base >= 8 or: [index >= 8]]) ifTrue:
- 		[machineCode at: 0 put: (self rexR: dest x: index b: base).
  		 offset := 1].
+ 	machineCode at: 0 + offset put: 16r88.
+ 	(base bitAnd: 7) ~= RBP "RBP,R13" ifTrue:
- 	machineCode
- 		at: 0 + offset put: 16r88.
- 	(base ~= RBP and: [base ~= R13]) ifTrue:
  		[machineCode
+ 			at: 1 + offset put: (self mod: ModRegInd RM: 4 RO: src);
- 			at: 1 + offset put: (self mod: ModRegInd RM: 4 RO: dest);
  			at: 2 + offset put: (self s: SIB1 i: index b: base).
  		 ^machineCodeSize := 3 + offset].
  	machineCode
+ 		at: 1 + offset put: (self mod: ModRegRegDisp8 RM: 4 RO: src);
- 		at: 1 + offset put: (self mod: ModRegRegDisp8 RM: 4 RO: dest);
  		at: 2 + offset put: (self s: SIB1 i: index b: base);
  		at: 3 + offset put: 0.
  	 ^machineCodeSize := 4 + offset!

Item was changed:
  ----- Method: CogX64Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	<returnTypeC: #void>
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill32]				-> [^self concretizeFill32].
  		[Nop]				-> [^self concretizeNop].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		"[CPUID]					-> [^self concretizeCPUID]."
  		"[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR]."
  		"[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR]."
  		"[LFENCE]				-> [^self concretizeFENCE: 5]."
  		"[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7]."
  		"[LOCK]					-> [^self concretizeLOCK]."
  		"[XCHGAwR]				-> [^self concretizeXCHGAwR]."
  		"[XCHGMwrR]			-> [^self concretizeXCHGMwrR]."
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallFull]				-> [^self concretizeCallFull].
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpFull].
  		[JumpLong]				-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeArithCqRWithRO: 0 raxOpcode: 15r05].
  		[AddCwR]					-> [^self concretizeArithCwR: 16r03].
  		[AddRR]						-> [^self concretizeOpRR: 16r03].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeArithCqRWithRO: 4 raxOpcode: 16r25].
  		[AndCwR]					-> [^self concretizeArithCwR: 16r23].
  		[AndRR]						-> [^self concretizeOpRR: 16r23].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeArithCqRWithRO: 7 raxOpcode: 16r3D].
  		[CmpCwR]					-> [^self concretizeArithCwR: 16r39].
  		[CmpC32R]					-> [^self concretizeCmpC32R].
  		[CmpRR]					-> [^self concretizeReverseOpRR: 16r39].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[OrCqR]						-> [^self concretizeArithCqRWithRO: 1 raxOpcode: 16r0D].
  		[OrCwR]					-> [^self concretizeArithCwR: 16r0B].
  		[OrRR]						-> [^self concretizeOpRR: 16r0B].
  		[SubCqR]					-> [^self concretizeArithCqRWithRO: 5 raxOpcode: 16r2D].
  		[SubCwR]					-> [^self concretizeArithCwR: 16r2B].
  		[SubRR]						-> [^self concretizeOpRR: 16r2B].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[XorCwR]					-> [^self concretizeArithCwR: 16r33].
  		[XorRR]						-> [^self concretizeOpRR: 16r33].
  		[NegateR]					-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[RotateLeftCqR]				-> [^self concretizeShiftCqRegOpcode: 0].
  		[RotateRightCqR]				-> [^self concretizeShiftCqRegOpcode: 1].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeShiftCqRegOpcode: 7].
  		[LogicalShiftRightCqR]			-> [^self concretizeShiftCqRegOpcode: 5].
  		[LogicalShiftLeftCqR]			-> [^self concretizeShiftCqRegOpcode: 4].
  		[ArithmeticShiftRightRR]			-> [^self concretizeShiftRegRegOpcode: 7].
  		[LogicalShiftLeftRR]				-> [^self concretizeShiftRegRegOpcode: 4].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveC32R]		-> [^self concretizeMoveC32R].
  		[MoveRR]			-> [^self concretizeReverseOpRR: 16r89].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
+ 		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveX32rRR]		-> [^self concretizeMoveX32rRR].
+ 		[MoveRX32rR]		-> [^self concretizeMoveRX32rR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[MoveRdR]			-> [^self concretizeMoveRdR].
  		[MoveRRd]			-> [^self concretizeMoveRRd].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd] }!

Item was removed:
- ----- Method: CogX64Compiler>>minAbstractGeneralPurposeReg (in category 'accessing') -----
- minAbstractGeneralPurposeReg
- 	"Answer the smallest index of an abstract general-purpose register used by this compiler.
- 	 N.B.  Abstract registers are negative numbers."
- 	<inline: true>
- 	^Scratch5Reg!

Item was changed:
  ----- Method: CogX64Compiler>>rexw:r:x:b: (in category 'encoding') -----
  rexw: width64 "<Boolean>" r: reg "<0-15>" x: sibReg "<0-15>"  b: fieldReg "<0-15>"
+ 	"Given width64, the R register, sib register, and modrm/sib/reg field register,
+ 	 answer the correctly encoded REX prefix byte.
- 	"Given width64, the R register, sib register, and modrm/sib/reg field, answer either nil,
- 	 if a REX prefix  byte is not needed, or the correctly encoded REX prefix byte.
  	 See AMD64 Architecture Programmer's Manual Volume 3: General-Purpose and System Instructions, Table 1-11"
  	| regBits |
+ 	regBits := ((reg bitAnd: 8) >> 1) + ((sibReg bitAnd: 8) >> 2) + (fieldReg >> 3).
+ 	^(width64 ifTrue: [16r48] ifFalse: [16r40]) + regBits!
- 	regBits := ((reg bitAnd: 8) >> 1) + ((sibReg bitAnd: 8) >> 2) + ((fieldReg bitAnd: 8) >> 3).
- 	^(width64 or: [regBits ~= 0]) ifTrue:
- 		[(width64 ifTrue: [16r48] ifFalse: [16r40]) + regBits]!

Item was added:
+ ----- Method: CogX64CompilerForTests class>>wordRegistersWithNamesDo: (in category 'test support') -----
+ wordRegistersWithNamesDo: aBinaryBlock
+ 	self registers
+ 		with: #('%ax' '%cx' '%dx' '%bx' '%sp' '%bp' '%si' '%di' '%r8w' '%r9w' '%r10w' '%r11w' '%r12w' '%r13w' '%r14w' '%r15w')
+ 		do: aBinaryBlock!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveM16rR (in category 'tests') -----
+ testMoveM16rR
+ 	"self new testMoveM16rR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveM16rR operand: offset operand: sreg operand: dreg.
+ 				self deny: inst byteReadsZeroExtend.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended po |
+ 						po := offset bitAnd: 1 << self processor bitsInWord - 1.
+ 						plainJane := self strip: str.
+ 						herIntended := 'movzwq ', (offset = 0 ifTrue: [''] ifFalse: ['0x', (po printStringBase: 16 length: 16 padded: true)]), '(', srname, '), ', drname.
+ 						self assert: herIntended equals: plainJane.
+ 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRM16r (in category 'tests') -----
+ testMoveRM16r
+ 	"self new testMoveRM16r"
+ 	self concreteCompilerClass wordRegistersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveRM16r operand: sreg operand: offset operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended po |
+ 						plainJane := self strip: str.
+ 						po := offset bitAnd: 1 << self processor bitsInWord - 1.
+ 						herIntended := 'movw ', srname, (offset = 0 ifTrue: [', '] ifFalse: [', 0x', (po printStringBase: 16 length: 16 padded: true)]), '(', drname, ')'.
+ 						self assert: herIntended equals: plainJane.
+ 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRX32rR (in category 'tests') -----
+ testMoveRX32rR
+ 	"self new testMoveRX32rR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:idxreg :irname|
+ 			irname ~= '%rsp' ifTrue:
+ 				[self concreteCompilerClass registersWithNamesDo:
+ 					[:basereg :brname|
+ 					self concreteCompilerClass doubleWordRegistersWithNamesDo:
+ 						[:sreg :srname| | inst len |
+ 						inst := self gen: MoveRX32rR operand: sreg operand: idxreg operand: basereg.
+ 						len := inst concretizeAt: 0.
+ 						self processor
+ 							disassembleInstructionAt: 0
+ 							In: inst machineCode object
+ 							into: [:str :sz| | plainJane herIntended |
+ 								"Convert e.g. '00000000: movl %rax, 0x2(%rax) : 89 40 02' to  'movl %rax, 0x2(%rax)'"
+ 								plainJane := self strip: str.
+ 								herIntended := 'movl ', srname, ', (', brname, ',', irname, ',4)'.
+ 								self assert: herIntended equals: plainJane.
+ 								self assert: len = sz]]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRXbrR (in category 'tests') -----
+ testMoveRXbrR
+ 	"self new testMoveXbrRR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:idxreg :irname|
+ 		irname ~= '%rsp' ifTrue:
+ 			[self concreteCompilerClass registersWithNamesDo:
+ 				[:basereg :brname|
+ 				self concreteCompilerClass byteRegistersWithNamesDo:
+ 					[:sreg :srname| | inst len |
+ 					inst := self gen: MoveRXbrR operand: sreg operand: idxreg operand: basereg.
+ 					len := inst concretizeAt: 0.
+ 					self processor
+ 						disassembleInstructionAt: 0
+ 						In: inst machineCode object
+ 						into: [:str :sz| | plainJane herIntended |
+ 							plainJane := self strip: str.
+ 							herIntended := 'movb ', srname, ', (', brname, ',', irname, ',1)'.
+ 							self assert: herIntended equals: plainJane.
+ 							self assert: len = sz]]]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveRXwrR (in category 'tests') -----
  testMoveRXwrR
  	"self new testMoveXwrRR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:idxreg :irname|
  			irname ~= '%rsp' ifTrue:
  				[self concreteCompilerClass registersWithNamesDo:
  					[:basereg :brname|
  					self concreteCompilerClass registersWithNamesDo:
+ 						[:sreg :srname| | inst len |
+ 						inst := self gen: MoveRXwrR operand: sreg operand: idxreg operand: basereg.
+ 						len := inst concretizeAt: 0.
+ 						self processor
+ 							disassembleInstructionAt: 0
+ 							In: inst machineCode object
+ 							into: [:str :sz| | plainJane herIntended |
+ 								"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 								plainJane := self strip: str.
+ 								herIntended := 'movq ', srname, ', (', brname, ',', irname, ',8)'.
+ 								self assert: herIntended equals: plainJane.
+ 								self assert: len = sz]]]]]!
- 						[:sreg :srname|
- 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 							[:offset| | inst len |
- 							inst := self gen: MoveRXwrR operand: sreg operand: idxreg operand: basereg.
- 							len := inst concretizeAt: 0.
- 							self processor
- 								disassembleInstructionAt: 0
- 								In: inst machineCode object
- 								into: [:str :sz| | plainJane herIntended |
- 									"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
- 									plainJane := self strip: str.
- 									herIntended := 'movq ', srname, ', (', brname, ',', irname, ',8)'.
- 									self assert: herIntended equals: plainJane.
- 									self assert: len = sz]]]]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveX32rRR (in category 'tests') -----
  testMoveX32rRR
  	"self new testMoveX32rRR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:idxreg :irname|
  			irname ~= '%rsp' ifTrue:
  				[self concreteCompilerClass registersWithNamesDo:
  					[:basereg :brname|
  					self concreteCompilerClass doubleWordRegistersWithNamesDo:
+ 						[:dreg :drname| | inst len |
+ 						inst := self gen: MoveX32rRR operand: idxreg operand: basereg operand: dreg.
+ 						len := inst concretizeAt: 0.
+ 						self processor
+ 							disassembleInstructionAt: 3
+ 							In: inst machineCode object
+ 							into: [:str :sz| | plainJane herIntended |
+ 								"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 								plainJane := self strip: str.
+ 								herIntended := 'movl (', brname, ',', irname, ',4), ',drname.
+ 								self assert: herIntended equals: plainJane.
+ 								self assert: len - 3 = sz]]]]]!
- 						[:dreg :drname|
- 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 							[:offset| | inst len |
- 							inst := self gen: MoveX32rRR operand: idxreg operand: basereg operand: dreg.
- 							len := inst concretizeAt: 0.
- 							self processor
- 								disassembleInstructionAt: 3
- 								In: inst machineCode object
- 								into: [:str :sz| | plainJane herIntended |
- 									"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
- 									plainJane := self strip: str.
- 									herIntended := 'movl (', brname, ',', irname, ',4), ',drname.
- 									self assert: herIntended equals: plainJane.
- 									self assert: len - 3 = sz]]]]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveXbrRR (in category 'tests') -----
  testMoveXbrRR
  	"self new testMoveXbrRR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:idxreg :irname|
  		irname ~= '%rsp' ifTrue:
  			[self concreteCompilerClass registersWithNamesDo:
  				[:basereg :brname|
  				self concreteCompilerClass byteRegistersWithNamesDo:
+ 					[:dreg :drname| | inst len |
+ 					inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
+ 					self deny: inst byteReadsZeroExtend.
+ 					len := inst concretizeAt: 0.
+ 					self processor
+ 						disassembleInstructionAt: 0
+ 						In: inst machineCode object
+ 						into: [:str :sz| | plainJane herIntended |
+ 							"Convert e.g. '00000000: movzbq %ds:(%rax,%rax,1), %rax : 48 0F B6 04 00 ' to  'movzbq (%rax,%rax,1), %rax'"
+ 							plainJane := self strip: str.
+ 							herIntended := 'movb (', brname, ',', irname, ',1), ',drname.
+ 							self assert: herIntended equals: plainJane.
+ 							self assert: len = sz]]]]]!
- 					[:dreg :drname|
- 					((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 						[:offset| | inst len |
- 						inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
- 						self deny: inst byteReadsZeroExtend.
- 						len := inst concretizeAt: 0.
- 						self processor
- 							disassembleInstructionAt: 0
- 							In: inst machineCode object
- 							into: [:str :sz| | plainJane herIntended |
- 								"Convert e.g. '00000000: movzbq %ds:(%rax,%rax,1), %rax : 48 0F B6 04 00 ' to  'movzbq (%rax,%rax,1), %rax'"
- 								plainJane := self strip: str.
- 								herIntended := 'movb (', brname, ',', irname, ',1), ',drname.
- 								self assert: herIntended equals: plainJane.
- 								self assert: len = sz]]]]]]!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveXwrRR (in category 'tests') -----
  testMoveXwrRR
  	"self new testMoveXwrRR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:idxreg :irname|
  			irname ~= '%rsp' ifTrue:
  				[self concreteCompilerClass registersWithNamesDo:
  					[:basereg :brname|
  					self concreteCompilerClass registersWithNamesDo:
+ 						[:dreg :drname| | inst len |
+ 						inst := self gen: MoveXwrRR operand: idxreg operand: basereg operand: dreg.
+ 						len := inst concretizeAt: 0.
+ 						self processor
+ 							disassembleInstructionAt: 0
+ 							In: inst machineCode object
+ 							into: [:str :sz| | plainJane herIntended |
+ 								"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 								plainJane := self strip: str.
+ 								herIntended := 'movq (', brname, ',', irname, ',8), ',drname.
+ 								self assert: herIntended equals: plainJane.
+ 								self assert: len = sz]]]]]!
- 						[:dreg :drname|
- 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 							[:offset| | inst len |
- 							inst := self gen: MoveXwrRR operand: idxreg operand: basereg operand: dreg.
- 							len := inst concretizeAt: 0.
- 							self processor
- 								disassembleInstructionAt: 0
- 								In: inst machineCode object
- 								into: [:str :sz| | plainJane herIntended |
- 									"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
- 									plainJane := self strip: str.
- 									herIntended := 'movq (', brname, ',', irname, ',8), ',drname.
- 									self assert: herIntended equals: plainJane.
- 									self assert: len = sz]]]]]]!

Item was changed:
  ----- Method: Cogit>>CallRT:registersToBeSavedMask: (in category 'compile abstract instructions') -----
  CallRT: callTarget registersToBeSavedMask: registersToBeSaved
  	<returnTypeC: #'AbstractInstruction *'>
+ 	| callerSavedRegsToBeSaved lastInst reg registersToBePushed |
- 	| callerSavedRegsToBeSaved lastInst |
  	<var: 'lastInst' type: #'AbstractInstruction *'>
  	callerSavedRegsToBeSaved := callerSavedRegMask bitAnd: registersToBeSaved.
  
+ 	registersToBePushed := callerSavedRegsToBeSaved.
+ 	reg := 0.
+ 	[registersToBePushed ~= 0] whileTrue:
+ 		[(registersToBePushed anyMask: 1) ifTrue:
+ 			[self PushR: reg].
+ 		 reg := reg + 1.
+ 		 registersToBePushed := registersToBePushed >>> 1].
- 	backEnd maxAbstractGeneralPurposeReg to: backEnd minAbstractGeneralPurposeReg by: -1 do:
- 		[:reg|
- 		(reg ~= TempReg
- 		 and: [callerSavedRegsToBeSaved anyMask: (self registerMaskFor: reg)]) ifTrue:
- 			[self PushR: reg]].
  	
  	lastInst := self CallRT: callTarget.
  
+ 	[reg >= 0] whileTrue:
+ 		[(callerSavedRegsToBeSaved anyMask: 1 << reg) ifTrue:
+ 			[lastInst := self PopR: reg].
+ 		 reg := reg - 1].
- 	backEnd minAbstractGeneralPurposeReg to: backEnd maxAbstractGeneralPurposeReg do:
- 		[:reg|
- 		(reg ~= TempReg
- 		 and: [callerSavedRegsToBeSaved anyMask: (self registerMaskFor: reg)]) ifTrue:
- 			[lastInst := self PopR: reg]].
  
  	^lastInst!

Item was added:
+ ----- Method: Cogit>>MoveR:M16:r: (in category 'abstract instructions') -----
+ MoveR: srcReg M16: offset r: baseReg
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self gen: MoveRM16r operand: srcReg quickConstant: offset operand: baseReg!

Item was added:
+ ----- Method: Cogit>>MoveR:X32r:R: (in category 'abstract instructions') -----
+ MoveR: sourceReg X32r: indexReg R: baseReg
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self gen: MoveRX32rR operand: sourceReg operand: indexReg operand: baseReg!

Item was changed:
  ----- Method: Cogit>>cog:selector: (in category 'jit - api') -----
  cog: aMethodObj selector: aSelectorOop
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	self cCode: [] inSmalltalk: "for debugging, allow excluding methods based on selector or methodClass"
- 	self cCode: [] inSmalltalk: "for debugging, allow excluding mehtods based on selector or methodClass"
  		[self class initializationOptions
  			at: #DoNotJIT
  			ifPresent:
  				[:excluded| | methodClass selector |
  				methodClass := coInterpreter nameOfClass: (coInterpreter methodClassOf: aMethodObj).
  				selector := coInterpreter stringOf: aSelectorOop.
  				(excluded anySatisfy: [:exclude| selector = exclude or: [methodClass = exclude]]) ifTrue:
  					[coInterpreter transcript nextPutAll: 'EXCLUDING '; nextPutAll: methodClass; nextPutAll: '>>#'; nextPutAll: selector; cr; flush.
  					 ^nil]]].
  	"In Newspeak we support anonymous accessors and hence tolerate the same
  	 method being cogged multiple times.  But only if the method class association is nil."
  	NewspeakVM
  		ifTrue:
  			[(coInterpreter methodHasCogMethod: aMethodObj) ifTrue:
  				[cogMethod := coInterpreter cogMethodOf: aMethodObj.
  				 self deny: cogMethod selector = aSelectorOop.
  				 cogMethod selector = aSelectorOop ifTrue:
  					[^cogMethod].
  				 (coInterpreter methodClassAssociationOf: aMethodObj) ~= objectMemory nilObject ifTrue:
  					[self warnMultiple: cogMethod selectors: aSelectorOop.
  					^nil]]]
  		ifFalse: [self deny: (coInterpreter methodHasCogMethod: aMethodObj)].
  	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop)
  		isMNUCase: false.
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	NewspeakVM ifTrue:
  		[cogMethod := methodZone findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop.
  		 cogMethod ifNotNil:
  			[(coInterpreter methodHasCogMethod: aMethodObj) not ifTrue:
  				[self assert: (coInterpreter rawHeaderOf: aMethodObj) = cogMethod methodHeader.
  				 cogMethod methodObject: aMethodObj.
  				 coInterpreter rawHeaderOf: aMethodObj put: cogMethod asInteger].
  			^cogMethod]].
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	methodObj := aMethodObj.
  	methodHeader := objectMemory methodHeaderOf: aMethodObj.
  	cogMethod := self compileCogMethod: aSelectorOop.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		 self maybeFreeCounters.
  		 "Right now no errors should be reported, so nothing more to do."
  		 "self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was changed:
  ----- Method: Cogit>>reportLastNInstructions (in category 'debugging') -----
  reportLastNInstructions
  	<doNotGenerate>
  	| skipNext printInst |
  	skipNext := false.
  	printInst := [:inst|
  				coInterpreter transcript nextPutAll:
  					(EagerInstructionDecoration
  						ifTrue: [inst]
  						ifFalse: [processor
  									decorateDisassembly: inst
+ 									for: self
+ 									fromAddress: (Integer readFrom: inst readStream base: 16)]); cr].
- 									for: self]); cr].
  	lastNInstructions withIndexDo:
  		[:thing :idx| | next pc label |
  		skipNext
  			ifTrue: [skipNext := false]
  			ifFalse:
  				[thing isArray
  					ifTrue:
  						[thing first isString "i.e. { '(simulated return to '. processor retpcIn: coInterpreter memory. ')'}"
  							ifTrue:
  								[thing do:
  									[:stringOrNumber|
  									coInterpreter transcript nextPutAll: (stringOrNumber isString
  															ifTrue: [stringOrNumber]
  															ifFalse: [stringOrNumber hex])].
  									coInterpreter transcript cr]
  							ifFalse: "if possible, add the label to the instruction line to condense the output"
  								[coInterpreter transcript cr.
  								 pc := thing at: processor registerStatePCIndex.
  								 label := self relativeLabelForPC: pc.
  								 ((next := lastNInstructions at: idx + 1 ifAbsent: []) notNil
  								  and: [next isString
  								  and: [(Integer readFrom: next readStream radix: 16) = pc]])
  									ifTrue: "Decorate instruction and eliminate pc line"
  										[skipNext := true.
  										 processor printRegisterStateExceptPC: thing on: coInterpreter transcript.
  										 label ifNotNil: [coInterpreter transcript nextPutAll: label; space].
  										 printInst value: next]
  									ifFalse:
  										[label ifNotNil: [coInterpreter transcript nextPutAll: label; nextPut: $:; cr].
  										 processor printRegisterState: thing on: coInterpreter transcript]]]
  					ifFalse:
  						[printInst value: thing]]].
  	coInterpreter transcript flush!

Item was added:
+ ----- Method: NewCoObjectMemory>>freeStart: (in category 'accessing') -----
+ freeStart: aValue
+ 	^freeStart := aValue!

Item was removed:
- ----- Method: NewObjectMemory>>freeStart: (in category 'accessing') -----
- freeStart: aValue
- 	^freeStart := aValue!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>primitiveGeneratorOrNil (in category 'primitive generators') -----
  primitiveGeneratorOrNil
  	"If there is a generator for the current primitive then answer it;
  	 otherwise answer nil."
  	<returnTypeC: #'PrimitiveDescriptor *'>
  	| primitiveDescriptor |
  	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
  	(coInterpreter isQuickPrimitiveIndex: primitiveIndex) ifTrue:
  		[primitiveDescriptor := self addressOf: (primitiveGeneratorTable at: 0). "an unused one"
  		 primitiveDescriptor primitiveGenerator: (coInterpreter quickPrimitiveGeneratorFor: primitiveIndex).
  		 ^primitiveDescriptor].
  	(primitiveIndex between: 1 and: MaxCompiledPrimitiveIndex) ifTrue:
+ 		[self cCode: [] inSmalltalk: "for debugging, allow excluding specific primitives"
+ 			[self class initializationOptions at: #DoNotJIT ifPresent:
+ 				[:excluded|
+ 				((excluded includes: primitiveIndex)
+ 				 and: [(primitiveGeneratorTable at: primitiveIndex) primitiveGenerator notNil]) ifTrue:
+ 					[coInterpreter transcript nextPutAll: 'EXCLUDING primitive #'; print: primitiveIndex; space; nextPutAll: (primitiveGeneratorTable at: primitiveIndex) primitiveGenerator; cr; flush.
+ 				 ^nil]]].
+ 		 ^self addressOf: (primitiveGeneratorTable at: primitiveIndex)].
- 		[^self addressOf: (primitiveGeneratorTable at: primitiveIndex)].
  	^nil!

Item was changed:
  ----- Method: Spur64BitMMLECoSimulator>>freeStart (in category 'accessing') -----
  freeStart
+ 	freeStart = 16r328C68 ifTrue: [self halt].
- 	"freeStart = 16r1163E0 ifTrue: [self halt]."
  	^super freeStart!

Item was changed:
  ----- Method: StackInterpreter>>signed64BitIntegerFor: (in category 'primitive support') -----
  signed64BitIntegerFor: integerValue
  	<var: 'integerValue' type: #sqLong>
  	"Answer a Large Integer object for the given integer value.  N.B. will *not* cause a GC."
  	| newLargeInteger magnitude largeClass highWord sz |
  	<inline: false>
  	<var: 'magnitude' type: #sqLong>
  	<var: 'highWord' type: #usqInt>
  
  	objectMemory wordSize = 8 ifTrue:
  		[(objectMemory isIntegerValue: integerValue) ifTrue:
  			[^objectMemory integerObjectOf: integerValue].
  		 sz := 8].
  
  	integerValue < 0
  		ifTrue:[	largeClass := ClassLargeNegativeIntegerCompactIndex.
  				magnitude := 0 - integerValue]
  		ifFalse:[	largeClass := ClassLargePositiveIntegerCompactIndex.
  				magnitude := integerValue].
  
  	"Make sure to handle the most -ve value correctly. 0 - most -ve = most -ve and most -ve - 1
  	 is +ve.  Alas the simple (negative or: [integerValue - 1 < 0]) fails with contemporary gcc and icc
  	 versions with optimization and sometimes without.  The shift works on all, touch wood."
  	
  	objectMemory wordSize = 4 ifTrue:
  		[(magnitude <= 16r7FFFFFFF
  		  and: [integerValue >= 0
  			  or: [0 ~= (self cCode: [integerValue << 1]
  							inSmalltalk: [integerValue << 1 bitAnd: (1 << 64) - 1])]]) ifTrue:
  				[^self signed32BitIntegerFor: integerValue].
  
  		 (highWord := magnitude >> 32) = 0 
  			ifTrue: [sz := 4] 
  			ifFalse:
  				[sz := 5.
  				 (highWord := highWord >> 8) = 0 ifFalse:
  					[sz := sz + 1.
  					 (highWord := highWord >> 8) = 0 ifFalse:
  						[sz := sz + 1.
  						 (highWord := highWord >> 8) = 0 ifFalse:
  							[sz := sz + 1]]]]].
  
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: largeClass
  							format: (objectMemory byteFormatForNumBytes: sz)
  							numSlots: sz + 3 // objectMemory bytesPerOop.
  	self cppIf: VMBIGENDIAN
  		ifTrue:
  			[sz > 4 ifTrue:
  				[objectMemory
  					storeByte: 7 ofObject: newLargeInteger withValue: (magnitude >> 56 bitAnd: 16rFF);
  					storeByte: 6 ofObject: newLargeInteger withValue: (magnitude >> 48 bitAnd: 16rFF);
  					storeByte: 5 ofObject: newLargeInteger withValue: (magnitude >> 40 bitAnd: 16rFF);
  					storeByte: 4 ofObject: newLargeInteger withValue: (magnitude >> 32 bitAnd: 16rFF)].
  			objectMemory
  				storeByte: 3 ofObject: newLargeInteger withValue: (magnitude >> 24 bitAnd: 16rFF);
  				storeByte: 2 ofObject: newLargeInteger withValue: (magnitude >> 16 bitAnd: 16rFF);
  				storeByte: 1 ofObject: newLargeInteger withValue: (magnitude >>   8 bitAnd: 16rFF);
  				storeByte: 0 ofObject: newLargeInteger withValue: (magnitude ">> 0" bitAnd: 16rFF)]
  		ifFalse:
  			[sz > 4 ifTrue:
+ 				[objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: magnitude >> 32.
+ 				 magnitude := magnitude bitAnd: 16rFFFFFFFF].
- 				[objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: magnitude >> 32].
  			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude].
  	^newLargeInteger!



More information about the Vm-dev mailing list