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

commits at source.squeak.org commits at source.squeak.org
Thu Oct 10 03:14:33 UTC 2013


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

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

Name: VMMaker.oscog-eem.447
Author: eem
Time: 9 October 2013, 8:11:44.69 pm
UUID: 044e4325-2db5-46a4-9a8d-a762ec8e004c
Ancestors: VMMaker.oscog-eem.446

Refactor sends of setEndOfMemory: & setMemoryStart: from image
read/open (real vs simulated) into setHeapBase:memoryLimit:endOfMemory:
and reverseBytesInImage
so that Spur can initialize itself coherently.

Tweak writeImageFileIO to use sq:Image:File:Write: instead of cCode
string, and fix use of timesRepeat (Slang doesn't handle this cuz
too hard to add the iteration variable).

Refactor scavenger initalization for standard simulator launch.
Replace 2 & 7 with meaningful message names.

Rescue generation of both Stack and Cog VMs:
isPotentialCCaseLabel needs to be cleverer.
Filter-out isNonArgumentImplicitReceiverVariableName: inst vars
in addClass:.
Avoid complaining about subclassResponsibilities as conflicts.
Add subclassResponsibility as a meta error to CCodeGenerator.
Fix CoInterpreter>>addNewMethodToCache: to have same arg name
as StackInterpreter's method.
Implement CoInterpreter>>followForwardedFrameContents:stackPointer:.
genInnerPrimitiveNew* are now subclass responsibilities of 
CogObjectRepresentation.
Tidy up objectMemoryClass & objectRepresentationClass (move to
class side, with imnstance side methods in VMClass).
Fix SimpleStackbasedCogit>>ancilliaryClasses.
Add ObjectMemory>>followForwarded*:
Mark format constants <api>.
Add #Spur to initializationOptions in VMClass class>>initializeMiscConstants.
Fix printTypedefOn: for alignment using BaseHeaderSize.

64-bit method surrogates regenerated as side-effect of generating VMs.

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

Item was changed:
  ----- Method: BlockNode>>isPotentialCCaseLabel (in category '*VMMaker-C translation') -----
  isPotentialCCaseLabel
  	| stmt |
+ 	statements size ~= 1 ifTrue: [^false].
+ 	stmt := statements first.
+ 	^self isPotentialCCaseLabel: stmt!
- 	^statements size = 1
- 	  and: [(stmt := statements first) isVariableNode
- 		or: [(stmt isLiteralNode
- 				and: [stmt isConstantNumber or: [stmt literalValue isSymbol]])
- 		or: [stmt isMessageNode
- 			and: [stmt selector key = #asSymbol
- 			and: [stmt receiver isLiteralNode
- 			and: [stmt receiver literalValue isSymbol]]]]]]!

