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

commits at source.squeak.org commits at source.squeak.org
Sat Sep 13 23:10:29 UTC 2014


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

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

Name: VMMaker.oscog-eem.880
Author: eem
Time: 13 September 2014, 4:07:45.226 pm
UUID: 4aeaa3e0-8c6b-44b4-a124-128870605261
Ancestors: VMMaker.oscog-eem.879

Move evaluation of Cogit primitive desacriptor enabled
function from initialization to just-in-time, and add enablers
on SmallInteger primitives to ensure they are applied only
to SmallInteger receivers (falling back to interpreter prims if
not).  Hence fix Cog for 4.1 (e.g. MuO) images.

Declare primitiveTable as static since the change localizes it.

Add more of the potential Spur image segment implementation.

Fix a cast in the simulator.

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

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'dynSuperEntry' 'dynSuperEntryAlignment' 'dynamicSuperSendTrampolines'
  			'ceImplicitReceiverTrampoline' 'ceExplicitReceiverTrampoline' 'cmDynSuperEntryOffset'
  			'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"cogmethod.h"';
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	aCCodeGenerator
  		var: #ceGetSP
  			declareC: 'unsigned long (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(unsigned long from, unsigned long to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static unsigned long (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'unsigned long (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *, void *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel';
  		var: #primInvokeLabel type: #'AbstractInstruction *'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss sendMissCall entry noCheckEntry dynSuperEntry
  					mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #annotations type: #'InstructionAnnotation *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #sendTrampolines
  			declareC: 'sqInt sendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static sqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #CFramePointer type: #'void *';
  		declareVar: #CStackPointer type: #'void *';
  		declareVar: #minValidCallAddress type: #'unsigned long';
  		declareVar: #debugPrimCallStackOffset type: #'unsigned long'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
+ 				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
- 				declareC: 'BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator);
  			var: #primitiveGeneratorTable
+ 				declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
- 				declareC: 'PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
  							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was removed:
- ----- Method: Cogit>>checkPrimitiveTableEnablers (in category 'initialization') -----
- checkPrimitiveTableEnablers
- 	"Disable primitive generators with enablers that answer false."
- 	| primitiveDescriptor |
- 	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
- 	1 to: MaxCompiledPrimitiveIndex do:
- 		[:i|
- 		primitiveDescriptor := self addressOf: (primitiveGeneratorTable at: i).
- 		primitiveDescriptor enabled notNil ifTrue:
- 			[(self perform: primitiveDescriptor enabled with: i) ifFalse:
- 				[primitiveDescriptor primitiveGenerator: nil]]]!

Item was changed:
  ----- Method: Cogit>>compilePrimitive (in category 'compile abstract instructions') -----
  compilePrimitive
  	"Compile a primitive.  If possible, performance-critical primtiives will
  	 be generated by their own routines (primitiveGenerator).  Otherwise,
  	 if there is a primitive at all, we call the C routine with the usual
  	 stack-switching dance, test the primFailCode and then either return
  	 on success or continue to the method body."
  	<inline: false>
  	| primitiveDescriptor primitiveRoutine |
  	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	primitiveIndex = 0 ifTrue: [^0].
+ 	"If a descriptor specifies an argument count (by numArgs >= 0) then it must match
+ 	 for the generated code to be correct.  For example for speed many primitives use
+ 	 ResultReceiverReg instead of accessing the stack, so the receiver better be at
+ 	 numArgs down the stack.  Use the interpreter version if not.  Likewise if it has an
+ 	 enabled function that must answer true for the generated code to be correct."
  	((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
+ 	 and: [primitiveDescriptor primitiveGenerator notNil
+ 	 and: [(primitiveDescriptor primNumArgs < 0 "means don't care"
+ 		   or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)])
+ 	 and: [primitiveDescriptor enabled isNil
+ 		   or: [self perform: primitiveDescriptor enabled with: primitiveIndex]]]]) ifTrue:
+ 		[^self perform: primitiveDescriptor primitiveGenerator].
- 	 and: [primitiveDescriptor primitiveGenerator notNil]) ifTrue:
- 		["If a descriptor specifies an argument count (by numArgs >= 0)
- 		  then it must match for the generated code to be correct.  For
- 		  example for speed many primitives use ResultReceiverReg
- 		  instead of accessing the stack, so the receiver better be at
- 		  numArgs down the stack.  Use the interpreter version if not."
- 		 (primitiveDescriptor primNumArgs < 0 "means don't care"
- 		  or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)]) ifTrue:
- 			[^self perform: primitiveDescriptor primitiveGenerator]].
  	((primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex) isNil "no primitive"
  	or: [primitiveRoutine = (coInterpreter functionPointerFor: 0 inClass: nil) "routine = primitiveFail"]) ifTrue:
  		[^self genFastPrimFail].
  	minValidCallAddress := minValidCallAddress min: primitiveRoutine asUnsignedInteger.
  	^self compileInterpreterPrimitive: primitiveRoutine!

