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

commits at source.squeak.org commits at source.squeak.org
Fri Nov 22 23:27:29 UTC 2013


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

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

Name: VMMaker.oscog-eem.517
Author: eem
Time: 22 November 2013, 3:23:32.735 pm
UUID: 14ff7126-70ec-4cc4-9f55-70256e6a3d35
Ancestors: VMMaker.oscog-eem.516

Move the defines for BaseHeaderSize BytesPerWord BytesPerOop
out of interpreter, cogit or plugin source and into interp.h, and fix
generateCPtrAsOop:on:indent: to print BaseHeaderSize symbolically
so that plugin source can be safely shared.

Reorder the memory regions in Spur to put the code zone between
newSpace (low) and oldSpace (high).  Hence avoid two range checks
when scavenging.  If the codeZone is below newSpace then
copyAndForward: must check for both <= newSpaceLimit and >=
newSpaceStart) to filter-out cogMethods.  Add a checkMemoryMap
assert to various SpurMemMgr classes and check it on scavenge.
Replace several uses of startOfMemory by the relevant start and fix
related asserts.  Add oldSpaceStart and use in place of
newSpaceLimit in the relevant places.  Add isOldObject: and use in
beRootIfOld:.

Place the guardPage below newSpace in Spur.

Change simulateCogCodeAt: et al to use the new run/single-step
primitives that allow the read-only/executable range to be origined
at other than zero.  Needs Cog-eem.122 to be able to simulate.
Refactor recording simulated instructions into recordProcessing.

Add those primitives to the processor alien plugins.

Simplify generating machine-code new/new:/newMethod by
introducing an UnimplementedPrimitive error and nuking
implementsNew et al.

Nuke addressCouldBeObjWhileScavenging:.

Fix bug in inferTypesForImplicitlyTypedVariablesIn: that would strip
lewading u form explicitly typed vars such as unsigned char over.

JFK RIP.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstantsOn: (in category 'C code generator') -----
  emitCConstantsOn: aStream 
  	"Store the global variable declarations on the given stream."
  	| unused constList |
  	unused := constants keys asSet.
  	"Don't generate any defines for the externally defined constants,
  	 STACKVM, COGVM, COGMTVM et al, unless they're actually used."
  	(VMClass class>>#initializeMiscConstants) literalsDo:
  		[:lit|
  		(lit isVariableBinding and: [lit key isString]) ifTrue:
  			[unused add: lit key]].
  	methods do:
  		[:meth|
  		meth declarations keysDo:
  			[:v|
  			(meth typeFor: v in: self) ifNotNil:
  				[:type| unused remove: type ifAbsent: []]].
  		unused remove: meth returnType ifAbsent: [].
  		meth parseTree nodesDo:
  			[:n| n isConstant ifTrue: [unused remove: n name ifAbsent: []]]].
  	unused copy do:
  		[:const|
  		(variableDeclarations anySatisfy: [:value| value includesSubString: const]) ifTrue:
  			[unused remove: const ifAbsent: []]].
+ 	"and VMBasicConstants mostBasicConstantNames *must* be taken from interp.h"
+ 	unused addAll: VMBasicConstants mostBasicConstantNames.
- 	unused remove: #BytesPerWord ifAbsent: []. "force inclusion of BytesPerWord declaration"
- 	unused remove: #BaseHeaderSize ifAbsent: []. "force inclusion of BaseHeaderSize declaration"
  	constList := constants keys reject: [:any| unused includes: any].
  	aStream cr; nextPutAll: '/*** Constants ***/'; cr.
  	(self sortStrings: constList) do:
  		[:varName| | node default value |
  		node := constants at: varName.
  		node name isEmpty ifFalse:
  			["If the definition includes a C comment, take it as is, otherwise convert the value from Smalltalk to C.
  			  Allow the class to provide an alternative definition, either of just the value or the whole shebang."
  			default := (node value isString and: [node value includesSubString: '/*'])
  							ifTrue: [node value]
  							ifFalse: [self cLiteralFor: node value name: varName].
  			value := vmClass
  						ifNotNil:
  							[(vmClass specialValueForConstant: node name default: default)
  								ifNotNil: [:specialDef| specialDef]
  								ifNil: [default]]
  						ifNil: [default].
  			value first ~= $# ifTrue:
  				[aStream nextPutAll: '#define '; nextPutAll: node name; space].
  			aStream nextPutAll: value; cr]].
  	aStream cr!

Item was changed:
  ----- Method: CoInterpreter>>initializeCodeGenerator (in category 'initialization') -----
  initializeCodeGenerator
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[cogit
+ 				initializeCodeZoneFrom: objectMemory newSpaceLimit
+ 				upTo: objectMemory newSpaceLimit + cogCodeSize]
+ 		ifFalse:
+ 			[cogit
+ 				initializeCodeZoneFrom: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize])
+ 				upTo: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize]) + cogCodeSize]!
- 	cogit
- 		initializeCodeZoneFrom: (self cCode: [objectMemory memory] inSmalltalk: [0])
- 		upTo: (self cCode: [objectMemory memory] inSmalltalk: [0]) + cogCodeSize!