Item was added:
+ ----- Method: BlockNode>>isPotentialCCaseLabel: (in category '*VMMaker-C translation') -----
+ isPotentialCCaseLabel: stmt
+ 	(stmt isVariableNode
+ 	 or: [stmt isLiteralNode
+ 		and: [stmt isConstantNumber or: [stmt literalValue isSymbol]]]) ifTrue:
+ 		[^true].
+ 	stmt isMessageNode ifTrue:
+ 		[(#(* + -) includes: stmt selector key) ifTrue:
+ 			[^(self isPotentialCCaseLabel: stmt receiver)
+ 			   and: [self isPotentialCCaseLabel: stmt arguments first]].
+ 		  ^stmt selector key = #asSymbol
+ 		  and: [stmt receiver isLiteralNode
+ 		  and: [stmt receiver literalValue isSymbol]]].
+ 	^false!

Item was changed:
  ----- Method: CCodeGenerator>>addClass: (in category 'public') -----
  addClass: aClass
  	"Add the variables and methods of the given class to the code base."
  
  	aClass prepareToBeAddedToCodeGenerator: self.
  	self checkClassForNameConflicts: aClass.
  	self addClassVarsFor: aClass.
  	"ikp..."
  	self addPoolVarsFor: aClass.
  	(aClass inheritsFrom: VMStructType) ifFalse:
+ 		[variables addAll: (vmClass
+ 							ifNil: [aClass instVarNames]
+ 							ifNotNil: [aClass instVarNames reject:
+ 										[:ivn| vmClass isNonArgumentImplicitReceiverVariableName: ivn]])].
- 		[variables addAll: aClass instVarNames].
  	self retainMethods: (aClass requiredMethodNames: self options).
  	
  	'Adding Class ' , aClass name , '...'
  		displayProgressAt: Sensor cursorPoint
  		from: 0
  		to: aClass selectors size
  		during:
  			[:bar |
  			 aClass selectors doWithIndex:
  				[:sel :i | | source |
  				bar value: i.
  				self addMethodFor: aClass selector: sel]].
  	aClass declareCVarsIn: self!

Item was changed:
  ----- Method: CCodeGenerator>>addMethod: (in category 'utilities') -----
  addMethod: aTMethod
  	"Add the given method to the code base and answer it.
  	 Only allow duplicate definitions for struct accessors, since we don't actually
  	 generate code for these methods and hence the conflict doesn't matter."
  
+ 	(methods at: aTMethod selector ifAbsent: []) ifNotNil:
- 	(methods at:  aTMethod selector ifAbsent: []) ifNotNil:
  		[:conflict |
+ 		aTMethod compiledMethod isSubclassResponsibility ifTrue:
+ 			[^nil].
  		(conflict isStructAccessor
  		 and: [aTMethod isStructAccessor
  		 and: [conflict compiledMethod decompileString = aTMethod compiledMethod decompileString]]) ifTrue:
  			[^nil].
  		self error: 'Method name conflict: ', aTMethod selector].
  	^methods at: aTMethod selector put: aTMethod!

Item was changed:
  ----- Method: CCodeGenerator>>addMethodFor:selector: (in category 'utilities') -----
  addMethodFor: aClass selector: selector
  	"Add the given method to the code base and answer its translation
  	 or nil if it shouldn't be translated."
  
  	| method tmethod |
  	method := aClass compiledMethodAt: selector.
  	(method pragmaAt: #doNotGenerate) ifNotNil:
  		[^nil].
  	"process optional methods by interpreting the argument to the option: pragma as either
  	 a Cogit class name or a class variable name or a variable name in VMBasicConstants."
  	(method pragmaAt: #option:) ifNotNil:
+ 		[:pragma| | key vmMaker |
- 		[:pragma| | key |
  		key := pragma argumentAt: 1.
+ 		vmMaker := VMClass getVMMaker.
  		((Cogit withAllSubclasses anySatisfy: [:c| c name = key])
+ 		and: [vmMaker cogitClassName ~= key]) ifTrue:
- 		and: [VMClass getVMMaker cogitClassName ~= key]) ifTrue:
  			[^nil].
  		(aClass bindingOf: key) ifNotNil:
  			[:binding|
  			binding value == false ifTrue: [^nil]].
  		(VMBasicConstants bindingOf: key) ifNotNil:
  			[:binding|
+ 			binding value == false ifTrue: [^nil]].
+ 		(vmMaker options at: key ifAbsent: []) ifNotNil:
+ 			[:option| option == false ifTrue: [^nil]]].
- 			binding value == false ifTrue: [^nil]]].
  	tmethod := self addMethod: (self compileToTMethodSelector: selector in: aClass).
  	"If the method has a macro then add the macro.  But keep the method
  	 for analysis purposes (e.g. its variable accesses)."
  	(method pragmaAt: #cmacro:) ifNotNil:
  		[:pragma|
  		self addMacro: (pragma argumentAt: 1) for: selector.
  		tmethod inline: false].
  	(method propertyValueAt: #cmacro:) ifNotNil:
  		[:macro|
  		self addMacro: macro for: selector.
  		tmethod inline: false].
  	^tmethod!

Item was changed:
  ----- Method: CCodeGenerator>>checkClassForNameConflicts: (in category 'error notification') -----
  checkClassForNameConflicts: aClass
  	"Verify that the given class does not have constant, variable, or method names that conflict with
  	 those of previously added classes. Raise an error if a conflict is found, otherwise just return."
  
  	"check for constant name collisions in class pools"
  	aClass classPool associationsDo:
  		[:assoc |
  		(constants includesKey: assoc key asString) ifTrue:
  			[self error: 'Constant ', assoc key, ' was defined in a previously added class']].
  
  	"and in shared pools"
  	(aClass sharedPools reject: [:pool| pools includes: pool]) do:
  		[:pool |
  		pool bindingsDo:
  			[:assoc |
  			(constants includesKey: assoc key asString) ifTrue:
  				[self error: 'Constant ', assoc key, ' was defined in a previously added class']]].
  
  	"check for instance variable name collisions"
  	(aClass inheritsFrom: VMStructType) ifFalse:
  		[aClass instVarNames do:
  			[:varName |
  			(variables includes: varName) ifTrue:
  				[self error: 'Instance variable ', varName, ' was defined in a previously added class']]].
  
  	"check for method name collisions"
  	aClass selectors do:
+ 		[:sel | | meth |
- 		[:sel |
  		((methods includesKey: sel)
  		and: [(aClass isStructClass and: [(aClass isAccessor: sel)
  				and: [(methods at: sel) isStructAccessor]]) not
+ 		and: [((meth := aClass compiledMethodAt: sel) pragmaAt: #doNotGenerate) isNil
+ 		and: [meth isSubclassResponsibility not]]]) ifTrue:
- 		and: [((aClass compiledMethodAt: sel) pragmaAt: #doNotGenerate) isNil]]) ifTrue:
  			[self error: 'Method ', sel, ' was defined in a previously added class.']]!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert32:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asLong					#generateAsLong:on:indent:
  	#asUnsignedLong			#generateAsUnsignedLong:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#flag:						#generateFlag:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
  	#bytesPerWord 			#generateBytesPerWord:on:indent:
  	#wordSize		 			#generateBytesPerWord:on:indent:
  	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
  	
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
  
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
+ 	#subclassResponsibility			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  ----- Method: CoInterpreter>>addNewMethodToCache: (in category 'method lookup cache') -----
+ addNewMethodToCache: classObj
- addNewMethodToCache: class
  	"Override to refuse to cache other than compiled methods.
  	 This protects open PICs against having to test for compiled methods."
  	(objectMemory isOopCompiledMethod: newMethod) ifFalse:
  		[primitiveFunctionPointer := #primitiveInvokeObjectAsMethod.
  		^self].
+ 	super addNewMethodToCache: classObj!
- 	super addNewMethodToCache: class!

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

Item was added:
+ ----- Method: CoInterpreter>>followForwardedFrameContents:stackPointer: (in category 'lazy become') -----
+ followForwardedFrameContents: theFP stackPointer: theSP
+ 	"follow pointers in the current stack frame up to theSP."
+ 	<var: #theFP type: #'char *'>
+ 	<var: #theSP type: #'char *'>
+ 	theFP + (self frameStackedReceiverOffset: theFP)
+ 		to: theFP + FoxCallerSavedIP + BytesPerWord
+ 		by: BytesPerWord
+ 		do: [:ptr| | oop |
+ 			oop := stackPages longAt: ptr.
+ 			((objectMemory isNonImmediate: oop)
+ 			 and: [objectMemory isForwarded: oop]) ifTrue:
+ 				[stackPages longAt: ptr put: (objectMemory followForwarded: oop)]].
+ 	theSP
+ 		to: (self frameReceiverOffset: theFP)
+ 		by: BytesPerWord
+ 		do: [:ptr| | oop |
+ 			oop := stackPages longAt: ptr.
+ 			((objectMemory isNonImmediate: oop)
+ 			 and: [objectMemory isForwarded: oop]) ifTrue:
+ 				[stackPages longAt: ptr put: (objectMemory followForwarded: oop)]].
+ 	self assert: (objectMemory isForwarded: (self frameMethod: theFP)) not.
+ 	(self frameHasContext: theFP) ifTrue:
+ 		[self assert: (objectMemory isForwarded: (self frameContext: theFP)) not]!

Item was changed:
  ----- Method: CoInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating the given amount of memory to its object heap. Fail if the image has an unknown format or requires more than the given amount of memory."
  	"Details: This method detects when the image was stored on a machine with the opposite byte ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header information to start 512 bytes into the file, since some file transfer programs for the Macintosh apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix area could also be used to store an exec command on Unix systems, allowing one to launch Smalltalk by invoking the image name as a command."
  	"This code is based on C code by Ian Piumarta and Smalltalk code by Tim Rowledge. Many thanks to both of you!!!!"
  
  	| swapBytes headerStart headerSize dataSize oldBaseAddr
  	  minimumMemory heapSize bytesRead bytesToShift
  	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize |
  	<var: #f type: 'sqImageFile '>
  	<var: #memStart type: 'usqInt'>
  	<var: #desiredHeapSize type: 'usqInt'>
  	<var: #headerStart type: 'squeakFileOffsetType '>
  	<var: #dataSize type: 'size_t '>
  	<var: #imageOffset type: 'squeakFileOffsetType '>
  
  	metaclassSizeBits := 6 * BytesPerWord.	"guess (Metaclass instSize * BPW)"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - BytesPerWord.  "record header start position"
  
  	headerSize			:= self getLongFromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags			:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory		:= self getLongFromFile: f swap: swapBytes. "N.B.  not used."
  	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.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"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]].
  	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].
  
  	"compare memory requirements with availability"
  	minimumMemory := cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ objectMemory edenBytes
  						+ self interpreterAllocationReserveBytes.
  	heapSize             :=  cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ desiredHeapSize
  						"+ edenBytes" "don't include edenBytes; this is part of the heap and so part of desiredHeapSize"
  						+ self interpreterAllocationReserveBytes.
  	heapSize < minimumMemory ifTrue:
  		[self insufficientMemorySpecifiedError].
  
  	"allocate a contiguous block of memory for the Squeak heap and ancilliary data structures"
  	"N.B. If the platform needs to it will redefine this macro to make heapSize
  	 an in/out parameter and assign the ammount actually allocated into heapSize.
  	 See e.g. platforms/Mac OS/vm/sqPlatformSpecific.h.  (I *hate* this. eem 7/23/2009)"
  	"objectMemory memory: (self cCode: 'sqAllocateMemory(minimumMemory, heapSize)').  "
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
+ 								headerSize: headerSize) asUnsignedInteger.
- 								headerSize: headerSize) asUnsignedInteger.	
  	
  	objectMemory memory = nil ifTrue: [self insufficientMemoryAvailableError].
  	heapBase := objectMemory memory + cogCodeSize.
  	self assert: objectMemory startOfMemory = heapBase.
+ 	objectMemory
+ 		setHeapBase: heapBase
+ 		memoryLimit: objectMemory memory + heapSize - 24  "decrease memoryLimit a tad for safety (?!!?!!? eem eem 10/9/2013 15:15)"
+ 		endOfMemory: heapBase + dataSize.
- 	objectMemory setMemoryLimit: objectMemory memory + heapSize - 24.  "decrease memoryLimit a tad for safety"
- 	objectMemory setEndOfMemory: heapBase + dataSize.
  
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := self cCode: 'sqImageFileRead(pointerForOop(heapBase), sizeof(unsigned char), dataSize, f)'.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := heapBase - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  	self initializeCodeGenerator.
  	^dataSize!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
+ 	^4 + self baseHeaderSize!
- 	^12!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmNumArgs (in category 'accessing') -----
  cmNumArgs
+ 	^memory unsignedByteAt: address + 1 + baseHeaderSize!
- 	^memory unsignedByteAt: address + 9!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmNumArgs: (in category 'accessing') -----
  cmNumArgs: aValue
  	^memory
+ 		unsignedByteAt: address + baseHeaderSize + 1
- 		unsignedByteAt: address + 9
  		put: aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmRefersToYoung (in category 'accessing') -----
  cmRefersToYoung
+ 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -3) bitAnd: 16r1) ~= 0!
- 	^(((memory unsignedByteAt: address + 10) bitShift: -3) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmRefersToYoung: (in category 'accessing') -----
  cmRefersToYoung: aValue
  	memory
+ 		unsignedByteAt: address + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rF7) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 3)).
- 		unsignedByteAt: address + 10
- 		put: (((memory unsignedByteAt: address + 10) bitAnd: 16rF7) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 3)).
  	^aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmType (in category 'accessing') -----
  cmType