Item was changed:
  ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress
  	<api>
  	self cCode: [self sqMakeMemoryExecutableFrom: startAddress To: endAddress]
  		inSmalltalk: [self initializeProcessor].
  	codeBase := methodZoneBase := startAddress.
  	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
  								min: coInterpreter primitiveFailAddress.
  	self initializeBackend.
  	self maybeGenerateCheckFeatures.
  	self maybeGenerateICacheFlush.
  	self generateVMOwnerLockFunctions.
  	ceGetSP := self cCoerceSimple: self genGetLeafCallStackPointer to: #'unsigned long (*)(void)'.
  	self generateStackPointerCapture.
  	self generateTrampolines.
  	self cCode: '' inSmalltalk: [methodZone zoneEnd: endAddress]. "so that simulator works"
- 	self checkPrimitiveTableEnablers.
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	self computeEntryOffsets.
  	self generateClosedPICPrototype.
  	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
  	self generateOpenPICPrototype!

Item was added:
+ ----- Method: Cogit>>mclassIsSmallInteger: (in category 'initialization') -----
+ mclassIsSmallInteger: ignoredPrimIndex 
+ 	^(coInterpreter methodClassOf: methodObj) = objectMemory classSmallInteger!

Item was added:
+ ----- Method: Cogit>>processorHasDivQuoRemAndMClassIsSmallInteger: (in category 'initialization') -----
+ processorHasDivQuoRemAndMClassIsSmallInteger: ignoredPrimIndex
+ 	^(self processorHasDivQuoRem: ignoredPrimIndex)
+ 	   and: [self mclassIsSmallInteger: ignoredPrimIndex]!

Item was added:
+ ----- Method: Cogit>>processorHasMultiplyAndMClassIsSmallInteger: (in category 'initialization') -----
+ processorHasMultiplyAndMClassIsSmallInteger: ignoredPrimIndex
+ 	^(self processorHasMultiply: ignoredPrimIndex)
+ 	   and: [self mclassIsSmallInteger: ignoredPrimIndex]!

Item was changed:
  ----- Method: Interpreter>>primitiveStoreImageSegment (in category 'image segment in/out') -----
  primitiveStoreImageSegment
  	"This primitive is called from Squeak as...
  		<imageSegment> storeSegmentFor: arrayOfRoots into: aWordArray outPointers: anArray."
  
+ "This primitive will store a binary image segment (in the same format as the Squeak image file) of the receiver and every object in its proper tree of subParts (ie, that is not refered to from anywhere else outside the tree).  All pointers from within the tree to objects outside the tree will be copied into the array of outPointers.  In their place in the image segment will be an oop equal to the offset in the outPointer array (the first would be 4). but with the high bit set."
- "This primitive will store a binary image segment (in the same format as the Squeak image file) of the receiver and every object in its proper tree of subParts (ie, that is not refered to from anywhere else outside the tree).  All pointers from within the tree to objects outside the tree will be copied into the array of outpointers.  In their place in the image segment will be an oop equal to the offset in the outPointer array (the first would be 4). but with the high bit set."
  
+ "The primitive expects the array and wordArray to be more than adequately long.  In this case it returns normally, and truncates the two arrays to exactly the right size.  To simplify truncation, both incoming arrays are required to be whatever the objectMemory considers  long objects.  If either array is too small, the primitive will fail, but in no other case."
- "The primitive expects the array and wordArray to be more than adequately long.  In this case it returns normally, and truncates the two arrays to exactly the right size.  To simplify truncation, both incoming arrays are required to be 256 bytes or more long (ie with 3-word headers).  If either array is too small, the primitive will fail, but in no other case.
  