Item was changed:
  ----- Method: CoInterpreter>>isCogMethodReference: (in category 'compiled methods') -----
  isCogMethodReference: methodHeader
  	<api>
  	self assert: ((objectMemory isIntegerObject: methodHeader)
+ 				 or: [methodHeader asUnsignedInteger < cogit maxCogMethodAddress
- 				or: [methodHeader asUnsignedInteger < objectMemory startOfMemory
  					and: [methodHeader asUnsignedInteger >= cogit minCogMethodAddress]]).
  	^objectMemory isNonIntegerObject: methodHeader!

Item was changed:
  ----- Method: CoInterpreterStackPages>>initializeStack:numSlots:pageSize: (in category 'initialization') -----
  initializeStack: theStackPages numSlots: stackSlots pageSize: slotsPerPage
  	"Initialize the stack pages.  In the C VM theStackPages will be alloca'ed memory to hold the
  	 stack pages on the C stack.  In the simulator they are housed in the memory between the
  	 cogMethodZone and the heap."
  
  	<var: #theStackPages type: #'char *'>
  	<returnTypeC: #void>
  	| numPages page structStackPageSize pageStructBase count |
  	<var: #page type: #'StackPage *'>
  	<var: #pageStructBase type: #'char *'>
  	self cCode: []
  		inSmalltalk:
+ 			[objectMemory hasSpurMemoryManagerAPI
+ 				ifTrue:
+ 					[self assert: objectMemory oldSpaceStart - objectMemory newSpaceLimit - coInterpreter cogCodeSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize - Cogit guardPageSize
+ 					= (stackSlots * BytesPerWord roundUpTo: objectMemory allocationUnit)]
+ 				ifFalse:
+ 					[self assert: objectMemory startOfMemory - coInterpreter cogCodeSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize - Cogit guardPageSize
+ 					= (stackSlots * BytesPerWord roundUpTo: objectMemory allocationUnit)]].
- 			[self assert: objectMemory startOfMemory - coInterpreter cogCodeSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize
- 					= (stackSlots * BytesPerWord roundUpTo: objectMemory allocationUnit)].
  	structStackPageSize := coInterpreter sizeof: InterpreterStackPage.
  	bytesPerPage := slotsPerPage * BytesPerWord.
  	numPages := coInterpreter numStkPages.
  
  	"Because stack pages grow down baseAddress is at the top of a stack page and so to avoid
  	 subtracting BytesPerWord from baseAddress and lastAddress in the init loop below we simply
  	 push the stackPage array up one word to avoid the overlap.  This word is extraStackBytes."
  	pageStructBase := theStackPages + (numPages * bytesPerPage) + BytesPerWord.
  	pages := self cCode: [self cCoerceSimple: pageStructBase to: #'StackPage *']
  				  inSmalltalk:
  					[pageMap := Dictionary new.
  					 ((0 to: numPages - 1) collect:
  						[:i|
  						 InterpreterStackPage surrogateClass new
  							address: pageStructBase + (i * structStackPageSize)
  							simulator: coInterpreter
  							zoneBase: coInterpreter stackZoneBase
  							zoneLimit: objectMemory startOfMemory])
  						do: [:pageSurrogate|
  							pageMap at: pageSurrogate address put: pageSurrogate];
  						yourself].
  	"make sure there's enough headroom"
  	self assert: coInterpreter stackPageByteSize - coInterpreter stackLimitBytes - coInterpreter stackLimitOffset
  				>= coInterpreter stackPageHeadroom.
  	0 to: numPages - 1 do:
  		[:index|
  		 page := self stackPageAt: index.
  		 page
  			lastAddress: theStackPages + (index * bytesPerPage);
  			baseAddress: page lastAddress + bytesPerPage;
  			stackLimit: page baseAddress - coInterpreter stackLimitBytes;
  			realStackLimit: page stackLimit;
  			baseFP: 0;
  			nextPage: (self stackPageAt: (index = (numPages - 1) ifTrue: [0] ifFalse: [index + 1]));
  			prevPage: (self stackPageAt: (index = 0 ifTrue: [numPages - 1] ifFalse: [index - 1]))].
  
  	"Now compute stackBasePlus1 so that the pageIndexFor: call maps all addresses from
  	 aPage baseAddress to aBase limitAddress + 1 to the same index (stacks grow down)"
  	stackBasePlus1 := (self cCoerceSimple: theStackPages to: #'char *') + 1.
  	self cCode: []
  		inSmalltalk:
  			[minStackAddress := theStackPages.
  			 maxStackAddress := theStackPages + (numPages * bytesPerPage) + BytesPerWord - 1].
  
  	"The overflow limit is the amount of stack to retain when moving frames from an overflowing
  	 stack to reduce thrashing.  See stackOverflowOrEvent:mayContextSwitch:"
  	page := self stackPageAt: 0.
  	overflowLimit := page baseAddress - page realStackLimit * 3 // 5.
  	0 to: numPages - 1 do:
  		[:index|
  		 page := self stackPageAt: index.
  		 self assert: (self pageIndexFor: page baseAddress) == index.
  		 self assert: (self pageIndexFor: page baseAddress - (slotsPerPage - 1 * BytesPerWord)) == index.
  		 self assert: (self stackPageFor: page baseAddress) == page.
  		 self assert: (self stackPageFor: page stackLimit) == page.
  		 self cCode: []
  			inSmalltalk:
  				[| memIndex |
  				 memIndex := index * slotsPerPage + 1. "this is memIndex in the block above"
  				 self assert: (self memIndexFor: (self oopForPointer: page baseAddress))
  							== (memIndex + slotsPerPage - 1).
  				 index < (numPages - 1) ifTrue:
  					[self assert: (self stackPageFor: page baseAddress + BytesPerWord) == (self stackPageAt: index + 1)]].
  		coInterpreter initializePageTraceToInvalid: page].
  
  	mostRecentlyUsedPage := self stackPageAt: 0.
  	page := mostRecentlyUsedPage.
  	count := 0.
  	[| theIndex |
  	 count := count + 1.
  	 theIndex := self pageIndexFor: page baseAddress.
  	 self assert: (self stackPageAt: theIndex) == page.
  	 self assert: (self pageIndexFor: page baseAddress) == theIndex.
  	 self assert: (self pageIndexFor: page stackLimit) == theIndex.
  	 self assert: (self pageIndexFor: page lastAddress + 1) == theIndex.
  	 (page := page nextPage) ~= mostRecentlyUsedPage] whileTrue.
  	self assert: count == numPages.
  	self assert: self pageListIsWellFormed!

Item was added:
+ ----- Method: CogMethodZone>>zoneEnd: (in category 'simulation only') -----
+ zoneEnd: zoneEnd
+ 	<doNotGenerate> 
+ 	limitAddress := zoneEnd!

Item was changed:
  ----- Method: CogObjectRepresentation>>genInnerPrimitiveNew: (in category 'primitive generators') -----
  genInnerPrimitiveNew: retNoffset
+ 	"subclasses override if they can"
+ 	^cogit unimplementedPrimitive!
- 	self subclassResponsibility.
- 	^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>genInnerPrimitiveNewMethod: (in category 'primitive generators') -----
  genInnerPrimitiveNewMethod: retNoffset
+ 	"subclasses override if they can"
+ 	^cogit unimplementedPrimitive!
- 	self subclassResponsibility.
- 	^0!

Item was changed:
  ----- Method: CogObjectRepresentation>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
  genInnerPrimitiveNewWithArg: retNoffset
+ 	"subclasses override if they can"
+ 	^cogit unimplementedPrimitive!
- 	self subclassResponsibility!

Item was removed:
- ----- Method: CogObjectRepresentation>>implementsNew (in category 'initialization') -----
- implementsNew
- 	^false!

Item was removed:
- ----- Method: CogObjectRepresentation>>implementsNewMethod (in category 'initialization') -----
- implementsNewMethod
- 	^false!

Item was removed:
- ----- Method: CogObjectRepresentation>>implementsNewWithArg (in category 'initialization') -----
- implementsNewWithArg
- 	^false!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreSourceReg:slotIndex:destReg:scratchReg: (in category 'compile abstract instructions') -----
  genStoreSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg
  	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered mask rememberedBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  	"do the store"
  	cogit MoveR: sourceReg
  		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		   r: destReg.
  	"now the check.  Is value stored an integer?  If so we're done"
  	cogit MoveR: sourceReg R: scratchReg.
  	cogit AndCq: objectMemory tagMask R: scratchReg.
  	jmpImmediate := cogit JumpNonZero: 0.
  	"Get the old/new boundary in scratchReg"
+ 	cogit MoveCw: objectMemory newSpaceLimit R: scratchReg.
- 	cogit MoveAw: objectMemory newSpaceLimitAddress 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: sourceReg. "N.B. FLAGS := sourceReg - 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).
  	"N.B. MoveMb:r:R: does not zero other bits"
  	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 CallRT: ceStoreCheckTrampoline.
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  	(jmpAlreadyRemembered jmpTarget:
  		cogit Label))).
  	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>implementsNew (in category 'initialization') -----
- implementsNew
- 	^true!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>implementsNewWithArg (in category 'initialization') -----
- implementsNewWithArg
- 	^true!

Item was changed:
  ----- Method: CogStackPageSurrogate32>>trace (in category 'accessing') -----
  trace
+ 	^memory longAt: address + 29!
- 	^memory unsignedLongAt: address + 29!

Item was changed:
  ----- Method: CogStackPageSurrogate32>>trace: (in category 'accessing') -----
  trace: aValue
  	self assert: (address + 28 >= zoneBase and: [address + 31 < zoneLimit]).
+ 	^memory longAt: address + 29 put: aValue!
- 	^memory unsignedLongAt: address + 29 put: (16rFFFFFFFF bitAnd: aValue)!

Item was changed:
  ----- Method: CogStackPageSurrogate64>>trace (in category 'accessing') -----
  trace
+ 	^memory longAt: address + 57!
- 	^memory unsignedLongAt: address + 57!

Item was changed:
  ----- Method: CogStackPageSurrogate64>>trace: (in category 'accessing') -----
  trace: aValue
  	self assert: (address + 56 >= zoneBase and: [address + 59 < zoneLimit]).
+ 	^memory longAt: address + 57 put: aValue!
- 	^memory unsignedLongAt: address + 57 put: aValue!

Item was changed:
  ----- Method: CogVMSimulator>>fetchPointer:ofObject: (in category 'interpreter access') -----
  fetchPointer: fieldIndex ofObject: oop
  	"index by word size, and return a pointer as long as the word size"
+ 	self assert: (objectMemory cheapIsInMemory: oop).
- 	self assert: oop >= objectMemory startOfMemory.
  	^objectMemory fetchPointer: fieldIndex ofObject: oop!

Item was added:
+ ----- Method: CogVMSimulator>>heapBase: (in category 'accessing') -----
+ heapBase: anObject
+ 	"Set the value of heapBase; used by the Spur CoSimulator to reposition cog code between newSpace and oldSpace."
+ 
+ 	^heapBase := anObject!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize count heapSize oldBaseAddr bytesToShift swapBytes hdrNumStackPages
  	 hdrEdenBytes hdrCogCodeSize stackZoneSize methodCacheSize headerFlags primTraceLogSize firstSegSize hdrMaxExtSemTabSize |
  	"open image file and read the header"
  
  	["begin ensure block..."
  	f := FileStream readOnlyFileNamed: fileName.
  	imageName := f fullName.
  	f binary.
  	version := self nextLongFrom: f.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getLongFromFile: f swap: swapBytes.
  	heapSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getLongFromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [self defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = 40.
  	hdrEdenBytes	:= self getLongFromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = 48.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * BytesPerWord.
  	primTraceLogSize := primTraceLog size * BytesPerWord.
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
+ 	heapBase := (Cogit guardPageSize
+ 				+ cogCodeSize
- 	heapBase := (cogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  	objectMemory
  		setHeapBase: heapBase
  		memoryLimit:  heapBase
  						+ heapSize
  						+ objectMemory newSpaceBytes
  						+ self interpreterAllocationReserveBytes
  						+ extraBytes
  		endOfMemory: heapBase + heapSize.
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	objectMemory memory: ((cogit processor endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: objectMemory memoryLimit // 4).
  	count := objectMemory readHeapFromImageFile: f dataBytes: heapSize.
  	count ~= heapSize ifTrue: [self halt].
  	]
  		ensure: [f close].
+ 	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize.
+ 	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize + methodCacheSize.
- 	self moveMethodCacheToMemoryAt: cogCodeSize + stackZoneSize.
- 	self movePrimTraceLogToMemoryAt: cogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
  	self initializeCodeGenerator!

Item was changed:
  ----- Method: CogVMSimulator>>stackZoneBase (in category 'stack pages') -----
  stackZoneBase
  	"In the simulator the stack zone starts immediately after the code zone."
+ 	^objectMemory cogCodeBase + cogCodeSize!
- 	^cogCodeSize!

Item was changed:
  CogClass subclass: #Cogit
  	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxMethodBefore maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass UnimplementedPrimitive YoungSelectorInPIC'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass YoungSelectorInPIC'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/13/2013 15:37' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventuakly teh total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was added:
+ ----- Method: Cogit class>>guardPageSize (in category 'accessing') -----
+ guardPageSize
+ 	^1024!

Item was changed:
  ----- Method: Cogit class>>initializeErrorCodes (in category 'class initialization') -----
  initializeErrorCodes
  	"External errors, returned to or from cog:selector:"
  	NotFullyInitialized := -1.
  	InsufficientCodeSpace := -2.
  	MethodTooBig := -4.
  	YoungSelectorInPIC := -5.
  	EncounteredUnknownBytecode := -6.
+ 	UnimplementedPrimitive := -7.
+ 	MaxNegativeErrorCode := UnimplementedPrimitive.
- 	MaxNegativeErrorCode := EncounteredUnknownBytecode.
  	"Internal errors returned by generator routines to other generator routines"
  	BadRegisterSet := 1!

Item was changed:
  ----- Method: Cogit>>handleWriteSimulationTrap: (in category 'simulation only') -----
  handleWriteSimulationTrap: aProcessorSimulationTrap 
  	<doNotGenerate>
  	| variableValue |
+ 	(aProcessorSimulationTrap address between: codeBase and: methodZone zoneEnd) ifTrue:
- 	aProcessorSimulationTrap address < coInterpreter cogCodeSize ifTrue:
  		[self error: 'attempt to write to code space'].
  	variableValue := processor perform: aProcessorSimulationTrap registerAccessor.
  	(simulatedVariableSetters at: aProcessorSimulationTrap address) value: variableValue.
  	processor pc: aProcessorSimulationTrap nextpc!

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.
- 	codeBase := methodZoneBase := (self
- 											cCode: [startAddress]
- 											inSmalltalk: [startAddress + guardPageSize]).
  	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 changed:
  ----- Method: Cogit>>initializeProcessor (in category 'initialization') -----
  initializeProcessor
  	"Initialize the simulation processor, arranging that its initial stack is somewhere on the rump C stack."
  	<doNotGenerate>
+ 	guardPageSize := self class guardPageSize.
- 	guardPageSize := 1024.
  	lastNInstructions := OrderedCollection new.
  	"This is for testing.  On many OS's the stack must remain aligned;
  	 e.g. IA32 using SSE requires 16 byte alignment."
  	expectedSPAlignment := 0. expectedFPAlignment := 8. cStackAlignment := 16.
  	processor class setStackAlignmentDelta: cStackAlignment.
  	self initializeProcessorStack: coInterpreter rumpCStackAddress.
  	objectMemory
  		longAt: self cFramePointerAddress put: processor fp;
  		longAt: self cStackPointerAddress put: processor sp.
  	threadManager ifNotNil:
  		[processor := MultiProcessor for: processor coInterpreter: coInterpreter]!

Item was removed:
- ----- Method: Cogit>>objectRepresentationImplementsNew: (in category 'initialization') -----
- objectRepresentationImplementsNew: primIndex
- 	^objectRepresentation implementsNew!

Item was removed:
- ----- Method: Cogit>>objectRepresentationImplementsNewMethod: (in category 'initialization') -----
- objectRepresentationImplementsNewMethod: primIndex
- 	^objectRepresentation implementsNewMethod!

Item was removed:
- ----- Method: Cogit>>objectRepresentationImplementsNewWithArg: (in category 'initialization') -----
- objectRepresentationImplementsNewWithArg: primIndex
- 	^objectRepresentation implementsNewWithArg!

Item was added:
+ ----- Method: Cogit>>recordProcessing (in category 'simulation only') -----
+ recordProcessing
+ 	self recordRegisters.
+ 	printRegisters ifTrue:
+ 		[processor printRegistersOn: coInterpreter transcript].
+ 	self recordLastInstruction!

Item was changed:
  ----- Method: Cogit>>simulateCogCodeAt: (in category 'simulation only') -----
  simulateCogCodeAt: address "<Integer>"
  	<doNotGenerate>
  	| stackZoneBase |
  	stackZoneBase := coInterpreter stackZoneBase.
  	processor pc: address.
  	[[[singleStep ifTrue:
  		[[processor sp < stackZoneBase ifTrue: [self halt].
+ 		  self recordProcessing.
- 		  self recordRegisters.
- 		  printRegisters ifTrue:
- 			[processor printRegistersOn: coInterpreter transcript].
- 		  self recordLastInstruction.
- 		  printInstructions ifTrue:
- 			[coInterpreter transcript nextPutAll: lastNInstructions last; cr.
- 			 printRegisters ifTrue: [coInterpreter transcript cr].
- 			 coInterpreter transcript flush].
  		  (breakPC isInteger
  			ifTrue:
  				[processor pc = breakPC
  				 and: [breakBlock value: self]]
  			ifFalse:
  				[breakBlock value: self]) ifTrue:
  			["printRegisters := printInstructions := true"
  			 "self reportLastNInstructions"
  			 "coInterpreter printExternalHeadFrame"
  			 "coInterpreter printFrameAndCallers: coInterpreter framePointer SP: coInterpreter stackPointer"
  			 "coInterpreter shortPrintFrameAndCallers: coInterpreter framePointer"
  			 "coInterpreter printFrame: processor fp WithSP: processor sp"
  			 "coInterpreter printFrameAndCallers: processor fp SP: processor sp"
  			 "coInterpreter shortPrintFrameAndCallers: processor fp"
  			"self disassembleMethodFor: processor pc"
  			 coInterpreter changed: #byteCountText.
  			 self halt: 'machine code breakpoint at ',
  						(breakPC isInteger
  							ifTrue: [breakPC hex]
  							ifFalse: [String streamContents: [:s| breakBlock decompile printOn: s indent: 0]])]] value]. "So that the Debugger's Over steps over all this"
  	   singleStep
  		ifTrue: [processor
  					singleStepIn: coInterpreter memory
  					minimumAddress: guardPageSize
+ 					executableAndReadOnlyFrom: codeBase
+ 					to: methodZone zoneEnd]
- 					readOnlyBelow: coInterpreter cogCodeSize]
  		ifFalse: [processor
  					runInMemory: coInterpreter memory
  					minimumAddress: guardPageSize
+ 					executableAndReadOnlyFrom: codeBase
+ 					to: methodZone zoneEnd].
- 					readOnlyBelow: coInterpreter cogCodeSize].
  	   ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  	 	[(self confirm: 'continue?') ifFalse:
  			[self halt]].
  	   true] whileTrue]
  		on: ProcessorSimulationTrap
  		do: [:ex| self handleSimulationTrap: ex].
  	 true] whileTrue!

Item was changed:
  ----- Method: Cogit>>simulateLeafCallOf: (in category 'simulation only') -----
  simulateLeafCallOf: someFunction
  	"Simulate execution of machine code that leaf-calls someFunction,
  	 answering the result returned by someFunction."
  	<doNotGenerate>
  	| spOnEntry |
  	self recordRegisters.
  	processor
  		simulateLeafCallOf: someFunction
  		nextpc: 16rBADF00D5
  		memory: coInterpreter memory.
  	spOnEntry := processor sp.
  	self recordInstruction: {'(simulated call of '. someFunction. ')'}.
+ 	[[processor pc between: codeBase and: methodZone zoneEnd] whileTrue:
- 	[[processor pc between: 0 and: coInterpreter cogCodeSize] whileTrue:
  		[singleStep
+ 			ifTrue: [self recordProcessing.
- 			ifTrue: [self recordLastInstruction.
- 					self recordRegisters.
  					processor
  						singleStepIn: coInterpreter memory
  						minimumAddress: guardPageSize
+ 						executableAndReadOnlyFrom: codeBase
+ 						to: methodZone zoneEnd]
- 						readOnlyBelow: coInterpreter cogCodeSize]
  			ifFalse: [processor
  						runInMemory: coInterpreter memory
  						minimumAddress: guardPageSize
+ 						executableAndReadOnlyFrom: codeBase
+ 						to: methodZone zoneEnd]]]
- 						readOnlyBelow: coInterpreter cogCodeSize]]]
  		on: ProcessorSimulationTrap
  		do: [:ex| | retpc |
  			"If the ip is out of bounds the return has already occurred."
+ 			((processor pc between: codeBase and: methodZone zoneEnd)
- 			((processor pc between: 0 and: coInterpreter cogCodeSize)
  			 and: [processor sp <= spOnEntry]) ifTrue:
  				[retpc := processor leafRetpcIn: coInterpreter memory.
  				 self assert: retpc = 16rBADF00D5.
  				 self recordInstruction: {'(simulated return to '. retpc. ')'.
  				 processor simulateLeafReturnIn: coInterpreter memory}.
  				 self recordRegisters]].
  	^processor cResultRegister!

Item was added:
+ ----- Method: Cogit>>unimplementedPrimitive (in category 'accessing') -----
+ unimplementedPrimitive
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: NewCoObjectMemorySimulator>>cogCodeBase (in category 'simulation only') -----
+ cogCodeBase
+ 	^0!

Item was added:
+ ----- Method: ObjectMemory>>cheapIsInMemory: (in category 'plugin support') -----
+ cheapIsInMemory: address 
+ 	"Answer if the given address is in ST object memory.  For simulation only."
+ 	<doNotGenerate>
+ 	^address >= self startOfMemory
+ 	  and: [address < endOfMemory]!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueakV3 (in category 'class initialization') -----
  initializePrimitiveTableForSqueakV3
  	"Initialize the table of primitive generators.  This does not include normal primitives implemened in the coInterpreter."
  	"SimpleStackBasedCogit initializePrimitiveTableForSqueakV3"
  	MaxCompiledPrimitiveIndex := 222.
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1)
  		(2 genPrimitiveSubtract			1)
  		(3 genPrimitiveLessThan		1)
  		(4 genPrimitiveGreaterThan		1)
  		(5 genPrimitiveLessOrEqual		1)
  		(6 genPrimitiveGreaterOrEqual	1)
  		(7 genPrimitiveEqual			1)
  		(8 genPrimitiveNotEqual		1)
  		(9 genPrimitiveMultiply			1	processorHasMultiply:)
  		(10 genPrimitiveDivide			1	processorHasDivQuoRem:)
  		(11 genPrimitiveMod			1	processorHasDivQuoRem:)
  		(12 genPrimitiveDiv				1	processorHasDivQuoRem:)
  		(13 genPrimitiveQuo			1	processorHasDivQuoRem:)
  		(14 genPrimitiveBitAnd			1)
  		(15 genPrimitiveBitOr			1)
  		(16 genPrimitiveBitXor			1)
  		(17 genPrimitiveBitShift			1)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 primitiveFloatAt)"
  		"(39 primitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0	processorHasDoublePrecisionFloatingPointSupport:)
  		(41 genPrimitiveFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(42 genPrimitiveFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(43 genPrimitiveFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(44 genPrimitiveFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(45 genPrimitiveFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(46 genPrimitiveFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)
  		(47 genPrimitiveFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(48 genPrimitiveFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(49 genPrimitiveFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(50 genPrimitiveFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
  		"(51 primitiveTruncated)"
  		"(52 primitiveFractionalPart)"
  		"(53 primitiveExponent)"
  		"(54 primitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)
  		"(56 primitiveSine)"
  		"(57 primitiveArctan)"
  		"(58 primitiveLogN)"
  		"(59 primitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt			1)
  		"(61 primitiveAtPut)"
  		(62 genPrimitiveSize		0)
  		(63 genPrimitiveStringAt	1)
  		"(64 primitiveStringAtPut)"
  		"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)
- 		(70 genPrimitiveNew			0			objectRepresentationImplementsNew:)
- 		(71 genPrimitiveNewWithArg	1			objectRepresentationImplementsNewWithArg:)
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
+ 		(79 genPrimitiveNewMethod	2)
- 		(79 genPrimitiveNewMethod	2			objectRepresentationImplementsNewMethod:)
  
  		"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)
  
  		"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>>genPrimitiveNew (in category 'primitive generators') -----
  genPrimitiveNew
  	| r |
+ 	((r := objectRepresentation genInnerPrimitiveNew: BytesPerWord) < 0
+ 	 and: [r ~= UnimplementedPrimitive]) ifTrue:
- 	(r := objectRepresentation genInnerPrimitiveNew: BytesPerWord) < 0 ifTrue:
  		[^r].
+ 	"Call the interpreter primitive either when the machine-code primitive
+ 	 fails, or if the machine-code primitive is unimplemented."
  	^self compileFallbackToInterpreterPrimitive!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveNewMethod (in category 'primitive generators') -----
  genPrimitiveNewMethod
  	| r |
+ 	((r := objectRepresentation genInnerPrimitiveNewMethod: 2 * BytesPerWord) < 0
+ 	 and: [r ~= UnimplementedPrimitive]) ifTrue:
- 	(r := objectRepresentation genInnerPrimitiveNewMethod: 2 * BytesPerWord) < 0 ifTrue:
  		[^r].
+ 	"Call the interpreter primitive either when the machine-code primitive
+ 	 fails, or if the machine-code primitive is unimplemented."
  	^self compileFallbackToInterpreterPrimitive!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveNewWithArg (in category 'primitive generators') -----
  genPrimitiveNewWithArg
  	| r |
+ 	((r := objectRepresentation genInnerPrimitiveNewWithArg: BytesPerWord) < 0
+ 	 and: [r ~= UnimplementedPrimitive]) ifTrue:
- 	(r := objectRepresentation genInnerPrimitiveNewWithArg: BytesPerWord) < 0 ifTrue:
  		[^r].
+ 	"Call the interpreter primitive either when the machine-code primitive
+ 	 fails, or if the machine-code primitive is unimplemented."
  	^self compileFallbackToInterpreterPrimitive!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>generateCPtrAsOop:on:indent: (in category 'translating builtins') -----
  generateCPtrAsOop: aNode on: aStream indent: anInteger
- 
  	aStream nextPutAll: '((sqInt)(long)('.
  	self emitCExpression: aNode receiver on: aStream.
+ 	aStream nextPutAll: ') - BaseHeaderSize)'!
- 	aStream nextPutAll: ') - ';
- 		nextPutAll: ObjectMemory baseHeaderSize printString;
- 		nextPut: $).!

Item was changed:
  Spur32BitMemoryManager subclass: #Spur32BitCoMemoryManager
  	instanceVariableNames: 'cogit'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants'
  	category: 'VMMaker-SpurMemoryManager'!
+ 
+ !Spur32BitCoMemoryManager commentStamp: 'eem 11/20/2013 13:45' prior: 0!
+ Spur32BitCoMemoryManager is a refinement of Spur32BitMemoryManager that supports the CoInterpreter/Cogit just-in-time compiler.  The signifiant difference from Spur32BitMemoryManager is the memory layout.  Spur32BitCoMemoryManager adds the cgCodeZone between newSpace and the firts oldSpace segment:
+ 
+ low address:
+ 	newSpace:
+ 		past/future survivor space
+ 		future/past survivor space
+ 		eden
+ 	cogCodeZone:
+ 		generated run-time
+ 		cog methods
+ 		free space
+ 		young referrers
+ 	first oldSpace segment
+ 	...
+ 	subsequent oldSpace segment
+ high address:
+ 
+ Instance Variables
+ 	cogit:		<SimpleStackBasedCogit or subclass>
+ 
+ cogit
+ 	- the just-in-time compiler
+ !

Item was changed:
  ----- Method: Spur32BitCoMemoryManager>>ceStoreCheck: (in category 'trampolines') -----
  ceStoreCheck: anOop
  	<api>
  	"Do the store check.  Answer the argument for the benefit of the code generator;
  	 ReceiverResultReg may be caller-saved and hence smashed by this call.  Answering
  	 it allows the code generator to reload ReceiverResultReg cheaply."
  	self assert: (self isNonImmediate: anOop).
+ 	self assert: (self oop: anOop isGreaterThanOrEqualTo: oldSpaceStart).
- 	self assert: (self oop: anOop isGreaterThan: newSpaceLimit).
  	self assert: (self isRemembered: anOop) not.
  	scavenger remember: anOop.
  	self setIsRememberedOf: anOop to: true.
  	^anOop!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>checkMemoryMap (in category 'debug support') -----
+ checkMemoryMap
+ 	"Override to check that Cog methods are considered neither young nor old.
+ 	 Being young would cause them to be scavenged.
+ 	 Being old would cause them to be remembered if stored into (but wait, they don't get stored into)."
+ 
+ 	self assert: (self isYoungObject: newSpaceStart).
+ 	self assert: (self isYoungObject: newSpaceLimit - self wordSize).
+ 	self assert: (self isOldObject: newSpaceStart) not.
+ 	self assert: (self isOldObject: newSpaceLimit - self wordSize) not.
+ 	self assert: (self isYoungObject: newSpaceLimit) not.
+ 	self assert: (self isYoungObject: oldSpaceStart) not.
+ 	self assert: (self isYoungObject: endOfMemory) not.
+ 	self assert: (self isOldObject: oldSpaceStart).
+ 	self assert: (self isOldObject: endOfMemory).
+ 
+ 	self assert: (self isYoungObject: cogit minCogMethodAddress) not.
+ 	self assert: (self isYoungObject: cogit maxCogMethodAddress) not.
+ 	self assert: (self isOldObject: cogit minCogMethodAddress) not.
+ 	self assert: (self isOldObject: cogit maxCogMethodAddress) not!

Item was removed:
- ----- Method: Spur32BitCoMemoryManager>>edenBytes: (in category 'snapshot') -----
- edenBytes: bytes
- 	newSpaceLimit := bytes + coInterpreter cogCodeSize!

Item was removed:
- ----- Method: Spur32BitCoMemoryManager>>newSpaceBytes (in category 'accessing') -----
- newSpaceBytes
- 	"during snapshot load newSpaceLimit holds newSpace size + cogCodeSize temporarily."
- 	^newSpaceLimit - coInterpreter cogCodeSize - coInterpreter interpreterAllocationReserveBytes!

Item was removed:
- ----- Method: Spur32BitCoMemoryManager>>newSpaceLimitAddress (in category 'trampoline support') -----
- newSpaceLimitAddress
- 	<api>
- 	<returnTypeC: #usqInt>
- 	^self cCode: [(self addressOf: newSpaceLimit) asUnsignedInteger]
- 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #newSpaceLimit in: self]!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>setHeapBase:memoryLimit:endOfMemory: (in category 'snapshot') -----
+ setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
+ 	super setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd.
+ 	oldSpaceStart := newSpaceLimit + coInterpreter cogCodeSize!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>cogCodeBase (in category 'simulation only') -----
+ cogCodeBase
+ 	^newSpaceLimit!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>isIntegerObject: (in category 'object testing') -----
  isIntegerObject: oop
  	"This list records the valid senders of isIntegerObject: as we replace uses of
  	  isIntegerObject: by isImmediate: where appropriate."
  	| sel |
  	sel := thisContext sender method selector.
  	(#(	DoIt
  		DoItIn:
  		on:do: "from the debugger"
  		makeBaseFrameFor:
  		quickFetchInteger:ofObject:
  		frameOfMarriedContext:
  		objCouldBeClassObj:
  		isMarriedOrWidowedContext:
  		shortPrint:
  		bytecodePrimAt
  		bytecodePrimAtPut
  		commonAt:
  		commonAtPut:
  		loadFloatOrIntFrom:
  		positive32BitValueOf:
  		primitiveExternalCall
  		checkedIntegerValueOf:
  		bytecodePrimAtPut
  		commonAtPut:
  		primitiveVMParameter
  		checkIsStillMarriedContext:currentFP:
  		displayBitsOf:Left:Top:Right:Bottom:
  		fetchStackPointerOf:
  		primitiveContextAt
  		primitiveContextAtPut
  		subscript:with:storing:format:
  		printContext:
  		compare31or32Bits:equal:
  		signed64BitValueOf:
  		primDigitMultiply:negative:
  		digitLength:
  		isNegativeIntegerValueOf:
  		magnitude64BitValueOf:
  		primitiveMakePoint
  		primitiveAsCharacter
  		primitiveInputSemaphore
  		baseFrameReturn
  		primitiveExternalCall
  		primDigitCompare:
  		isLiveContext:
  		numPointerSlotsOf:
  		fileValueOf:
  		loadBitBltDestForm
  		fetchIntOrFloat:ofObject:ifNil:
  		fetchIntOrFloat:ofObject:
  		loadBitBltSourceForm
  		loadPoint:from:
  		primDigitAdd:
  		primDigitSubtract:
  		positive64BitValueOf:
  		digitBitLogic:with:opIndex:
  		signed32BitValueOf:
  		isNormalized:
  		primDigitDiv:negative:
  		bytesOrInt:growTo:
  		primitiveNewMethod
  		isCogMethodReference:
  		functionForPrimitiveExternalCall:
  		genSpecialSelectorArithmetic
  		genSpecialSelectorComparison
  		ensureContextHasBytecodePC:
  		instVar:ofContext:
  		ceBaseFrameReturn:
  		inlineCacheTagForInstance:
  		primitiveObjectAtPut
  		commonVariable:at:put:cacheIndex:
  		primDigitBitShiftMagnitude:
  		externalInstVar:ofContext:
  		primitiveGrowMemoryByAtLeast
  		primitiveFileSetPosition
+ 		cogMethodDoesntLookKosher:
+ 		shortPrintOop:) includes: sel) ifFalse:
- 		cogMethodDoesntLookKosher:) includes: sel) ifFalse:
  		[self halt].
  	^super isIntegerObject: oop!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>setHeapBase:memoryLimit:endOfMemory: (in category 'initialization') -----
+ setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
+ 	"As invoced by CogVMSimulator>>openOn:extraBytes: baseOfHeap contains the combined
+ 	 zone sizes for cog methods, stack zone, etc.  The memory map in SqueakV3 looks like
+ 		0:	cogCode
+ 			stackZone
+ 			methodCache
+ 			primTraceLog
+ 			rumpCStack
+ 		heapBase:
+ 			nilObj etc
+ 	 But here in Spur we want
+ 		0:	(newSpace):
+ 			past/future survivor space
+ 			past/future survivor space
+ 			eden
+ 		M:
+ 			cogCode
+ 			stackZone
+ 			methodCache
+ 			primTraceLog
+ 			rumpCStack
+ 		heapBase:
+ 			nilObj etc"
+ 	super setHeapBase: Cogit guardPageSize memoryLimit: memLimit endOfMemory: memEnd.
+ 	oldSpaceStart := newSpaceLimit + baseOfHeap.
+ 	coInterpreter heapBase: oldSpaceStart.!

Item was changed:
  ----- Method: SpurGenerationScavenger>>copyAndForward: (in category 'scavenger') -----
  copyAndForward: survivor
  	"copyAndForward: survivor copies a survivor object either to
  	 futureSurvivorSpace or, if it is to be promoted, to oldSpace.
  	 It leaves a forwarding pointer behind.  If the object is weak
  	 then corpse is threaded onto the weakList for later treatment."
  	<inline: false>
  	| bytesInObj newLocation hash |
+ 	self assert: ((manager isInEden: survivor) "cog methods should be excluded."
+ 				or: [manager isInPastSpace: survivor]).
- 	self assert: survivor >= manager startOfMemory. "cog methods should be excluded."
  	bytesInObj := manager bytesInObject: survivor.
  	"Must remember hash before copying because threading
  	 on to the weak & ephemeron lists smashes the hash field."
  	hash := manager rawHashBitsOf: survivor.
  	((self shouldBeTenured: survivor)
  	 or: [futureSurvivorStart + bytesInObj > futureSpace limit])
  		ifTrue:
  			[newLocation := self copyToOldSpace: survivor.
  			 manager forwardSurvivor: survivor to: newLocation]
  		ifFalse:
  			[newLocation := self copyToFutureSpace: survivor bytes: bytesInObj.
  			 manager forwardSurvivor: survivor to: newLocation.
  			 "if weak or ephemeron add to the relevant lists if newLocation is young.  If
  			  old, newLocation will be remembered and dealt with in the rememberedSet."
  			 (manager isWeakNonImm: newLocation) ifTrue:
  				[self addToWeakList: survivor].
  			 ((manager isEphemeron: newLocation)
  			  and: [(self isScavengeSurvivor: (manager keyOfEphemeron: newLocation)) not]) ifTrue:
  				[self addToEphemeronList: survivor]].
  	hash ~= 0 ifTrue:
  		[manager setHashBitsOf: newLocation to: hash].
  	^newLocation!

Item was changed:
  ----- Method: SpurGenerationScavenger>>corpseForCorpseOffset: (in category 'weakness and ephemerality') -----
  corpseForCorpseOffset: corpseOffset
  	"Use the identityHash and format fields to construct a 27 bit offset through
  	 non-future newSpace and use this to implement lists for weak array and
  	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30 bytes
  	 or 1Gb, big enough for newSpace for a good few years yet."
+ 	^corpseOffset << manager shiftForAllocationUnit + manager newSpaceStart!
- 	^corpseOffset << manager shiftForAllocationUnit + manager startOfMemory!

Item was changed:
  ----- Method: SpurGenerationScavenger>>corpseOffsetOf: (in category 'weakness and ephemerality') -----
  corpseOffsetOf: corpse
  	"Answer the offset of the corpse in newSpace as a multiple of allocationUnits.
  	 Use the identityHash and format fields to construct a 27 bit offset through
  	 non-future newSpace and use this to implement lists for weak array and
  	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30
  	 bytes or 1Gb, big enough for newSpace for a good few years yet."
+ 	^corpse - manager newSpaceStart >> manager shiftForAllocationUnit.!
- 	^corpse - manager startOfMemory >> manager shiftForAllocationUnit.!

Item was removed:
- ----- Method: SpurGenerationScavenger>>manager:newSpaceStart:newSpaceBytes:edenBytes: (in category 'initialization') -----
- manager: aSpurMemoryManager newSpaceStart: startAddress newSpaceBytes: totalBytes edenBytes: requestedEdenBytes 	self manager: aSpurMemoryManager.
- 	self newSpaceStart: startAddress newSpaceBytes: totalBytes edenBytes: requestedEdenBytes!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
+ 	self declareCAsOop: #(	memory freeStart scavengeThreshold newSpaceStart newSpaceLimit pastSpaceStart
+ 							lowSpaceThreshold freeOldSpaceStart oldSpaceStart endOfMemory sortedFreeChunks)
- 	self declareCAsOop: #(	memory freeStart scavengeThreshold newSpaceLimit pastSpaceStart
- 							lowSpaceThreshold freeOldSpaceStart startOfMemory endOfMemory sortedFreeChunks)
  		in: aCCodeGenerator.
  	self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs'])
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #freeListsMask type: #usqInt;
  		var: #freeLists type: #'sqInt *';
  		var: #classTableBitmap type: #'unsigned char *';
  		var: #objStackInvalidBecause type: #'char *';
  		var: #highestObjects type: #SpurCircularBuffer;
  		var: #unscannedEphemerons type: #SpurContiguousObjStack.
  	aCCodeGenerator
  		var: #remapBuffer
  		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #extraRoots
  		declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'!

Item was removed:
- ----- Method: SpurMemoryManager>>addressCouldBeObjWhileScavenging: (in category 'debug support') -----
- addressCouldBeObjWhileScavenging: address
- 	^(address bitAnd: self baseHeaderSize - 1) = 0
- 	  and: [(self isInOldSpace: address)
- 		or: [(self isInEden: address)
- 		or: [(self isInSurvivorSpace: address)
- 		or: [scavengeInProgress and: [self isInFutureSpace: address]]]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>adjustAllOopsBy: (in category 'snapshot') -----
  adjustAllOopsBy: bytesToShift
  	"Adjust all oop references by the given number of bytes. This is
  	 done just after reading in an image when the new base address
  	 of the object heap is different from the base address in the image,
  	 or when loading multiple segments that have been coalesced.  Also
  	 set bits in the classTableBitmap corresponding to used classes."
  
  	| obj |
  	self countNumClassPagesPreSwizzle: bytesToShift;
  		ensureAdequateClassTableBitmap.
  	(bytesToShift ~= 0
  	 or: [segmentManager numSegments > 1])
  		ifTrue:
  			[self assert: self newSpaceIsEmpty.
+ 			 obj := self objectStartingAt: oldSpaceStart.
- 			 obj := self objectStartingAt: newSpaceLimit.
  			 [self oop: obj isLessThan: endOfMemory] whileTrue:
  				[(self isFreeObject: obj)
  					ifTrue: [self swizzleFieldsOfFreeChunk: obj]
  					ifFalse:
  						[self inClassTableBitmapSet: (self classIndexOf: obj).
  						 self swizzleFieldsOfObject: obj].
  				 obj := self objectAfter: obj]]
  		ifFalse:
  			[self assert: self newSpaceIsEmpty.
+ 			 obj := self objectStartingAt: oldSpaceStart.
- 			 obj := self objectStartingAt: newSpaceLimit.
  			 [self oop: obj isLessThan: endOfMemory] whileTrue:
  				[(self isFreeObject: obj) ifFalse:
  					[self inClassTableBitmapSet: (self classIndexOf: obj)].
  				 obj := self objectAfter: obj]]!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize:newSpaceSize:stackSize:codeSize: (in category 'spur bootstrap') -----
  allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes
  	"Intialize the receiver for bootsraping an image.
  	 Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
  	 to allocate in oldSpace.  Later on (in initializePostBootstrap) freeStart and scavengeThreshold
  	 will be set to sane values."
  	<doNotGenerate>
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
  	memory := (self endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes + stackBytes) // 4.
+ 	"N.B. This layout does NOT reflect the layout of SpurCoMemoryManager"
+ 	newSpaceStart := codeBytes + stackBytes.
- 	startOfMemory := codeBytes + stackBytes.
  	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	"leave newSpace empty for the bootstrap"
+ 	freeStart := newSpaceBytes + newSpaceStart.
+ 	newSpaceLimit := newSpaceBytes + newSpaceStart.
- 	freeStart := newSpaceBytes + startOfMemory.
- 	newSpaceLimit := newSpaceBytes + startOfMemory.
  	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
+ 	scavenger := SpurGenerationScavengerSimulator new.
+ 	scavenger manager: self.
+ 	scavenger newSpaceStart: newSpaceStart
+ 				newSpaceBytes: newSpaceBytes
+ 				edenBytes: newSpaceBytes * self scavengerDenominator
+ 						- self numSurvivorSpaces // self scavengerDenominator!
- 	scavenger := SpurGenerationScavengerSimulator new
- 					manager: self
- 					newSpaceStart: startOfMemory
- 					newSpaceBytes: newSpaceBytes
- 					edenBytes: newSpaceBytes * self scavengerDenominator - self numSurvivorSpaces // self scavengerDenominator!

Item was changed:
  ----- Method: SpurMemoryManager>>baseAddressOfImage (in category 'snapshot') -----
  baseAddressOfImage
+ 	^oldSpaceStart!
- 	^newSpaceLimit!

Item was changed:
  ----- Method: SpurMemoryManager>>beRootIfOld: (in category 'store check') -----
  beRootIfOld: oop 
  	"If this object is old, mark it as a root (because a new object
  	 may be stored into it)."
  	<api>
  	<inline: false>
+ 	(self isOldObject: oop) ifTrue:"No, oop is an old object"
- 	(self isYoung: oop) ifTrue:"Yes, oop is an old object"
  		[self possibleRootStoreInto: oop]!

Item was changed:
  ----- Method: SpurMemoryManager>>cheapAddressCouldBeInHeap: (in category 'debug support') -----
  cheapAddressCouldBeInHeap: address 
  	^(address bitAnd: self wordSize - 1) = 0
+ 	  and: [(self oop: address isGreaterThanOrEqualTo: newSpaceStart)
- 	  and: [(self oop: address isGreaterThanOrEqualTo: startOfMemory)
  	  and: [self oop: address isLessThan: endOfMemory]]!

Item was added:
+ ----- Method: SpurMemoryManager>>cheapIsInMemory: (in category 'plugin support') -----
+ cheapIsInMemory: address
+ 	"Answer if the given address is in ST object memory.  For simulation only."
+ 	<doNotGenerate>
+ 	^(address < newSpaceLimit and: [address >= newSpaceStart])
+ 	 or: [address >= oldSpaceStart and: [address < endOfMemory]]!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity: (in category 'debug support') -----
  checkHeapIntegrity: excludeUnmarkedNewSpaceObjs
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccessibleObjects has set a bit at each
  	 object's header.  Scan all objects in the heap checking that every
  	 pointer points to a header.  Scan the rootTable, remapBuffer and
  	 extraRootTable checking that every entry is a pointer to a header.
  	 Check that the number of roots is correct and that all rootTable
  	 entries have their rootBit set. Answer if all checks pass."
  	| ok numRememberedRootsInHeap |
  	<inline: false>
  	ok := true.
  	numRememberedRootsInHeap := 0.
  	self allHeapEntitiesDo:
  		[:obj| | containsYoung fieldOop classIndex classOop |
  		((self isFreeObject: obj)
  		 or: [(self isYoungObject: obj) and: [(self isMarked: obj) not and: [excludeUnmarkedNewSpaceObjs]]]) ifFalse:
  			[containsYoung := false.
  			 (self isRemembered: obj) ifTrue:
  				[numRememberedRootsInHeap := numRememberedRootsInHeap + 1.
  				 (scavenger isInRememberedSet: obj) ifFalse:
  					[coInterpreter print: 'remembered object '; printHex: obj; print: ' is not in remembered table'; cr.
  					 self eek.
  					 ok := false]].
  			 (self isForwarded: obj)
  				ifTrue:
  					[fieldOop := self fetchPointer: 0 ofMaybeForwardedObject: obj.
  					 (heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  						[coInterpreter print: 'object leak in forwarder '; printHex: obj; print: ' to unmapped '; printHex: fieldOop; cr.
  						 self eek.
  						 ok := false].
  					 (self isYoung: fieldOop) ifTrue:
  						[containsYoung := true]]
  				ifFalse:
  					[classOop := self classAtIndex: (classIndex := self classIndexOf: obj).
  					 ((classOop isNil or: [classOop = nilObj])
  					  and: [(self isHiddenObj: obj) not]) ifTrue:
  						[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; print: (classOop ifNil: ['nil'] ifNotNil: ['nilObj']); cr.
  						 self eek.
  						 ok := false].
  					 self baseHeaderSize to: (self lastPointerOf: obj) by: BytesPerOop do:
  						[:ptr|
  						 fieldOop := self longAt: obj + ptr.
  						 (self isNonImmediate: fieldOop) ifTrue:
  							[| fi |
  							 fi := ptr - self baseHeaderSize / self wordSize.
  							 (fieldOop bitAnd: self wordSize - 1) ~= 0
  								ifTrue:
  									[coInterpreter print: 'misaligned oop in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  									 self eek.
  									 ok := false]
  								ifFalse:
  									[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  										[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  										 self eek.
  										 ok := false].
+ 									 (self isYoung: fieldOop) ifTrue:
- 									 "don't be misled by CogMethods; they appear to be young, but they're not"
- 									 ((self isYoung: fieldOop)
- 									  and: [self oop: fieldOop isGreaterThanOrEqualTo: startOfMemory]) ifTrue:
  										[containsYoung := true]]]]].
  					(containsYoung and: [(self isYoung: obj) not]) ifTrue:
  						[(self isRemembered: obj) ifFalse:
  							[coInterpreter print: 'unremembered object '; printHex: obj; print: ' contains young oop(s)'; cr.
  							 self eek.
  							 ok := false]]]].
  	numRememberedRootsInHeap ~= scavenger rememberedSetSize ifTrue:
  		[coInterpreter
  			print: 'root count mismatch. #heap roots ';
  			printNum: numRememberedRootsInHeap;
  			print: '; #roots ';
  			printNum: scavenger rememberedSetSize;
  			cr.
  		self eek.
  		"But the system copes with overflow..."
  		self flag: 'no support for remembered set overflow yet'.
  		"ok := rootTableOverflowed and: [needGCFlag]"].
  	scavenger rememberedSetWithIndexDo:
  		[:obj :i|
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned oop in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  						 self eek.
  						 ok := false]
  					ifFalse:
  						[(self isYoung: obj) ifTrue:
  							[coInterpreter print: 'non-root in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  							 self eek.
  							 ok := false]]]].
  	1 to: remapBufferCount do:
  		[:ri| | obj |
  		obj := remapBuffer at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	1 to: extraRootCount do:
  		[:ri| | obj |
  		obj := (extraRoots at: ri) at: 0.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	^ok!

Item was added:
+ ----- Method: SpurMemoryManager>>checkMemoryMap (in category 'debug support') -----
+ checkMemoryMap
+ 	self assert: (self isYoungObject: newSpaceStart).
+ 	self assert: (self isYoungObject: newSpaceLimit - self wordSize).
+ 	self assert: (self isOldObject: newSpaceStart) not.
+ 	self assert: (self isOldObject: newSpaceLimit - self wordSize) not.
+ 	self assert: (self isYoungObject: newSpaceLimit) not.
+ 	self assert: (self isYoungObject: oldSpaceStart) not.
+ 	self assert: (self isYoungObject: endOfMemory) not.
+ 	self assert: (self isOldObject: newSpaceLimit).
+ 	self assert: (self isOldObject: oldSpaceStart).
+ 	self assert: (self isOldObject: endOfMemory)!

Item was changed:
  ----- Method: SpurMemoryManager>>checkOkayOop: (in category 'debug support') -----
  checkOkayOop: oop
  	"Verify that the given oop is legitimate. Check address, header, and size but not class.
  	 Answer true if OK.  Otherwise print reason and answer false."
  	<api>
  	<var: #oop type: #usqInt>
  	| classIndex fmt unusedBits unusedBitsInYoungObjects |
  	<var: #unusedBits type: #usqLong>
  
  	"address and size checks"
  	(self isImmediate: oop) ifTrue: [^true].
+ 	(self addressCouldBeObj: oop) ifFalse:
- 	(self addressCouldBeObjWhileScavenging: oop) ifFalse:
  		[self print: 'oop '; printHex: oop; print: ' is not a valid address'. ^false].
  
  	(self oop: (self addressAfter: oop) isLessThanOrEqualTo: endOfMemory) ifFalse:
  		[self print: 'oop '; printHex: oop; print: ' size would make it extend beyond the end of memory'. ^false].
  
  	"header type checks"
  	(classIndex := self classIndexOf: oop) >= self firstClassIndexPun ifFalse:
  		[self print: 'oop '; printHex: oop; print: ' is a free chunk, or bridge, not an object'. ^false].
  	((self rawNumSlotsOf: oop) = self numSlotsMask
  	 and: [(self rawNumSlotsOf: oop - self baseHeaderSize) ~= self numSlotsMask]) ifTrue:
  		[self print: 'oop '; printHex: oop; print: ' header has overflow header word, but overflow word does not have a saturated numSlots field'. ^false].
  
  	"format check"
  	fmt := self formatOf: oop.
  	(fmt = 6) | (fmt = 8) ifTrue:
  		[self print: 'oop '; printHex: oop; print: ' has an unknown format type'. ^false].
  	(fmt = self forwardedFormat) ~= (classIndex = self isForwardedObjectClassIndexPun) ifTrue:
  		[self print: 'oop '; printHex: oop; print: ' has mis-matched format/classIndex fields; only one of them is the isForwarded value'. ^false].
  
  	"specific header bit checks"
  	unusedBits := (1 << self classIndexFieldWidth)
  				   | (1 << (self identityHashFieldWidth + 32)).
  	((self longLongAt: oop) bitAnd: unusedBits) ~= 0 ifTrue:
  		[self print: 'oop '; printHex: oop; print: ' has some unused header bits set; should be zero'. ^false].
  
  	unusedBitsInYoungObjects := self newSpaceRefCountMask.
  	((self longAt: oop) bitAnd: unusedBitsInYoungObjects) ~= 0 ifTrue:
  		[self print: 'oop '; printHex: oop; print: ' has some header bits unused in young objects set; should be zero'. ^false].
  	^true!

Item was changed:
  ----- Method: SpurMemoryManager>>checkedLongAt: (in category 'memory access') -----
  checkedLongAt: byteAddress
  	"Assumes zero-based array indexing."
  	<api>
+ 	(self isInMemory: byteAddress) ifFalse:
- 	(byteAddress asUnsignedInteger < self startOfMemory
- 	 or: [byteAddress asUnsignedInteger > endOfMemory
- 	 or: [byteAddress asUnsignedInteger > newSpaceLimit
- 		and: [(segmentManager isInSegments: byteAddress asUnsignedInteger) not]]]) ifTrue:
  		[self warning: 'checkedLongAt bad address'.
  		 coInterpreter primitiveFail].
  	^self longAt: byteAddress!

Item was changed:
  ----- Method: SpurMemoryManager>>countNumClassPagesPreSwizzle: (in category 'class table') -----
  countNumClassPagesPreSwizzle: bytesToShift
  	"Compute the used size of the class table before swizzling.  Needed to
  	 initialize the classTableBitmap which is populated during adjustAllOopsBy:"
  	| firstObj classTableRoot nilObjPreSwizzle |
+ 	firstObj := self objectStartingAt: oldSpaceStart. "a.k.a. nilObj"
- 	firstObj := self objectStartingAt: newSpaceLimit. "a.k.a. nilObj"
  	"first five objects are nilObj, falseObj, trueObj, freeListsObj, classTableRootObj"
  	classTableRoot := self objectAfter:
  							(self objectAfter:
  									(self objectAfter:
  											(self objectAfter: firstObj
  												limit: endOfMemory)
  										limit: endOfMemory)
  								limit: endOfMemory)
  							limit: endOfMemory.
+ 	nilObjPreSwizzle := oldSpaceStart - bytesToShift.
- 	nilObjPreSwizzle := newSpaceLimit - bytesToShift.
  	numClassTablePages := self numSlotsOf: classTableRoot.
  	self assert: numClassTablePages = (self classTableRootSlots + self hiddenRootSlots).
  	2 to: numClassTablePages - 1 do:
  		[:i|
  		(self fetchPointer: i ofObject: classTableRoot) = nilObjPreSwizzle ifTrue:
  			[numClassTablePages := i.
  			 ^self]]
  	!

Item was changed:
+ ----- Method: SpurMemoryManager>>edenBytes: (in category 'accessing') -----
- ----- Method: SpurMemoryManager>>edenBytes: (in category 'snapshot') -----
  edenBytes: bytes
+ 	edenBytes := bytes!
- 	newSpaceLimit := bytes!

Item was changed:
  ----- Method: SpurMemoryManager>>firstAccessibleObject (in category 'object enumeration') -----
  firstAccessibleObject
  	<inline: false>
+ 	self assert: nilObj = oldSpaceStart.
- 	self assert: nilObj = newSpaceLimit.
  	"flush newSpace to settle the enumeration."
  	self flushNewSpace.
  	^nilObj!

Item was changed:
  ----- Method: SpurMemoryManager>>inPlaceBecome:and:copyHashFlag: (in category 'become implementation') -----
  inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag
  	"Do become in place by swapping object contents."
  	| headerTemp temp1 temp2 o1HasYoung o2HasYoung |
  	self assert: (self numSlotsOf: obj1) = (self numSlotsOf: obj2).
  	"swap headers, but swapping headers swaps remembered bits;
  	 these need to be unswapped."
  	temp1 := self isRemembered: obj1.
  	temp2 := self isRemembered: obj2.
  	headerTemp := self longLongAt: obj1.
  	self longLongAt: obj1 put: (self longLongAt: obj2).
  	self longLongAt: obj2 put: headerTemp.
  	self setIsRememberedOf: obj1 to: temp1.
  	self setIsRememberedOf: obj2 to: temp2.
  	"swapping headers swaps hash; if !!copyHashFlag undo hash copy"
  	copyHashFlag ifFalse:
  		[temp1 := self rawHashBitsOf: obj1.
  		 self setHashBitsOf: obj1 to: (self rawHashBitsOf: obj2).
  		 self setHashBitsOf: obj2 to: temp1].
  	o1HasYoung := o2HasYoung := false.
  	0 to: (self numSlotsOf: obj1) - 1 do:
  		[:i|
  		temp1 := self fetchPointer: i ofObject: obj1.
  		temp2 := self fetchPointer: i ofObject: obj2.
  		self storePointerUnchecked: i
  			ofObject: obj1
  			withValue: temp2.
  		self storePointerUnchecked: i
  			ofObject: obj2
  			withValue: temp1.
  		(self isYoung: temp2) ifTrue:
  			[o1HasYoung := true].
  		(self isYoung: temp1) ifTrue:
  			[o2HasYoung := true]].
+ 	(self isOldObject: obj1) ifTrue:
- 	(self isYoungObject: obj1) ifFalse:
  		[o1HasYoung ifTrue:
  			[self possibleRootStoreInto: obj1]].
+ 	(self isOldObject: obj2) ifTrue:
- 	(self isYoungObject: obj2) ifFalse:
  		[o2HasYoung ifTrue:
  			[self possibleRootStoreInto: obj2]]!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeNewSpaceVariables (in category 'gc - scavenging') -----
  initializeNewSpaceVariables
  	freeStart := scavenger eden start.
  	pastSpaceStart := scavenger pastSpace start.
  	scavengeThreshold := scavenger eden limit
  							- (scavenger edenBytes / 64)
  							- coInterpreter interpreterAllocationReserveBytes.
+ 	newSpaceStart := scavenger pastSpace start min: scavenger futureSpace start.
+ 	self assert: newSpaceStart < scavenger eden start.
- 	startOfMemory := scavenger pastSpace start min: scavenger futureSpace start.
- 	self assert: startOfMemory < scavenger eden start.
  	self initSpaceForAllocationCheck: (self addressOf: scavenger eden)!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeObjectMemory: (in category 'initialization') -----
  initializeObjectMemory: bytesToShift
  	"Initialize object memory variables at startup time. Assume endOfMemory is initially set (by the image-reading code) to the end of the last object in the image. Initialization redefines endOfMemory to be the end of the object allocation area based on the total available memory, but reserving some space for forwarding blocks."
  	"Assume: image reader initializes the following variables:
  		memory
  		memoryLimit
  		specialObjectsOop
  		lastHash
  	"
  	<inline: false>
  	| freeListObj |
  	"Catch mis-initializations leading to bad translations to C"
  	self assert: BaseHeaderSize = self baseHeaderSize.
  	self bootstrapping ifFalse:
  		[self
  			initSegmentBridgeWithBytes: self bridgeSize
  			at: endOfMemory - self bridgeSize].
  	segmentManager adjustSegmentSwizzlesBy: bytesToShift.
  	"image may be at a different address; adjust oops for new location"
  	self adjustAllOopsBy: bytesToShift.
  	specialObjectsOop := segmentManager swizzleObj: specialObjectsOop.
  
  	"heavily used special objects"
  	nilObj		:= self splObj: NilObject.
  	falseObj	:= self splObj: FalseObject.
  	trueObj		:= self splObj: TrueObject.
  
  	"In Cog we insist that nil, true & false are next to each other (Cogit generates tighter
  	 conditional branch code as a result).  In addition, Spur places the free lists and
  	 class table root page immediately following them."
+ 	self assert: nilObj = oldSpaceStart.
- 	self assert: nilObj = newSpaceLimit.
  	self assert: falseObj = (self objectAfter: nilObj).
  	self assert: trueObj = (self objectAfter: falseObj).
  	freeListObj := self objectAfter: trueObj.
  	self reInitializeClassTablePostLoad: (self objectAfter: freeListObj).
  	markStack := self swizzleObjStackAt: MarkStackRootIndex.
  	weaklingStack := self swizzleObjStackAt: WeaklingStackRootIndex.
  	ephemeronQueue := self swizzleObjStackAt: EphemeronQueueRootIndex.
  
  	self initializeFreeSpacePostLoad: freeListObj.
  	segmentManager collapseSegmentsPostSwizzle.
  	self computeFreeSpacePostSwizzle.
  	self bootstrapping ifFalse:
  		[self initializeNewSpaceVariables].
  	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart"
  	segmentManager checkSegments.
  
  	"These defaults should depend on machine size; e.g. too small on a powerful laptop, too big on a Pi."
  	growHeadroom := 16*1024*1024.		"headroom when growing"
  	shrinkThreshold := 32*1024*1024.		"free space before shrinking"!

Item was changed:
  ----- Method: SpurMemoryManager>>isInMemory: (in category 'plugin support') -----
  isInMemory: address 
+ 	"Answer if the given address is in ST object memory."
+ 	^(self isInNewSpace: address)
+ 	  or: [segmentManager isInSegments: address]!
- 	"Return true if the given address is in ST object memory"
- 	^(self oop: address isGreaterThanOrEqualTo: startOfMemory)
- 		and: [(self oop: address isLessThan: newSpaceLimit)
- 			or: [segmentManager isInSegments: address]]!

Item was changed:
  ----- Method: SpurMemoryManager>>isInNewSpace: (in category 'object testing') -----
  isInNewSpace: objOop
  	^(self oop: objOop isLessThan: newSpaceLimit)
+ 	  and: [self oop: objOop isGreaterThanOrEqualTo: newSpaceStart]!
- 	  and: [self oop: objOop isGreaterThanOrEqualTo: startOfMemory]!

Item was changed:
  ----- Method: SpurMemoryManager>>isInOldSpace: (in category 'object testing') -----
  isInOldSpace: address
  	^self
  		oop: address
+ 		isGreaterThanOrEqualTo: oldSpaceStart
- 		isGreaterThanOrEqualTo: newSpaceLimit
  		andLessThan: endOfMemory!

Item was added:
+ ----- Method: SpurMemoryManager>>isInPastSpace: (in category 'object testing') -----
+ isInPastSpace: address
+ 	^self
+ 		oop: address
+ 		isGreaterThanOrEqualTo: scavenger pastSpace start
+ 		andLessThan: pastSpaceStart!

Item was added:
+ ----- Method: SpurMemoryManager>>isOldObject: (in category 'object testing') -----
+ isOldObject: objOop
+ 	<api>
+ 	"Answer if obj is old. Require that obj is non-immediate."
+ 	self assert: (self isNonImmediate: objOop).
+ 	^self oop: objOop isGreaterThanOrEqualTo: oldSpaceStart!

Item was changed:
  ----- Method: SpurMemoryManager>>isYoungObject: (in category 'object testing') -----
  isYoungObject: objOop
  	<api>
+ 	"Answer if obj is young. Require that obj is non-immediate."
- 	"Answer if obj is young. Assume obj is non-immediate."
  	self assert: (self isNonImmediate: objOop).
  	^self oop: objOop isLessThan: newSpaceLimit!

Item was changed:
  ----- Method: SpurMemoryManager>>memoryBaseForImageRead (in category 'snapshot') -----
  memoryBaseForImageRead
  	"Answer the address to read the image into."
+ 	^oldSpaceStart!
- 	^newSpaceLimit!

Item was changed:
  ----- Method: SpurMemoryManager>>newSpaceBytes (in category 'accessing') -----
  newSpaceBytes
+ 	^edenBytes!
- 	"during snapshot load newSpaceLimit holds newSpace size temporarily."
- 	^newSpaceLimit - coInterpreter interpreterAllocationReserveBytes!

Item was changed:
  ----- Method: SpurMemoryManager>>newSpaceLimit (in category 'accessing') -----
  newSpaceLimit
+ 	<api>
- 	<cmacro: '() GIV(newSpaceLimit)'>
  	^newSpaceLimit!

Item was added:
+ ----- Method: SpurMemoryManager>>newSpaceStart (in category 'accessing') -----
+ newSpaceStart
+ 	^newSpaceStart!

Item was changed:
  ----- Method: SpurMemoryManager>>okayOop: (in category 'debug support') -----
  okayOop: signedOop
  	"Verify that the given oop is legitimate. Check address, header, and size but not class."
  
  	| oop classIndex fmt unusedBits unusedBitsInYoungObjects |
  	<var: #oop type: #usqInt>
  	<var: #unusedBits type: #usqLong>
  	oop := self cCoerce: signedOop to: #usqInt.
  
  	"address and size checks"
  	(self isImmediate: oop) ifTrue: [^true].
+ 	(self addressCouldBeObj: oop) ifFalse:
- 	(self addressCouldBeObjWhileScavenging: oop) ifFalse:
  		[self error: 'oop is not a valid address'. ^false].
  
  	(self oop: (self addressAfter: oop) isLessThanOrEqualTo: endOfMemory) ifFalse:
  		[self error: 'oop size would make it extend beyond the end of memory'. ^false].
  
  	"header type checks"
  	(classIndex := self classIndexOf: oop) >= self firstClassIndexPun ifFalse:
  		[self error: 'oop is a free chunk, or bridge, not an object'. ^false].
  	((self rawNumSlotsOf: oop) = self numSlotsMask
  	 and: [(self rawNumSlotsOf: oop - self baseHeaderSize) ~= self numSlotsMask]) ifTrue:
  		[self error: 'oop header has overflow header word, but overflow word does not have a saturated numSlots field'. ^false].
  
  	"format check"
  	fmt := self formatOf: oop.
  	(fmt = 6) | (fmt = 8) ifTrue:
  		[self error: 'oop has an unknown format type'. ^false].
  	(fmt = self forwardedFormat) ~= (classIndex = self isForwardedObjectClassIndexPun) ifTrue:
  		[self error: 'oop has mis-matched format/classIndex fields; only one of them is the isForwarded value'. ^false].
  
  	"specific header bit checks"
  	unusedBits := (1 << self classIndexFieldWidth)
  				   | (1 << (self identityHashFieldWidth + 32)).
  	((self longLongAt: oop) bitAnd: unusedBits) ~= 0 ifTrue:
  		[self error: 'some unused header bits are set; should be zero'. ^false].
  
  	unusedBitsInYoungObjects := (1 << self greyBitShift)
  								   | (1 << self pinnedBitShift)
  								   | (1 << self rememberedBitShift).
  	((self longAt: oop) bitAnd: unusedBitsInYoungObjects) ~= 0 ifTrue:
  		[self error: 'some header bits unused in young objects are set; should be zero'. ^false].
  	^true
  !

Item was added:
+ ----- Method: SpurMemoryManager>>oldSpaceStart (in category 'accessing') -----
+ oldSpaceStart
+ 	^oldSpaceStart!

Item was changed:
  ----- Method: SpurMemoryManager>>reverseBytesInMemory (in category 'snapshot') -----
  reverseBytesInMemory
+ 	self reverseBytesFrom: oldSpaceStart to: endOfMemory!
- 	self reverseBytesFrom: newSpaceLimit to: endOfMemory!

Item was changed:
  ----- Method: SpurMemoryManager>>scavengingGCTenuringIf: (in category 'gc - scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
  	"Run the scavenger."
  
  	self assert: remapBufferCount = 0.
  	self assert: scavenger eden limit - freeStart > coInterpreter interpreterAllocationReserveBytes.
+ 	self checkMemoryMap.
  	self checkFreeSpace.
  	"coInterpreter printCallStackFP: coInterpreter framePointer"
  
  	self runLeakCheckerForFullGC: false.
  	coInterpreter
  		preGCAction: GCModeScavenge;
  		"would prefer this to be in mapInterpreterOops, but
  		 compatibility with ObjectMemory dictates it goes here."
+ 		flushMethodCacheFrom: newSpaceStart to: newSpaceLimit.
- 		flushMethodCacheFrom: startOfMemory to: newSpaceLimit.
  	needGCFlag := false.
  
  	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  
  	self doScavenge: tenuringCriterion.
  
  	statScavenges := statScavenges + 1.
  	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
  	statRootTableCount := scavenger rememberedSetSize.
  
  	coInterpreter postGCAction: GCModeScavenge.
  	self runLeakCheckerForFullGC: false.
  
  	self checkFreeSpace!

Item was changed:
  ----- Method: SpurMemoryManager>>setHeapBase:memoryLimit:endOfMemory: (in category 'snapshot') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
  	"Transcript
  		cr; nextPutAll: 'heapBase: '; print: baseOfHeap; nextPut: $/; nextPutAll: baseOfHeap hex;
  		nextPutAll: ' memLimit '; print: memLimit; nextPut: $/; nextPutAll: memLimit hex;
  		nextPutAll: ' memEnd '; print: memEnd; nextPut: $/; nextPutAll: memEnd hex; cr; flush."
+ 	"This is a little counter-intuitive.  Eden must include interpreterAllocationReserveBytes."
+ 	newSpaceStart := baseOfHeap.
- 	startOfMemory := baseOfHeap.
  	newSpaceLimit := baseOfHeap
  					 + self newSpaceBytes
  					 + coInterpreter interpreterAllocationReserveBytes.
- 	freeOldSpaceStart := memEnd.
- 	endOfMemory := memLimit.
  	scavenger
+ 		newSpaceStart: newSpaceStart
+ 		newSpaceBytes: newSpaceLimit - newSpaceStart
+ 		edenBytes: newSpaceLimit - newSpaceStart
- 		newSpaceStart: baseOfHeap
- 		newSpaceBytes: newSpaceLimit - baseOfHeap
- 		edenBytes: newSpaceLimit - baseOfHeap
  				   * (self scavengerDenominator - self numSurvivorSpaces) // self scavengerDenominator.
  	freeStart := scavenger eden start.
+ 	pastSpaceStart := scavenger pastSpace start.
+ 
+ 	freeOldSpaceStart := memEnd.
+ 	endOfMemory := memLimit.
+ 	oldSpaceStart := newSpaceLimit!
- 	pastSpaceStart := scavenger pastSpace start!

Item was removed:
- ----- Method: SpurMemoryManager>>startOfMemory: (in category 'simulation') -----
- startOfMemory: value
- 	startOfMemory := value.
- 	(freeStart isNil or: [self oop: freeStart isLessThan: value]) ifTrue:
- 		[freeStart := value]!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofForwarder:withValue: (in category 'heap management') -----
  storePointer: fieldIndex ofForwarder: objOop withValue: valuePointer
  
  	self assert: (self isForwarded: objOop).
  	self assert: (self isOopForwarded: valuePointer) not.
  
+ 	(self isOldObject: objOop) ifTrue: "most stores into young objects"
+ 		[(self isYoung: valuePointer) ifTrue:
- 	(self isYoungObject: objOop) ifFalse: "most stores into young objects"
- 		[((self isNonImmediate: valuePointer) and: [self isYoung: valuePointer]) ifTrue:
  			[self possibleRootStoreInto: objOop]].
  
  	^self
  		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
  		put: valuePointer!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofObject:withValue: (in category 'object access') -----
  storePointer: fieldIndex ofObject: objOop withValue: valuePointer
  	"Note must check here for stores of young objects into old ones."
  	self assert: (self isForwarded: objOop) not.
  
+ 	(self isOldObject: objOop) ifTrue: "most stores into young objects"
+ 		[(self isYoung: valuePointer) ifTrue:
+ 			[self possibleRootStoreInto: objOop]].
- 	(self isYoungObject: objOop) ifFalse: "most stores into young objects"
- 		[(self isImmediate: valuePointer) ifFalse:
- 			[(self isYoung: valuePointer) ifTrue:
- 				[self possibleRootStoreInto: objOop]]].
  
  	^self
  		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
  		put: valuePointer!

Item was changed:
  ----- Method: SpurSegmentManager>>collapseSegmentsPostSwizzle (in category 'snapshot') -----
  collapseSegmentsPostSwizzle
  	"The image has been loaded, old segments reconstructed, and the heap
  	 swizzled into a single contiguous segment.  Collapse the segments into one."
  	<inline: false>
  	canSwizzle := false.
  	self cCode: []
  		inSmalltalk:
  			[segments ifNil:
  				[self allocateOrExtendSegmentInfos]].
  	numSegments := 1.
  	(segments at: 0)
+ 		segStart: manager oldSpaceStart;
+ 		segSize: manager endOfMemory - manager oldSpaceStart.
- 		segStart: manager newSpaceLimit;
- 		segSize: manager endOfMemory - manager newSpaceLimit.
  	manager bootstrapping ifTrue:
  		["finally plant a bridge at the end of the coalesced segment and cut back the
  		  manager's notion of the end of memory to immediately before the bridge."
  		 self assert: manager endOfMemory = (segments at: 0) segLimit.
  		 manager
  			initSegmentBridgeWithBytes: manager bridgeSize
  			at: manager endOfMemory - manager bridgeSize].
  	self assert: (self isValidSegmentBridge: manager endOfMemory - manager baseHeaderSize).
  	self assert: (manager numSlotsOfAny: manager endOfMemory - manager baseHeaderSize) = 0!

Item was changed:
  ----- Method: SpurSegmentManager>>readHeapFromImageFile:dataBytes: (in category 'snapshot') -----
  readHeapFromImageFile: f dataBytes: numBytes
  	"Read numBytes of image data from f into memory at memoryBaseForImageRead.
  	 Answer the number of bytes written.  In addition, read each segment, build up the
  	 segment info, while eliminating the bridge objects that end each segment and
  	 give the size of the subsequent segment."
  	<var: #f type: #sqImageFile>
  	<inline: false>
  	| bytesRead totalBytesRead bridge nextSegmentSize oldBase newBase segInfo bridgeSpan |
  	<var: 'segInfo' type: 'SpurSegmentInfo *'>
  	self allocateOrExtendSegmentInfos.
  
  	"segment sizes include the two-header-word bridge at the end of each segment."
  	numSegments := totalBytesRead := 0.
  	oldBase := 0. "N.B. still must be adjusted by oldBaseAddr."
+ 	newBase := manager oldSpaceStart.
- 	newBase := manager newSpaceLimit.
  	nextSegmentSize := firstSegmentSize.
+ 	bridge := firstSegmentSize + manager oldSpaceStart - manager baseHeaderSize.
- 	bridge := firstSegmentSize + manager newSpaceLimit - manager baseHeaderSize.
  	[segInfo := self addressOf: (segments at: numSegments).
  	 segInfo
  		segStart: oldBase;					"N.B. still must be adjusted by oldBaseAddr."
  		segSize: nextSegmentSize;
  		swizzle: newBase - oldBase.	"N.B. still must be adjusted by oldBaseAddr."
  	 bytesRead := self readHeapFrom: f at: newBase dataBytes: nextSegmentSize.
  	 bytesRead > 0 ifTrue:
  			[totalBytesRead := totalBytesRead + bytesRead].
  	 bytesRead ~= nextSegmentSize ifTrue:
  		[^totalBytesRead].
  	 numSegments := numSegments + 1.
  	 bridgeSpan := manager bytesPerSlot * (manager rawOverflowSlotsOf: bridge).
  	 oldBase := oldBase + nextSegmentSize + bridgeSpan.
  	 newBase := newBase + nextSegmentSize - manager bridgeSize.
  	 nextSegmentSize := manager longLongAt: bridge.
  	 nextSegmentSize ~= 0] whileTrue:
  		[bridge := bridge - manager bridgeSize + nextSegmentSize].
  	"newBase should point just past the last bridge. all others should have been eliminated."
+ 	self assert: newBase - manager oldSpaceStart
- 	self assert: newBase - manager newSpaceLimit
  				= (totalBytesRead - (numSegments * manager bridgeSize)).
  	"set freeOldSpaceStart now for adjustAllOopsBy:"
  	manager setFreeOldSpaceStart: newBase.
  	^totalBytesRead!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveNew (in category 'primitive generators') -----
  genPrimitiveNew
  	| r |
+ 	((r := objectRepresentation genInnerPrimitiveNew: 0) < 0
+ 	 and: [r ~= UnimplementedPrimitive]) ifTrue:
- 	(r := objectRepresentation genInnerPrimitiveNew: 0) < 0 ifTrue:
  		[^r].
+ 	"Call the interpreter primitive either when the machine-code primitive
+ 	 fails, or if the machine-code primitive is unimplemented."
  	^self compileFallbackToInterpreterPrimitive!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveNewWithArg (in category 'primitive generators') -----
  genPrimitiveNewWithArg
  	| r |
+ 	((r := objectRepresentation genInnerPrimitiveNewWithArg: 0) < 0
+ 	 and: [r ~= UnimplementedPrimitive]) ifTrue:
- 	(r := objectRepresentation genInnerPrimitiveNewWithArg: 0) < 0 ifTrue:
  		[^r].
+ 	"Call the interpreter primitive either when the machine-code primitive
+ 	 fails, or if the machine-code primitive is unimplemented."
  	^self compileFallbackToInterpreterPrimitive!

Item was changed:
  ----- Method: TMethod>>inferTypesForImplicitlyTypedVariablesIn: (in category 'type inference') -----
  inferTypesForImplicitlyTypedVariablesIn: aCodeGen
+ 	| explicitlyTyped |
+ 	explicitlyTyped := declarations keys asSet.
  	parseTree nodesDo:
  		[:node| | type var m |
  		"If there is something of the form i >= 0, then i should be signed, not unsigned."
  		(node isSend
  		 and: [(locals includes: (var := node receiver variableNameOrNil))
+ 		 and: [(explicitlyTyped includes: var) not
  		 and: [(#(<= < >= >) includes: node selector)
  		 and: [node args first isConstant
  		 and: [node args first value = 0
  		 and: [(type := self typeFor: var in: aCodeGen) notNil
+ 		 and: [type first == $u]]]]]]]) ifTrue:
- 		 and: [type first == $u]]]]]]) ifTrue:
  			[declarations at: var put: (declarations at: var) allButFirst].
  		"if an assignment of a known send, set the variable's type to the return type of the send."
  		(node isAssignment
  		 and: [(locals includes: (var := node variable name))
  		 and: [(declarations includesKey: var) not
  		 and: [node expression isSend
  		 and: [(m := aCodeGen methodNamed: node expression selector) notNil]]]]) ifTrue:
  			[(#(sqInt void nil) includes: m returnType) ifFalse:
  				["the $: is to map things like unsigned field : 3 to usqInt"
  				 declarations
  					at: var
  					put: ((m returnType includes: $:) ifTrue: [#usqInt] ifFalse: [m returnType]), ' ', var]]]!

Item was added:
+ ----- Method: VMBasicConstants class>>mostBasicConstantNames (in category 'accessing') -----
+ mostBasicConstantNames
+ 	^#(BaseHeaderSize BytesPerWord BytesPerOop)!

Item was changed:
  ----- Method: VMClass class>>writeVMHeaderTo:bytesPerWord: (in category 'translation') -----
  writeVMHeaderTo: aStream bytesPerWord: bytesPerWord
  	"Generate the contents of interp.h on aStream.  Specific Interpreter subclasses
  	 override to add more stuff."
  	aStream
  		nextPutAll: '#define VM_PROXY_MAJOR '; print: self vmProxyMajorVersion; cr;
  		nextPutAll: '#define VM_PROXY_MINOR '; print: self vmProxyMinorVersion; cr;
  		cr;
  		nextPutAll: '#define SQ_VI_BYTES_PER_WORD '; print: bytesPerWord; cr;
  		cr.
+ 
+ 	"The most basic constants must be defined here, not in e.g. the plugin sources, so allow those
+ 	 other sources to be shared between different builds (Spur vs SqueakV3, 32-bit vs 64-bit, etc)"
+ 	VMBasicConstants mostBasicConstantNames do:
+ 		[:const|
+ 		aStream nextPutAll: '#define '; nextPutAll: const; space; print: (VMBasicConstants classPool at: const); cr].
+ 	aStream cr.
+ 
  	((VMBasicConstants classPool associations select: [:a| a key beginsWith: 'PrimErr'])
  		asSortedCollection: [:a1 :a2| a1 value <= a2 value])
  		do: [:a|
  			aStream nextPutAll: '#define '; nextPutAll: a key; space; print: a value; cr].
  	aStream cr!



More information about the Vm-dev mailing list