+ 	^(memory unsignedByteAt: address + 2 + baseHeaderSize) bitAnd: 16r7!
- 	^(memory unsignedByteAt: address + 10) bitAnd: 16r7!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmType: (in category 'accessing') -----
  cmType: aValue
  	self assert: (aValue between: 0 and: 16r7).
  	memory
+ 		unsignedByteAt: address + baseHeaderSize + 2
+ 		put: ((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rF8) + aValue.
- 		unsignedByteAt: address + 10
- 		put: ((memory unsignedByteAt: address + 10) bitAnd: 16rF8) + aValue.
  	^aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmUsageCount (in category 'accessing') -----
  cmUsageCount
+ 	^((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -5) bitAnd: 16r7!
- 	^((memory unsignedByteAt: address + 10) bitShift: -5) bitAnd: 16r7!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmUsageCount: (in category 'accessing') -----
  cmUsageCount: aValue
  	self assert: (aValue between: 0 and: 16r7).
  	memory
+ 		unsignedByteAt: address + baseHeaderSize + 2
+ 		put: ((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16r1F) + (aValue bitShift: 5).
- 		unsignedByteAt: address + 10
- 		put: ((memory unsignedByteAt: address + 10) bitAnd: 16r1F) + (aValue bitShift: 5).
  	^aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmUsesPenultimateLit (in category 'accessing') -----
  cmUsesPenultimateLit
+ 	^((memory unsignedByteAt: address + 3 + baseHeaderSize) bitAnd: 16r1) ~= 0!
- 	^((memory unsignedByteAt: address + 11) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cmUsesPenultimateLit: (in category 'accessing') -----
  cmUsesPenultimateLit: aValue
  	memory
+ 		unsignedByteAt: address + baseHeaderSize + 3
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 3) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
- 		unsignedByteAt: address + 11
- 		put: (((memory unsignedByteAt: address + 11) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
  	^aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cpicHasMNUCase (in category 'accessing') -----
  cpicHasMNUCase
+ 	^(((memory unsignedByteAt: address + 2 + baseHeaderSize) bitShift: -4) bitAnd: 16r1) ~= 0!
- 	^(((memory unsignedByteAt: address + 10) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>cpicHasMNUCase: (in category 'accessing') -----
  cpicHasMNUCase: aValue
  	memory
+ 		unsignedByteAt: address + baseHeaderSize + 2
+ 		put: (((memory unsignedByteAt: address + baseHeaderSize + 2) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
- 		unsignedByteAt: address + 10
- 		put: (((memory unsignedByteAt: address + 10) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
  	^aValue!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>padToWord (in category 'accessing') -----
+ padToWord
+ 	^memory unsignedLongLongAt: address + 5!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>padToWord: (in category 'accessing') -----
+ padToWord: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 5
+ 		put: aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>stackCheckOffset (in category 'accessing') -----
  stackCheckOffset
+ 	^((memory unsignedShortAt: address + 3 + baseHeaderSize) bitShift: -4) bitAnd: 16rFFF!
- 	^((memory unsignedShortAt: address + 11) bitShift: -4) bitAnd: 16rFFF!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>stackCheckOffset: (in category 'accessing') -----
  stackCheckOffset: aValue
  	self assert: (aValue between: 0 and: 16rFFF).
  	memory
+ 		unsignedShortAt: address + baseHeaderSize + 3
+ 		put: ((memory unsignedShortAt: address + baseHeaderSize + 3) bitAnd: 16rF) + (aValue bitShift: 4).
- 		unsignedShortAt: address + 11
- 		put: ((memory unsignedShortAt: address + 11) bitAnd: 16rF) + (aValue bitShift: 4).
  	^aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
+ 	^32 + self baseHeaderSize!
- 	^40!

Item was changed:
  ----- Method: CogMethodSurrogate64>>blockEntryOffset (in category 'accessing') -----
  blockEntryOffset
+ 	^memory unsignedShortAt: address + 7 + baseHeaderSize!
- 	^memory unsignedShortAt: address + 15!

Item was changed:
  ----- Method: CogMethodSurrogate64>>blockEntryOffset: (in category 'accessing') -----
  blockEntryOffset: aValue
  	^memory
+ 		unsignedShortAt: address + baseHeaderSize + 7
- 		unsignedShortAt: address + 15
  		put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>blockSize (in category 'accessing') -----
  blockSize
+ 	^memory unsignedShortAt: address + 5 + baseHeaderSize!
- 	^memory unsignedShortAt: address + 13!

Item was changed:
  ----- Method: CogMethodSurrogate64>>blockSize: (in category 'accessing') -----
  blockSize: aValue
  	^memory
+ 		unsignedShortAt: address + baseHeaderSize + 5
- 		unsignedShortAt: address + 13
  		put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>methodHeader (in category 'accessing') -----
  methodHeader
+ 	^memory unsignedLongLongAt: address + 17 + baseHeaderSize!
- 	^memory unsignedLongLongAt: address + 25!

Item was changed:
  ----- Method: CogMethodSurrogate64>>methodHeader: (in category 'accessing') -----
  methodHeader: aValue
  	^memory
+ 		unsignedLongLongAt: address + baseHeaderSize + 17
- 		unsignedLongLongAt: address + 25
  		put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>methodObject (in category 'accessing') -----
  methodObject
+ 	^memory unsignedLongLongAt: address + 9 + baseHeaderSize!
- 	^memory unsignedLongLongAt: address + 17!

Item was changed:
  ----- Method: CogMethodSurrogate64>>methodObject: (in category 'accessing') -----
  methodObject: aValue
  	^memory
+ 		unsignedLongLongAt: address + baseHeaderSize + 9
- 		unsignedLongLongAt: address + 17
  		put: aValue!

Item was changed:
  ----- Method: CogMethodSurrogate64>>selector (in category 'accessing') -----
  selector
+ 	^memory unsignedLongLongAt: address + 25 + baseHeaderSize!
- 	^memory unsignedLongLongAt: address + 33!

Item was changed:
  ----- Method: CogMethodSurrogate64>>selector: (in category 'accessing') -----
  selector: aValue
  	^memory
+ 		unsignedLongLongAt: address + baseHeaderSize + 25
- 		unsignedLongLongAt: address + 33
  		put: aValue!

Item was added:
+ ----- Method: CogObjectRepresentation>>genInnerPrimitiveNew: (in category 'primitive generators') -----
+ genInnerPrimitiveNew: retNoffset
+ 	self subclassResponsibility.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentation>>genInnerPrimitiveNewMethod: (in category 'primitive generators') -----
+ genInnerPrimitiveNewMethod: retNoffset
+ 	self subclassResponsibility.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentation>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
+ genInnerPrimitiveNewWithArg: retNoffset
+ 	self subclassResponsibility.
+ 	^0!

Item was removed:
- ----- Method: CogVMSimulator>>cogCodeSize (in category 'simulation only') -----
- cogCodeSize
- 	^cogCodeSize!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
+ 	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
- 	"InterpreterSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize count heapSize oldBaseAddr bytesToShift swapBytes hdrNumStackPages
  	 hdrEdenBytes hdrCogCodeSize stackZoneSize methodCacheSize headerFlags primTraceLogSize |
  	"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 nextLongFrom: f swap: swapBytes.
+ 	heapSize := self nextLongFrom: f swap: swapBytes.  "length of heap in file"
- 	heapSize := self nextLongFrom: f swap: swapBytes.  "first unused location in heap"
  	oldBaseAddr := self nextLongFrom: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self nextLongFrom: f swap: swapBytes).
  	objectMemory lastHash: (self nextLongFrom: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self nextLongFrom: f swap: swapBytes.
  	headerFlags			:= self nextLongFrom: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory		:= self nextLongFrom: f swap: swapBytes.
  	hdrNumStackPages	:= self nextShortFrom: 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.
  	hdrEdenBytes	:= self nextLongFrom: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	"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 := cogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize.
+ 	objectMemory
+ 		setHeapBase: heapBase
+ 		memoryLimit:  heapBase
- 	objectMemory setMemoryLimit:   heapBase
  						+ heapSize
  						+ objectMemory edenBytes
  						+ self interpreterAllocationReserveBytes
+ 						+ extraBytes
+ 		endOfMemory: heapBase + heapSize.
- 						+ extraBytes.
  
  	objectMemory initialize.
  	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 := f readInto: objectMemory memory startingAt: heapBase // 4 + 1 count: heapSize // 4.
  	count ~= (heapSize // 4) ifTrue: [self halt].
  	]
  		ensure: [f close].
- 	objectMemory setEndOfMemory: heapBase + heapSize.
  	self moveMethodCacheToMemoryAt: cogCodeSize + stackZoneSize.
  	self movePrimTraceLogToMemoryAt: cogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory startOfMemory - oldBaseAddr.  "adjust pointers for zero base address"
+ 	Utilities
+ 		informUser: 'Relocating object pointers...'
+ 		during: [self initializeInterpreter: bytesToShift].
- 	Utilities informUser: 'Relocating object pointers...'
- 				during: [self initializeInterpreter: bytesToShift].
  	self initializeCodeGenerator!

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

Item was changed:
  ----- Method: Cogit class>>initializeWithOptions: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionary
+ 	self withAllSubclasses,
+ 	CogMethod withAllSubclasses,
+ 	CogMethodSurrogate withAllSubclasses
+ 		do: [:class|
+ 			class initializationOptions: optionsDictionary].
- 	CogMethodSurrogate withAllSubclassesDo:
- 		[:cmsClass|
- 		cmsClass initializationOptions: optionsDictionary].
  	super initializeWithOptions: optionsDictionary.
  	self initializeMiscConstants. "must preceed other initialization."
  	self initializeErrorCodes.
  	self initializeCogMethodConstants.
  	self initializeAnnotationConstants.
  	self initializeBytecodeTable.
  	self initializePrimitiveTable!

Item was changed:
  ----- Method: Cogit>>blockAlignment (in category 'accessing') -----
  blockAlignment
  	"Block method headers must be aligned on the correct boundary, just like non-block method headers.
  	 This is because the CoInterpreter encodes flags in the least significant three bits of the method field."
+ 	<api>
  	<cmacro: '(self) 8'>
  	self assert: (methodZone roundUpLength: 1) = 8.
  	^8!

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

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

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

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade class>>objectRepresentationClass (in category 'accessing') -----
+ objectRepresentationClass
+ 	^self subclassResponsibility!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>objectRepresentationClass (in category 'accessing') -----
- objectRepresentationClass
- 	^self subclassResponsibility!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSqueakV3ObjectRepresentation class>>objectRepresentationClass (in category 'accessing') -----
+ objectRepresentationClass
+ 	^CogObjectRepresentationForSqueakV3!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacadeForSqueakV3ObjectRepresentation>>objectRepresentationClass (in category 'accessing') -----
- objectRepresentationClass
- 	^CogObjectRepresentationForSqueakV3!

Item was added:
+ ----- Method: LittleEndianBitmap>>longLongAt:put: (in category 'accessing') -----
+ longLongAt: byteAddress put: a64BitValue
+ 	byteAddress - 1 \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
+ 	self
+ 		longAt: byteAddress put: (a64BitValue bitAnd: 16rffffffff);
+ 		longAt: byteAddress + 4 put: a64BitValue >> 32.
+ 	^a64BitValue!

Item was added:
+ ----- Method: NewCoObjectMemory class>>objectRepresentationClass (in category 'accessing class hierarchy') -----
+ objectRepresentationClass
+ 	^CogObjectRepresentationForSqueakV3!

Item was removed:
- ----- Method: NewObjectMemory>>objectRepresentationClass (in category 'cog jit support') -----
- objectRepresentationClass
- 	<doNotGenerate>
- 	^CogObjectRepresentationForSqueakV3!

Item was added:
+ ----- Method: NewObjectMemory>>reverseBytesInMemory (in category 'snapshot') -----
+ reverseBytesInMemory
+ 	self reverseBytesFrom: self startOfMemory to: freeStart!

Item was added:
+ ----- Method: ObjectMemory class>>objectRepresentationClass (in category 'accessing class hierarchy') -----
+ objectRepresentationClass
+ 	^self subclassResponsibility!

Item was changed:
+ ----- Method: ObjectMemory>>arrayFormat (in category 'header formats') -----
- ----- Method: ObjectMemory>>arrayFormat (in category 'header access') -----
  arrayFormat
+ 	<api>
  	^2!

Item was changed:
+ ----- Method: ObjectMemory>>firstByteFormat (in category 'header formats') -----
- ----- Method: ObjectMemory>>firstByteFormat (in category 'header access') -----
  firstByteFormat
+ 	<api>
  	^8!

Item was changed:
+ ----- Method: ObjectMemory>>firstCompiledMethodFormat (in category 'header formats') -----
- ----- Method: ObjectMemory>>firstCompiledMethodFormat (in category 'header access') -----
  firstCompiledMethodFormat
+ 	<api>
  	^12!

Item was changed:
+ ----- Method: ObjectMemory>>firstLongFormat (in category 'header formats') -----
- ----- Method: ObjectMemory>>firstLongFormat (in category 'header access') -----
  firstLongFormat
+ 	<api>
  	^6!

Item was changed:
+ ----- Method: ObjectMemory>>firstStringyFakeFormat (in category 'header formats') -----
- ----- Method: ObjectMemory>>firstStringyFakeFormat (in category 'header access') -----
  firstStringyFakeFormat
  	"A fake format for the interpreter used to mark indexable strings in
  	 the interpreter's at cache.  This is larger than any format."
  	^16!

Item was added:
+ ----- Method: ObjectMemory>>followForwarded: (in category 'spur compatibility') -----
+ followForwarded: objOop
+ 	<inline: false>
+ 	self shouldNotImplement.
+ 	^0!

Item was added:
+ ----- Method: ObjectMemory>>followForwardedObjectFields:toDepth: (in category 'spur compatibility') -----
+ followForwardedObjectFields: objOop toDepth: depth
+ 	self shouldNotImplement!

Item was changed:
+ ----- Method: ObjectMemory>>indexablePointersFormat (in category 'header formats') -----
- ----- Method: ObjectMemory>>indexablePointersFormat (in category 'header access') -----
  indexablePointersFormat
+ 	<api>
  	^3!

Item was added:
+ ----- Method: ObjectMemory>>setHeapBase:memoryLimit:endOfMemory: (in category 'initialization') -----
+ setHeapBase: ignored memoryLimit: memLimit endOfMemory: memEnd
+ 	self setMemoryLimit: memLimit.
+ 	self setEndOfMemory: memEnd!

Item was changed:
+ ----- Method: ObjectMemory>>weakArrayFormat (in category 'header formats') -----
- ----- Method: ObjectMemory>>weakArrayFormat (in category 'header access') -----
  weakArrayFormat
+ 	<api>
  	^4!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
+ 	initializationOptions ifNil:
+ 		[initializationOptions := options].
+ 	^(super ancilliaryClasses: options), (self objectRepresentationClass withAllSuperclasses copyUpThrough: CogObjectRepresentation)!
- 	"hard-wired for now"
- 	^(super ancilliaryClasses: options), { CogObjectRepresentationForSqueakV3 }!

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

Item was added:
+ ----- Method: Spur32BitCoMemoryManager class>>objectRepresentationClass (in category 'accessing class hierarchy') -----
+ objectRepresentationClass
+ 	^CogObjectRepresentationFor32BitSpur!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>edenBytes (in category 'accessing') -----
+ edenBytes
+ 	"during snapshot load newSpaceLimit holds newSpace size + cogCodeSize temporarily."
+ 	scavenger eden limit ifNil:
+ 		[| newSpaceBytes |
+ 		 newSpaceBytes := newSpaceLimit - coInterpreter cogCodeSize - coInterpreter interpreterAllocationReserveBytes.
+ 		 ^newSpaceBytes * self scavengerDenominator - self numSurvivorSpaces // self scavengerDenominator
+ 			roundTo: self allocationUnit].
+ 	"once initialized we can query the actual beast."
+ 	^scavenger eden limit - scavenger eden start!

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

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>vmEndianness (in category 'memory access') -----
+ vmEndianness
+ 	"1 = big, 0 = little"
+ 	^0!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>vmEndianness (in category 'memory access') -----
+ vmEndianness
+ 	"1 = big, 0 = little"
+ 	^0!

Item was removed:
- ----- Method: Spur32BitMemoryManager class>>objectRepresentationClass (in category 'accessing') -----
- objectRepresentationClass
- 	^CogObjectRepresentationFor32BitSpur!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>objectRepresentationClass (in category 'simulation') -----
- objectRepresentationClass
- 	^CogObjectRepresentationFor32BitSpur!

Item was removed:
- ----- Method: Spur64BitMemoryManager class>>objectRepresentationClass (in category 'accessing') -----
- objectRepresentationClass
- 	^CogObjectRepresentationFor64BitSpur!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>objectRepresentationClass (in category 'simulation') -----
- objectRepresentationClass
- 	^CogObjectRepresentationFor64BitSpur!

Item was changed:
  ----- Method: SpurGenerationScavenger>>initialize (in category 'initialization') -----
  initialize
+ 	pastSpace := SpurNewSpaceSpace new.
+ 	futureSpace := SpurNewSpaceSpace new.
+ 	eden := SpurNewSpaceSpace new.
  	rememberedSet := CArrayAccessor on: (Array new: RememberedSetLimit).
  	rememberedSetSize := 0.
  	tenuringThreshold := 0.
  	tenuringProportion := 0.9!

Item was changed:
  ----- Method: SpurGenerationScavenger>>manager:newSpaceStart:newSpaceBytes:edenBytes: (in category 'initialization') -----
  manager: aSpurMemoryManager newSpaceStart: startAddress newSpaceBytes: totalBytes edenBytes: requestedEdenBytes 
  	| edenBytes survivorBytes |
  	manager := aSpurMemoryManager.
  
  	edenBytes := requestedEdenBytes.
  	survivorBytes := totalBytes - edenBytes // 2 truncateTo: manager allocationUnit.
  	edenBytes := totalBytes - survivorBytes - survivorBytes truncateTo: manager allocationUnit.
  	self assert: totalBytes - edenBytes - survivorBytes - survivorBytes < manager allocationUnit.
  
  	"for tenuring we require older objects below younger objects.  since allocation
  	 grows up this means that the survivor spaces must preceed eden."
- 	pastSpace := SpurNewSpaceSpace new.
- 	futureSpace := SpurNewSpaceSpace new.
- 	eden := SpurNewSpaceSpace new.
  
  	pastSpace start: startAddress limit: startAddress + survivorBytes.
  	futureSpace start: pastSpace limit limit: pastSpace limit + survivorBytes.
  	eden start: futureSpace limit limit: futureSpace limit + edenBytes.
  
  	self assert: futureSpace limit <= (startAddress + totalBytes).
  	self assert: eden start \\ manager allocationUnit
  				+ (eden limit \\ manager allocationUnit) = 0.
  	self assert: pastSpace start \\ manager allocationUnit
  				+ (pastSpace limit \\ manager allocationUnit) = 0.
  	self assert: futureSpace start \\ manager allocationUnit
  				+ (futureSpace limit \\ manager allocationUnit) = 0.
  
  	self initFutureSpaceStart.
  	manager initSpaceForAllocationCheck: eden!

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>manager: (in category 'initialization') -----
+ manager: aSpurNBitMMXEndianSimulator
+ 	manager := aSpurNBitMMXEndianSimulator.
+ 	aSpurNBitMMXEndianSimulator coInterpreter ifNotNil:
+ 		[:coint| coInterpreter := coint]!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize:newSpaceSize:stackSize:codeSize: (in category 'simulation') -----
  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>
  	| endBridgeBytes |
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
  	endBridgeBytes := 2 * self baseHeaderSize.
  	memory := (self endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes + stackBytes + endBridgeBytes) // 4.
  	startOfMemory := codeBytes + stackBytes.
  	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + startOfMemory.
  	newSpaceLimit := newSpaceBytes + startOfMemory.
  	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
  	scavenger := SpurGenerationScavengerSimulator new
  					manager: self
  					newSpaceStart: startOfMemory
  					newSpaceBytes: newSpaceBytes
+ 					edenBytes: newSpaceBytes * self scavengerDenominator - self numSurvivorSpaces // self scavengerDenominator!
- 					edenBytes: newSpaceBytes * 5 // 7 "David's paper uses 140Kb eden + 2 x 28kb survivor spaces :-)"!

Item was changed:
  ----- Method: SpurMemoryManager>>arrayFormat (in category 'header formats') -----
  arrayFormat
+ 	<api>
  	^2!

Item was changed:
  ----- Method: SpurMemoryManager>>coInterpreter: (in category 'simulation') -----
  coInterpreter: aCoInterpreter
  	<doNotGenerate>
  	coInterpreter := aCoInterpreter.
+ 	scavenger ifNotNil:
+ 		[scavenger coInterpreter: aCoInterpreter]!
- 	scavenger coInterpreter: aCoInterpreter!

Item was added:
+ ----- Method: SpurMemoryManager>>defaultEdenBytes (in category 'snapshot') -----
+ defaultEdenBytes
+ 	^2 * 1024 * 1024
+ 	+ (coInterpreter interpreterAllocationReserveBytes
+ 	    * self scavengerDenominator + self numSurvivorSpaces // self scavengerDenominator)!

Item was changed:
  ----- Method: SpurMemoryManager>>edenBytes (in category 'accessing') -----
  edenBytes
+ 	"during snapshot load newSpaceLimit holds newSpace size temporarily."
+ 	scavenger eden limit ifNil:
+ 		[| newSpaceBytes |
+ 		 newSpaceBytes := newSpaceLimit - coInterpreter interpreterAllocationReserveBytes.
+ 		 ^newSpaceBytes * self scavengerDenominator - self numSurvivorSpaces // self scavengerDenominator
+ 			roundTo: self allocationUnit].
+ 	"once initialized we can query the actual beast."
  	^scavenger eden limit - scavenger eden start!

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

Item was changed:
  ----- Method: SpurMemoryManager>>firstByteFormat (in category 'header formats') -----
  firstByteFormat
+ 	<api>
  	^16!

Item was changed:
  ----- Method: SpurMemoryManager>>firstCompiledMethodFormat (in category 'header formats') -----
  firstCompiledMethodFormat
+ 	<api>
  	^24!

Item was changed:
  ----- Method: SpurMemoryManager>>firstLongFormat (in category 'header formats') -----
  firstLongFormat
+ 	<api>
  	^10!

Item was changed:
  ----- Method: SpurMemoryManager>>indexablePointersFormat (in category 'header formats') -----
  indexablePointersFormat
+ 	<api>
  	^3!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  	"We can put all initializations that set something to 0 or to false here.
  	 In C all global variables are initialized to 0, and 0 is false."
  	remapBuffer := Array new: RemapBufferSize.
  	remapBufferCount := 0.
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
  	needGCFlag := signalLowSpace := scavengeInProgress := false.
  	becomeEffectsFlags := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  
  	"we can initialize things that are virtual in C."
+ 	scavenger := SpurGenerationScavengerSimulator new manager: self; yourself.
  	segmentManager := SpurSegmentManager new manager: self; yourself.
  
  	"We can also initialize here anything that is only for simulation."
  	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new]!

Item was added:
+ ----- Method: SpurMemoryManager>>memoryLimit (in category 'snapshot') -----
+ memoryLimit
+ 	^endOfMemory!

Item was added:
+ ----- Method: SpurMemoryManager>>numSurvivorSpaces (in category 'scavenger') -----
+ numSurvivorSpaces
+ 	"there are two survivor spaces, futureSPace & pastSpace."
+ 	^2!

Item was added:
+ ----- Method: SpurMemoryManager>>scavengerDenominator (in category 'scavenger') -----
+ scavengerDenominator
+ 	"David's paper uses 140Kb eden + 2 x 28kb survivor spaces,
+ 	 which is 5 7ths for eden and 1 7th each for the survivor spaces.
+ 	 So express scavenger sizes in 7ths"
+ 	^7!

Item was added:
+ ----- Method: SpurMemoryManager>>vmEndianness (in category 'memory access') -----
+ vmEndianness
+ 	"1 = big, 0 = little"
+ 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>weakArrayFormat (in category 'header formats') -----
  weakArrayFormat
+ 	<api>
  	^4!

Item was changed:
  ----- Method: SpurSegmentManager>>writeSegment:toFile: (in category 'snapshot') -----
  writeSegment: aSpurSegmentInfo toFile: aBinaryStream
  	<var: 'aSpurSegmentInfo' type: 'SpurSegmentInfo *'>
+ 	<var: 'aBinaryStream' type: #'FILE *'>
- 	<var: 'aSpurSegmentInfo' type: #'FILE *'>
  	^self cCode:
  			[self
  				sq: aSpurSegmentInfo start
+ 				Image: 1
+ 				File: aSpurSegmentInfo segSize
- 				Image: aSpurSegmentInfo segSize
- 				File: 1
  				Write: aBinaryStream]
  		inSmalltalk:
  			[aBinaryStream
  				next: aSpurSegmentInfo segSize / 4
  				putAll: manager memory
  				startingAt: aSpurSegmentInfo start / 4 + 1.
  			 aSpurSegmentInfo segSize]!

Item was changed:
  ----- Method: StackInterpreter>>ensureImageFormatIsUpToDate: (in category 'image save/restore') -----
  ensureImageFormatIsUpToDate: swapBytes
+ 	"Ensure the image data has been updated to suit the current VM."
- 	"Ensure the image data has been updayed to suit the current VM."
  	<inline: false>
  	swapBytes
  		ifTrue: [self reverseBytesInImage]
  		ifFalse: [self convertFloatsToPlatformOrder]!

Item was changed:
  ----- Method: StackInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating the given amount of memory to its object heap. Fail if the image has an unknown format or requires more than the given amount of memory."
  	"Details: This method detects when the image was stored on a machine with the opposite byte ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header information to start 512 bytes into the file, since some file transfer programs for the Macintosh apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix area could also be used to store an exec command on Unix systems, allowing one to launch Smalltalk by invoking the image name as a command."
  	"This code is based on C code by Ian Piumarta and Smalltalk code by Tim Rowledge. Many thanks to both of you!!!!"
  
  	| swapBytes headerStart headerSize dataSize oldBaseAddr hdrNumStackPages
+ 	  minimumMemory heapBase bytesRead bytesToShift heapSize hdrEdenBytes
- 	  minimumMemory memStart bytesRead bytesToShift heapSize hdrEdenBytes
  	  headerFlags hdrMaxExtSemTabSize |
  	<var: #f type: 'sqImageFile '>
+ 	<var: #heapBase type: 'usqInt'>
- 	<var: #memStart type: 'usqInt'>
  	<var: #desiredHeapSize type: 'usqInt'>
  	<var: #headerStart type: 'squeakFileOffsetType '>
  	<var: #dataSize type: 'size_t '>
  	<var: #imageOffset type: 'squeakFileOffsetType '>
  
  	metaclassSizeBits := 6 * BytesPerWord.	"guess (Metaclass instSize * BPW)"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - BytesPerWord.  "record header start position"
  
  	headerSize			:= self getLongFromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	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.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to images run on Cog."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	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].
  	"decrease Squeak object heap to leave extra memory for the VM"
  	heapSize := self cCode: 'reserveExtraCHeapBytes(desiredHeapSize, extraVMMemory)'.
  
  	"compare memory requirements with availability".
  	minimumMemory := dataSize + objectMemory edenBytes + self interpreterAllocationReserveBytes.
  	heapSize < minimumMemory ifTrue:
  		[self insufficientMemorySpecifiedError].
  
  	"allocate a contiguous block of memory for the Squeak heap"
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
  								headerSize: headerSize) asUnsignedInteger.
  	objectMemory memory = nil ifTrue: [self insufficientMemoryAvailableError].
  
+ 	heapBase := objectMemory startOfMemory.
+ 	objectMemory
+ 		setHeapBase: heapBase
+ 		memoryLimit: (heapBase + heapSize) - 24  "decrease memoryLimit a tad for safety"
+ 		endOfMemory: heapBase + dataSize.
- 	memStart := objectMemory startOfMemory.
- 	objectMemory setMemoryLimit: (memStart + heapSize) - 24.  "decrease memoryLimit a tad for safety"
- 	objectMemory setEndOfMemory: memStart + dataSize.
  
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := self cCode: 'sqImageFileRead(pointerForOop(memory), sizeof(unsigned char), dataSize, f)'.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
+ 	bytesToShift := heapBase - oldBaseAddr.
- 	bytesToShift := memStart - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
+ 	^dataSize!
- 	^dataSize
- !

Item was changed:
  ----- Method: StackInterpreter>>reverseBytesInImage (in category 'image save/restore') -----
  reverseBytesInImage
  	"Byte-swap all words in memory after reading in the entire image file with bulk read. Contributed by Tim Rowledge."
  
  	"First, byte-swap every word in the image. This fixes objects headers."
+ 	objectMemory reverseBytesInMemory.
- 	objectMemory reverseBytesFrom: objectMemory startOfMemory to: objectMemory freeStart.
  
  	"Second, return the bytes of bytes-type objects to their
  	 orginal order, and perform any other format conversions."
  	self updateObjectsPostByteSwap!

Item was changed:
  ----- Method: StackInterpreter>>writeImageFileIO (in category 'image save/restore') -----
  writeImageFileIO
  
  	| headerStart headerSize f bytesWritten sCWIfn okToWrite |
  	<var: #f type: 'sqImageFile'>
  	<var: #headerStart type: 'squeakFileOffsetType '>
  	<var: #sCWIfn type: 'void *'>
  
  	"If the security plugin can be loaded, use it to check for write permission.
  	If not, assume it's ok"
  	sCWIfn := self ioLoadFunction: 'secCanWriteImage' From: 'SecurityPlugin'.
  	sCWIfn ~= 0 ifTrue:
  		[okToWrite := self cCode: '((sqInt (*)(void))sCWIfn)()'.
  		 okToWrite ifFalse:[^self primitiveFail]].
  	
  	"local constants"
  	headerStart := 0.  
  	headerSize := 64.  "header size in bytes; do not change!!"
  
  	f := self cCode: 'sqImageFileOpen(imageName, "wb")'.
  	f = nil ifTrue: "could not open the image file for writing"
  		[^self primitiveFail].
  
  	headerStart := self cCode: 'sqImageFileStartLocation(f,imageName,headerSize+imageBytes)'.
  	self cCode: '/* Note: on Unix systems one could put an exec command here, padded to 512 bytes */'.
  	"position file to start of header"
  	self sqImageFile: f Seek: headerStart.
  
  	self putLong: self imageFormatVersion toFile: f.
  	self putLong: headerSize toFile: f.
  	self putLong: objectMemory imageSizeToWrite toFile: f.
  	self putLong: objectMemory baseAddressOfImage toFile: f.
  	self putLong: objectMemory specialObjectsOop toFile: f.
  	self putLong: objectMemory newObjectHash toFile: f.
  	self putLong: self ioScreenSize toFile: f.
  	self putLong: self getImageHeaderFlags toFile: f.
  	self putLong: extraVMMemory toFile: f.
  	self putShort: desiredNumStackPages toFile: f.
  	self putShort: self unknownShortOrCodeSizeInKs toFile: f.
  	self putLong: desiredEdenBytes toFile: f.
  	self putShort: (maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]) toFile: f.
  	self putShort: 0 toFile: f.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[self putLong: objectMemory firstSegmentBytes toFile: f."Pad the rest of the header."
+ 			 1 to: 3 do: [:i| self putLong: 0 toFile: f]]
- 			 3 timesRepeat: [self putLong: 0 toFile: f]]
  		ifFalse:
+ 			[1 to: 4 do: [:i| self putLong: 0 toFile: f]].  "fill remaining header words with zeros"
- 			[1 to: 4 do: [:i | self putLong: 0 toFile: f]].  "fill remaining header words with zeros"
  	self successful ifFalse: [
  		"file write or seek failure"
  		self cCode: 'sqImageFileClose(f)'.
  		^ nil].
  
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"write the image data"
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[bytesWritten := objectMemory segmentManager writeImageToFile: f]
  		ifFalse:
  			[| memStart |
  			memStart := objectMemory baseAddressOfImage.
+ 			bytesWritten := self sq: (self pointerForOop: memStart)
+ 								Image: (self sizeof: #char)
+ 								File: objectMemory imageSizeToWrite
+ 								Write: f.
- 			bytesWritten := self cCode: 'sqImageFileWrite(pointerForOop(memStart), sizeof(unsigned char), imageBytes, f)'.
  	self touch: memStart].
  	self success: bytesWritten = objectMemory imageSizeToWrite.
  	self cCode: 'sqImageFileClose(f)'
  !

Item was changed:
  ----- Method: StackInterpreterSimulator class>>initializeWithOptions:objectMemoryClass: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionaryOrArray objectMemoryClass: objectMemoryClassOrNil
  	"The relevant ObjectMemory and Interpreter classes must be initialized in order.
  	 This happens notionally every time we start the simulator,
  	 but in fact happens when ever we instantiate a simulator."
+ 	initializationOptions := optionsDictionaryOrArray isArray
- 	| optionsDictionary |
- 	optionsDictionary := optionsDictionaryOrArray isArray
  							ifTrue: [Dictionary newFromPairs: optionsDictionaryOrArray]
  							ifFalse: [optionsDictionaryOrArray].
  	(objectMemoryClassOrNil ifNil: [self objectMemoryClass])
+ 		initializeWithOptions: initializationOptions.
- 		initializeWithOptions: optionsDictionary.
  
+ 	self initializeWithOptions: initializationOptions!
- 	StackInterpreter initializeWithOptions: optionsDictionary!

Item was changed:
  ----- Method: StackInterpreterSimulator class>>onObjectMemory:options: (in category 'instance creation') -----
  onObjectMemory: anObjectMemory options: optionsDictionaryOrArray
+ 	| simulatorClass |
  	^self == StackInterpreterSimulator
  		ifTrue:
+ 			[simulatorClass := SmalltalkImage current endianness == #big
+ 								ifTrue: [self notYetImplemented"StackInterpreterSimulatorMSB"]
+ 								ifFalse: [StackInterpreterSimulatorLSB].
+ 			simulatorClass initializeWithOptions: optionsDictionaryOrArray
- 			[self initializeWithOptions: optionsDictionaryOrArray
  				objectMemoryClass: (anObjectMemory ifNotNil: [anObjectMemory class]).
+ 			 simulatorClass
+ 				onObjectMemory: (anObjectMemory ifNil:
+ 										[self objectMemoryClass simulatorClass new])
+ 				options: optionsDictionaryOrArray]
- 			 SmalltalkImage current endianness == #big
- 				ifTrue: [self notYetImplemented"StackInterpreterSimulatorMSB onObjectMemory: anObjectMemory"]
- 				ifFalse: [StackInterpreterSimulatorLSB onObjectMemory: anObjectMemory]]
  		ifFalse: [super basicNew objectMemory: anObjectMemory; initialize]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"StackInterpreterSimulator new openOn: 'clone.im' extraMemory: 100000"
  
+ 	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
+ 	  hdrNumStackPages hdrEdenBytes headerFlags heapBase |
- 	| f version headerSize count oldBaseAddr bytesToShift swapBytes
- 	  hdrNumStackPages hdrEdenBytes headerFlags |
  	"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 nextLongFrom: f swap: swapBytes.
+ 	dataSize := self nextLongFrom: f swap: swapBytes.  "length of heap in file"
- 	objectMemory setEndOfMemory: (self nextLongFrom: f swap: swapBytes).  "first unused location in heap"
  	oldBaseAddr := self nextLongFrom: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self nextLongFrom: f swap: swapBytes).
  	objectMemory lastHash: (self nextLongFrom: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self nextLongFrom: f swap: swapBytes.
  	headerFlags			:= self nextLongFrom: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory		:= self nextLongFrom: f swap: swapBytes.
  	hdrNumStackPages	:= self nextShortFrom: 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.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to images run on Cog."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	hdrEdenBytes		:= self nextLongFrom: f swap: swapBytes.
  	objectMemory edenBytes: (hdrEdenBytes = 0
  							ifTrue: [objectMemory defaultEdenBytes]
  							ifFalse: [hdrEdenBytes]).
  	desiredEdenBytes := hdrEdenBytes.
  	"allocate interpreter memory"
+ 	heapBase := objectMemory startOfMemory.
+ 	objectMemory
+ 		setHeapBase: heapBase
+ 		memoryLimit: heapBase + dataSize + extraBytes + objectMemory edenBytes + self interpreterAllocationReserveBytes
+ 		endOfMemory: heapBase + dataSize.
+ 	objectMemory memory: (Bitmap new: objectMemory memoryLimit // 4).
- 	objectMemory setMemoryLimit: objectMemory endOfMemory + extraBytes + objectMemory edenBytes + self interpreterAllocationReserveBytes.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
+ 	count := f readInto: objectMemory memory startingAt: 1 count: dataSize // 4.
- 	objectMemory memory: (Bitmap new: objectMemory memoryLimit // 4).
- 	count := f readInto: objectMemory memory startingAt: 1 count: objectMemory endOfMemory // 4.
  	count ~= (objectMemory endOfMemory // 4) ifTrue: [self halt].
  	]
  		ensure: [f close].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
- 	objectMemory initialize.
  	bytesToShift := objectMemory startOfMemory - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities informUser: 'Relocating object pointers...'
  				during: [self initializeInterpreter: bytesToShift].
  !

Item was changed:
  ----- Method: StackInterpreterSimulator>>startOfMemory (in category 'initialization') -----
  startOfMemory
+ 	self shouldNotImplement!
- 	"Return the start of object memory."
- 
- 	^ 0!

Item was changed:
  ----- Method: VMClass class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  	"Falsify the `what type of VM is this?' flags that are defined in the various interp.h files,
  	 or in the case of VMBIGENDIAN the various sqConfig.h files.
  	 Subclass implementations need to include a super initializeMiscConstantsWith:."
  
  	VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:"
  	self isInterpreterClass ifTrue:
  		[STACKVM := COGVM := COGMTVM := false].
  	NewspeakVM := initializationOptions at: #NewspeakVM ifAbsent: [false].
+ 	initializationOptions
+ 		at: #Spur
+ 		put: ((initializationOptions at: #ObjectMemory ifAbsent: [])
+ 				ifNil: [false]
+ 				ifNotNil:
+ 					[:objMemClassName|
+ 					(Smalltalk at: objMemClassName) inheritsFrom: SpurMemoryManager]).
  	MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsent: [false].
  	"N.B.  Not yet implemented."
  	IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsent: [false].
  
  	"These for scripts etc... Usually they should get set by an Interpreter class's initializeMiscConstantsWith:"
  	(initializationOptions includesKey: #STACKVM) ifTrue:
  		[STACKVM := initializationOptions at: #STACKVM].
  	(initializationOptions includesKey: #COGVM) ifTrue:
  		[COGVM := initializationOptions at: #COGVM].
  	(initializationOptions includesKey: #COGMTVM) ifTrue:
  		[COGMTVM := initializationOptions at: #COGMTVM]!

Item was added:
+ ----- Method: VMClass class>>objectRepresentationClass (in category 'accessing class hierarchy') -----
+ objectRepresentationClass
+ 	^self objectMemoryClass objectRepresentationClass!

Item was added:
+ ----- Method: VMClass>>objectRepresentationClass (in category 'accessing') -----
+ objectRepresentationClass
+ 	<doNotGenerate>
+ 	^self class objectRepresentationClass!

Item was changed:
  ----- Method: VMStructType class>>printTypedefOn: (in category 'translation') -----
  printTypedefOn: aStream
  	aStream nextPutAll: 'typedef struct '.
  	self needsTypeTag ifTrue:
  		[aStream nextPutAll: self structTagName; space].
  	aStream nextPut: ${; cr.
  	self instVarNamesAndTypesForTranslationDo:
+ 		[:ivn :typeArg| | type |
- 		[:ivn :typeArg| | type index |
  		type := typeArg.
+ 		#(BytesPerWord BaseHeaderSize BytesPerOop) do:
+ 			[:sizeConstant| | index sizeConstantSize |
+ 			(type notNil
+ 			and: [(index := type indexOf: sizeConstant ifAbsent: 0) > 0]) ifTrue:
+ 				[sizeConstantSize  := VMBasicConstants classPool at: sizeConstant.
+ 				type := (type at: index + 1) = sizeConstantSize ifTrue:
+ 							[type := type copyReplaceFrom: index to: index + 1 with: #().
+ 							 type size = 1 ifTrue: [type first] ifFalse: [type]]]].
- 		(index := type indexOf: #BytesPerWord ifAbsent: 0) > 0 ifTrue:
- 			[type := (type at: index + 1) = BytesPerWord ifTrue:
- 						[type := type copyReplaceFrom: index to: index + 1 with: #().
- 						 type size = 1 ifTrue: [type first] ifFalse: [type]]].
  		type ifNotNil:
  			[type isArray
  				ifTrue:
  					[aStream tab: 1.
+ 					 aStream nextPutAll: type first.
+ 					 (type first last isSeparator or: [type first last = $*]) ifFalse:
- 					aStream nextPutAll: type first.
- 					(type first last isSeparator or: [type first last = $*]) ifFalse:
  						[aStream tab: 2].
+ 					 aStream nextPutAll: ivn.
+ 					 type last first isSeparator ifFalse:
- 					aStream nextPutAll: ivn.
- 					 type last first = $: ifTrue:
  						[aStream space].
  					 aStream
  						nextPutAll: type last;
  						nextPut: $;;
  						cr]
  				ifFalse:
  					[aStream tab: 1.
+ 					 aStream nextPutAll: type.
+ 					 (type last isSeparator or: [type last = $*]) ifFalse:
- 					aStream nextPutAll: type.
- 					(type last isSeparator or: [type last = $*]) ifFalse:
  						[aStream tab: 1].
  					 aStream
  						nextPutAll: ivn;
  						nextPut: $;;
  						cr]]].
  	aStream
  		nextPutAll: ' } ';
  		nextPutAll: self structTypeName;
  		nextPut: $;;
  		cr.
  	self name ~= self structTypeName ifTrue:
  		[aStream cr; nextPutAll: '#define '; nextPutAll: self name; space; nextPutAll: self structTypeName; cr].
  	aStream flush!



More information about the Vm-dev mailing list