- During operation of the primitive, it is necessary to convert from both internal and external oops to their mapped values.  To make this fast, the headers of the original objects in question are replaced by the mapped values (and this is noted by adding the forbidden XX header type).  Tables are kept of both kinds of oops, as well as of the original headers for restoration.
- 
- To be specific, there are two similar two-part tables, the outpointer array, and one in the upper fifth of the segmentWordArray.  Each grows oops from the bottom up, and preserved headers from halfway up.
- 
- In case of either success or failure, the headers must be restored.  In the event of primitive failure, the table of outpointers must also be nilled out (since the garbage in the high half will not have been discarded."
- 
  	| outPointerArray segmentWordArray arrayOfRoots ecode |
  
  	outPointerArray := self stackTop.
  	segmentWordArray := self stackValue: 1.
  	arrayOfRoots := self stackValue: 2.
  
  	"Essential type checks"
+ 	((self isArray: arrayOfRoots)						"Must be indexable pointers"
+ 	and: [(self isArray: outPointerArray)					"Must be indexable pointers"
+ 	and: [self isWords: segmentWordArray]]) ifFalse:	"Must be indexable words"
+ 		[^self primitiveFail].
- 	((self isArray: arrayOfRoots)				"Must be indexable pointers"
- 	and: [(self isArray: outPointerArray)		"Must be indexable pointers"
- 	and: [self isWords: segmentWordArray]])	"Must be indexable words"
- 		ifFalse: [^self primitiveFail].
  
  	ecode := self storeImageSegmentInto: segmentWordArray outPointers: outPointerArray roots: arrayOfRoots.
  	ecode = PrimNoErr
  		ifTrue: [self pop: 3]  "...leaving the receiver on the stack as return value"
  		ifFalse: [self primitiveFail]!

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

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

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

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>copyObj:toSegment:addr:stopAt:saveOopAt: (in category 'image segment in/out') -----
+ copyObj: objOop toSegment: segmentWordArray addr: limitSeg stopAt: stopAddr saveOopAt: oopPtr
+ 	"Copy objOop into the segment beginning at limitSeg, and forward it to the copy.
+ 	 Fail if out of space.  Answer the next segmentAddr if successful."
+ 
+ 	"Copy the object..."
+ 	| bodySize copy |
+ 	<inline: false>
+ 	bodySize := self bytesInObject: objOop.
+ 	(self oop: limitSeg + bodySize isGreaterThanOrEqualTo: stopAddr) ifTrue:
+ 		[^0]. "failure"
+ 	self mem: limitSeg cp: (self startOfObject: objOop) y: bodySize.
+ 	copy := self objectStartingAt: limitSeg.
+ 
+ 	"Clear remebered pinned and mark bits of all headers copied into the segment"
+ 	self
+ 		setIsRememberedOf: copy to: false;
+ 		setIsPinnedOf: copy to: false;
+ 		setIsMarkedOf: copy to: false.
+ 
+ 	"Make sure Cogged methods have their true header field written to the segment."
+ 	((self isCompiledMethod: objOop)
+ 	and: [coInterpreter methodHasCogMethod: objOop]) ifTrue:
+ 		[self storePointerUnchecked: HeaderIndex
+ 			ofObject: copy
+ 			withValue: (self methodHeaderOf: objOop)].
+ 
+ 	"Remember the oop for undoing in case of prim failure."
+ 	self longAt: oopPtr put: objOop.	
+ 	self forward: objOop to: copy.
+ 
+ 	"Return new end of segment"
+ 	^limitSeg + bodySize!

Item was changed:
  ----- Method: SpurMemoryManager>>classSmallInteger (in category 'accessing') -----
  classSmallInteger
+ 	<api>
  	^self splObj: ClassSmallInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>copyObj:toSegment:addr:stopAt:saveOopAt: (in category 'image segment in/out') -----
+ copyObj: objOop toSegment: segmentWordArray addr: limitSeg stopAt: stopAddr saveOopAt: oopPtr
+ 	"Copy objOop into the segment beginning at limitSeg, and forward it to the copy.
+ 	 Fail if out of space.  Answer the next segmentAddr if successful."
+ 
+ 	"Copy the object..."
+ 	| bodySize copy |
+ 	<inline: false>
+ 	bodySize := self bytesInObject: objOop.
+ 	(self oop: limitSeg + bodySize isGreaterThanOrEqualTo: stopAddr) ifTrue:
+ 		[^0]. "failure"
+ 	self mem: limitSeg cp: (self startOfObject: objOop) y: bodySize.
+ 	copy := self objectStartingAt: limitSeg.
+ 
+ 	"Clear remebered pinned and mark bits of all headers copied into the segment"
+ 	self
+ 		setIsRememberedOf: copy to: false;
+ 		setIsPinnedOf: copy to: false;
+ 		setIsMarkedOf: copy to: false.
+ 
+ 	"Remember the oop for undoing in case of prim failure."
+ 	self longAt: oopPtr put: objOop.	
+ 	self forward: objOop to: copy.
+ 
+ 	"Return new end of segment"
+ 	^limitSeg + bodySize!

Item was added:
+ ----- Method: SpurMemoryManager>>restoreObjectsFrom:to:from:to: (in category 'image segment in/out') -----
+ restoreObjectsFrom: firstIn to: lastIn from: firstSeg to: limitSeg
+ 	"Unforward objects"
+ 	| originalPtr originalObj copyPtr copyObj |
+ 	originalPtr := firstIn.
+ 	copyPtr := firstSeg.
+ 	[self oop: originalPtr isLessThanOrEqualTo: lastIn] whileTrue:
+ 		[originalObj := self longAt: originalPtr.
+ 		 copyObj := self objectStartingAt: copyPtr.
+ 		 self unforward: originalObj from: copyObj.
+ 		 originalPtr := originalPtr + self bytesPerOop.
+ 		 copyPtr := self addressAfter: copyObj].
+ 	self assert: copyPtr = limitSeg!

Item was changed:
+ ----- Method: SpurMemoryManager>>storeImageSegmentInto:outPointers:roots: (in category 'image segment in/out') -----
- ----- Method: SpurMemoryManager>>storeImageSegmentInto:outPointers:roots: (in category 'primitive support') -----
  storeImageSegmentInto: segmentWordArray outPointers: outPointerArray roots: arrayOfRoots
  	"This primitive is called from Squeak as...
  		<imageSegment> storeSegmentFor: arrayOfRoots into: aWordArray outPointers: anArray."
  
  "This primitive will store a binary image segment (in the same format as the Squeak image file) of the receiver and every object in its proper tree of subParts (ie, that is not refered to from anywhere else outside the tree).  All pointers from within the tree to objects outside the tree will be copied into the array of outpointers.  In their place in the image segment will be an oop equal to the offset in the outPointer array (the first would be 4). but with the high bit set."
  
  "The primitive expects the array and wordArray to be more than adequately long.  In this case it returns normally, and truncates the two arrays to exactly the right size.  To simplify truncation, both incoming arrays are required to have large headers (i.e. be 256 words long or larger).  If either array is too small, the primitive will fail, but in no other case.
  
+ During operation of the primitive, it is necessary to convert from both internal and external oops to their mapped values.  To make this fast, the original objects in question are forwarded to the mapped values.  Tables are kept of both kinds of oops.  Note that markObjects eliminates forwarding pointers, so there will be no forwarding pointers in the object graph once objects have been marked.
- During operation of the primitive, it is necessary to convert from both internal and external oops to their mapped values.  To make this fast, the headers of the original objects in question are replaced by the mapped values (and this is noted by adding the forbidden XX header type).  Tables are kept of both kinds of oops, as well as of the original headers for restoration.
  
+ To be specific, there are two similar tables, the outPointer array, and one in the upper eight of the segmentWordArray.  Each grows oops from the bottom up.
- To be specific, there are two similar two-part tables, the outpointer array, and one in the upper fifth of the segmentWordArray.  Each grows oops from the bottom up, and preserved headers from halfway up.
  
+ In case of either success or failure, the headers must be restored.  In the event of primitive failure, the table of outPointers must also be nilled out (since the garbage in the high half will not have been discarded."
- In case of either success or failure, the headers must be restored.  In the event of primitive failure, the table of outpointers must also be nilled out (since the garbage in the high half will not have been discarded."
  
+ 	| endSeg firstIn firstOut lastIn lastOut limitSeg newSegLimit |
- 	| endSeg firstIn firstOut hdrBaseIn hdrBaseOut lastIn lastOut lastSeg versionOffset |
  	true ifTrue: [^PrimErrUnsupported] ifFalse: [
  
  	((self hasOverflowHeader: outPointerArray)						"Must have 128-bit header"
  	and: [self hasOverflowHeader: segmentWordArray]) ifFalse:		"Must have 128-bit header"
  		[^PrimErrGenericFailure].
  
- 	"Use the top half of outPointers for saved headers."
  	firstOut := outPointerArray + self baseHeaderSize.
  	lastOut := firstOut - self bytesPerOop.
- 	hdrBaseOut := firstOut + ((self numSlotsOf: outPointerArray) // 2 * self bytesPerOop). "top half"
  
+ 	limitSeg := segmentWordArray + self baseHeaderSize.
+ 	endSeg := segmentWordArray + (self addressAfter: segmentWordArray).
- 	lastSeg := segmentWordArray.
- 	endSeg := segmentWordArray + (self addressAfter: segmentWordArray) - self bytesPerOop.
  
  	"Write a version number for byte order and version check"
+ 	limitSeg >= endSeg ifTrue: [^PrimErrGenericFailure].
+ 	self longAt: limitSeg put: self imageSegmentVersion.
+ 	limitSeg := limitSeg + self bytesPerOop.
- 	versionOffset := self bytesPerOop.
- 	lastSeg := lastSeg + versionOffset.
- 	lastSeg > endSeg ifTrue: [^PrimErrGenericFailure].
- 	self longAt: lastSeg put: self imageSegmentVersion.
  
+ 	"Allocate top 1/8 of segment for table of internal oops"
- 	"Allocate top 1/8 of segment for table of internal oops and saved headers"
  	firstIn := endSeg - ((self numSlotsOf: segmentWordArray) // 8).  "Take 1/8 of seg"
  	lastIn := firstIn - self bytesPerOop.
- 	hdrBaseIn := firstIn + ((self numSlotsOf: segmentWordArray) // 16). "top half of that"
  
  	self assert: self allObjectsUnmarked.
  	self markObjectsIn: arrayOfRoots.
  	self markObjects.
  	self unmarkObjectsIn: arrayOfRoots.
  
+ 	"All external objects, and only they, are now marked.
+ 	 Copy the array of roots into the segment, and forward its oop."
+ 	((lastIn := lastIn + self bytesPerOop) >= endSeg
+ 	 or: [0 = (newSegLimit := self copyObj: arrayOfRoots toSegment: segmentWordArray addr: limitSeg stopAt: firstIn saveOopAt: lastIn)]) ifTrue:
+ 		[lastIn := lastIn - self bytesPerWord.
+ 		self restoreObjectsFrom: firstIn to: lastIn from: segmentWordArray + self baseHeaderSize to: limitSeg.
+ 		self fillObj: outPointerArray numSlots: (self numSlotsOf: outPointerArray) with: nilObj.
+ 		^PrimErrGenericFailure].
+ 	limitSeg := newSegLimit.
+ 
+ 	"Now traverse arrayOfRoots, copying unmarked objects into the segment"
+ 
+ 	"Now the primitive can not fail; traverse the objects in the segment, unforwarding the originals and mapping external oops."
  	self flag: 'you are here']!

Item was added:
+ ----- Method: SpurMemoryManager>>unforward:from: (in category 'image segment in/out') -----
+ unforward: obj1 from: obj2
+ 	"Undo a forward: obj1 to: obj2 given that obj2 is a copy of obj1"
+ 	self set: obj1 classIndexTo: (self classIndexOf: obj2) formatTo: (self formatOf: obj2).
+ 	self storePointer: 0 ofForwarder: obj1 withValue: (self fetchPointer: 0 ofObject: obj2).
+ 	(self rawNumSlotsOf: obj2) = 0 ifTrue:
+ 		[self setRawNumSlotsOf: obj1 to: 0]!



More information about the Vm-dev mailing list