[Vm-dev] VM Maker: Cog-eem.181.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Aug 9 01:16:57 UTC 2014


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

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

Name: Cog-eem.181
Author: eem
Time: 8 August 2014, 6:16:28.951 pm
UUID: 6b7e85ce-d219-4fd5-b514-cc153b525585
Ancestors: Cog-eem.180

SpurBootstrap:
Modify bootstrap to install methods that use the new
CompiledMethod header format (655236 literals, primitive
in a callPrimitive bytecode).

Modify methods to new format when cloing image.

Allow prototype methods to be stored in their classes,
pointed to by a SpurBootstrap class prototype marked
with a pragma, hence solve inst and class var access issues.
Allow more than one set of protocols to augment those in
'method prototypes' so the new 'old squeak' type doesn't
have to duplicate all the prototypes in
'method prototypes squeak'.

Needs VMMaker-oscog.eem.849

=============== Diff against Cog-eem.180 ===============

Item was added:
+ ----- Method: CompiledMethod class>>CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive: (in category '*Cog-method prototypes') -----
+ CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex
+ 	"Answer an instance of me. The header is specified by the message 
+ 	 arguments. The remaining parts are not as yet determined."
+ 	| method |
+ 	nTemps > 63 ifTrue:
+ 		[^self error: 'Cannot compile -- too many temporary variables'].	
+ 	nLits > 65535 ifTrue:
+ 		[^self error: 'Cannot compile -- too many literals'].
+ 
+ 	 method := self newMethod: numberOfBytes + trailer size
+ 					header:    (nArgs bitShift: 24)
+ 							+ (nTemps bitShift: 18)
+ 							+ ((nTemps + stackSize) > SmallFrame ifTrue: [1 bitShift: 17] ifFalse: [0])
+ 							+ nLits
+ 							+ (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0]).
+ 	1 to: trailer size do:  "Copy the source code trailer to the end"
+ 		[:i | method at: method size - trailer size + i put: (trailer at: i)].
+ 	^method!

Item was added:
+ ----- Method: CompiledMethod class>>CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive:flag: (in category '*Cog-method prototypes') -----
+ CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex flag: flag
+ 	"Answer an instance of me. The header is specified by the message 
+ 	 arguments. The remaining parts are not as yet determined."
+ 	| method |
+ 	nTemps > 63 ifTrue:
+ 		[^self error: 'Cannot compile -- too many temporary variables'].	
+ 	nLits > 65535 ifTrue:
+ 		[^self error: 'Cannot compile -- too many literals'].
+ 
+ 	 method := self newMethod: numberOfBytes + trailer size
+ 					header:    (nArgs bitShift: 24)
+ 							+ (nTemps bitShift: 18)
+ 							+ ((nTemps + stackSize) > SmallFrame ifTrue: [1 bitShift: 17] ifFalse: [0])
+ 							+ nLits
+ 							+ (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])
+ 							+ (flag ifTrue: [1 bitShift: 29] ifFalse: [0]).
+ 	1 to: trailer size do:  "Copy the source code trailer to the end"
+ 		[:i | method at: method size - trailer size + i put: (trailer at: i)].
+ 	^method!

Item was added:
+ ----- Method: CompiledMethod class>>CompiledMethodclassPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive: (in category '*Cog-method prototypes') -----
+ CompiledMethodclassPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex
+ 	"Answer an instance of me. The header is specified by the message 
+ 	 arguments. The remaining parts are not as yet determined."
+ 	nTemps > 63 ifTrue:
+ 		[^self error: 'Cannot compile -- too many temporary variables'].	
+ 	nLits > 65535 ifTrue:
+ 		[^self error: 'Cannot compile -- too many literals'].
+ 
+ 	^trailer
+ 		createMethod: numberOfBytes
+ 		class: self
+ 		header:    (nArgs bitShift: 24)
+ 				+ (nTemps bitShift: 18)
+ 				+ ((nTemps + stackSize) > SmallFrame ifTrue: [1 bitShift: 17] ifFalse: [0])
+ 				+ nLits
+ 				+ (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])!

Item was added:
+ ----- Method: CompiledMethod class>>CompiledMethodclassPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive:flag: (in category '*Cog-method prototypes') -----
+ CompiledMethodclassPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex flag: flag
+ 	"Answer an instance of me. The header is specified by the message 
+ 	 arguments. The remaining parts are not as yet determined."
+ 	nTemps > 63 ifTrue:
+ 		[^self error: 'Cannot compile -- too many temporary variables'].	
+ 	nLits > 65535 ifTrue:
+ 		[^self error: 'Cannot compile -- too many literals'].
+ 
+ 	^trailer
+ 		createMethod: numberOfBytes
+ 		class: self
+ 		header:    (nArgs bitShift: 24)
+ 				+ (nTemps bitShift: 18)
+ 				+ ((nTemps + stackSize) > SmallFrame ifTrue: [1 bitShift: 17] ifFalse: [0])
+ 				+ nLits
+ 				+ (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])
+ 				+ (flag ifTrue: [1 bitShift: 29] ifFalse: [0])!

Item was added:
+ ----- Method: EncoderForV3PlusClosures>>EncoderForV3PlusClosuresPROTOTYPEgenCallPrimitive: (in category '*Cog-method prototypes') -----
+ EncoderForV3PlusClosuresPROTOTYPEgenCallPrimitive: primitiveIndex
+ 	"139	11101111	iiiiiiii jjjjjjjj	Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
+ 	(primitiveIndex < 1 or: [primitiveIndex > 65535]) ifTrue:
+ 		[self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 65535].
+ 	stream
+ 		nextPut: 139;
+ 		nextPut: (primitiveIndex bitAnd: 255);
+ 		nextPut: (primitiveIndex bitShift: -8)!

Item was added:
+ ----- Method: MethodNode>>MethodNodeOLDSQUEAKPROTOTYPEgenerate: (in category '*Cog-method prototypes') -----
+ MethodNodeOLDSQUEAKPROTOTYPEgenerate: trailer
+ 	"The receiver is the root of a parse tree. Answer an instance of aCompiledMethodClass.
+ 	 The argument, trailer, is arbitrary but is typically either the reference to the source code
+ 	 that is stored with every CompiledMethod, or an encoding of the method's temporary names."
+ 
+ 	| primErrNode blkSize nLits literals stack method |
+ 	self generate: trailer
+ 		ifQuick:
+ 			[:m |
+ 			  m	literalAt: 2 put: encoder associationForClass;
+ 				properties: properties.
+ 			^m].
+ 	primErrNode := self primitiveErrorVariableName ifNotNil:
+ 						[encoder fixTemp: self primitiveErrorVariableName].
+ 	encoder supportsClosureOpcodes ifTrue:
+ 		[self ensureClosureAnalysisDone.
+ 		 encoder rootNode: self. "this is for BlockNode>>sizeCodeForClosureValue:"].
+ 	blkSize := (block sizeCodeForEvaluatedValue: encoder)
+ 				+ (primitive > 0
+ 					ifTrue: [encoder sizeCallPrimitive: primitive]
+ 					ifFalse: [0])
+ 				+ (primErrNode
+ 					ifNil: [0]
+ 					ifNotNil:
+ 						[primErrNode
+ 							index: arguments size + temporaries size;
+ 							sizeCodeForStore: encoder "The VM relies on storeIntoTemp: (129)"]).
+ 	method := CompiledMethod
+ 				newBytes: blkSize
+ 				trailerBytes: trailer 
+ 				nArgs: arguments size
+ 				nTemps: (encoder supportsClosureOpcodes
+ 							ifTrue: [| locals |
+ 									locals := arguments,
+ 											  temporaries,
+ 											  (primErrNode
+ 												ifNil: [#()]
+ 												ifNotNil: [{primErrNode}]).
+ 									encoder
+ 										noteBlockExtent: block blockExtent
+ 										hasLocals: locals.
+ 									locals size]
+ 							ifFalse: [encoder maxTemp])
+ 				nStack: 0
+ 				nLits: (nLits := (literals := encoder allLiterals) size)
+ 				primitive: primitive.
+ 	1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
+ 	encoder streamToMethod: method.
+ 	stack := ParseStack new init.
+ 	primErrNode ifNotNil: [primErrNode emitCodeForStore: stack encoder: encoder].
+ 	stack position: method numTemps.
+ 	primitive > 0 ifTrue:
+ 		[encoder genCallPrimitive: primitive].
+ 	[block emitCodeForEvaluatedValue: stack encoder: encoder]
+ 		on: Error "If an attempt is made to write too much code the method will be asked"
+ 		do: [:ex|  "to grow, and the grow attempt will fail in CompiledMethod class>>#new:"
+ 			ex signalerContext sender method = (CompiledMethod class>>#new:)
+ 				ifTrue: [^self error: 'Compiler code size discrepancy']
+ 				ifFalse: [ex pass]].
+ 	stack position ~= (method numTemps + 1) ifTrue:
+ 		[^self error: 'Compiler stack discrepancy'].
+ 	encoder methodStreamPosition ~= (method size - trailer size) ifTrue:
+ 		[^self error: 'Compiler code size discrepancy'].
+ 	method needsFrameSize: stack size - method numTemps.
+ 	method properties: properties.
+ 	^method!

Item was added:
+ ----- Method: MethodNode>>MethodNodePROTOTYPEgenerate:using: (in category '*Cog-method prototypes') -----
+ MethodNodePROTOTYPEgenerate: trailer using: aCompiledMethodClass
+ 	"The receiver is the root of a parse tree. Answer an instance of aCompiledMethodClass.
+ 	 The argument, trailer, is arbitrary but is typically either the reference to the source code
+ 	 that is stored with every CompiledMethod, or an encoding of the method's temporary names."
+ 
+ 	| primErrNode blkSize nLits locals literals stack method |
+ 	self generate: trailer
+ 		using: aCompiledMethodClass
+ 		ifQuick:
+ 			[:m |
+ 			  m	literalAt: 2 put: encoder associationForClass;
+ 				properties: properties.
+ 			^m].
+ 	primErrNode := self primitiveErrorVariableName ifNotNil:
+ 						[encoder fixTemp: self primitiveErrorVariableName].
+ 	self ensureClosureAnalysisDone.
+ 	encoder rootNode: self. "this is for BlockNode>>sizeCodeForClosureValue:"
+ 	blkSize := (block sizeCodeForEvaluatedValue: encoder)
+ 				+ (primitive > 0
+ 					ifTrue: [encoder sizeCallPrimitive: primitive]
+ 					ifFalse: [0])
+ 				+ (primErrNode
+ 					ifNil: [0]
+ 					ifNotNil:
+ 						[primErrNode
+ 							index: arguments size + temporaries size;
+ 							sizeCodeForStore: encoder "The VM relies on storeIntoTemp: (129)"]).
+ 	locals := arguments, temporaries, (primErrNode ifNil: [#()] ifNotNil: [{primErrNode}]).
+ 	encoder noteBlockExtent: block blockExtent hasLocals: locals.
+ 	method := aCompiledMethodClass
+ 				newBytes: blkSize
+ 				trailerBytes: trailer 
+ 				nArgs: arguments size
+ 				nTemps: locals size
+ 				nStack: 0
+ 				nLits: (nLits := (literals := encoder allLiterals) size)
+ 				primitive: primitive.
+ 	1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
+ 	encoder streamToMethod: method.
+ 	stack := ParseStack new init.
+ 	primErrNode ifNotNil: [primErrNode emitCodeForStore: stack encoder: encoder].
+ 	stack position: method numTemps.
+ 	primitive > 0 ifTrue:
+ 		[encoder genCallPrimitive: primitive].
+ 	[block emitCodeForEvaluatedValue: stack encoder: encoder]
+ 		on: Error "If an attempt is made to write too much code the method will be asked"
+ 		do: [:ex|  "to grow, and the grow attempt will fail in CompiledMethod class>>#new:"
+ 			ex signalerContext sender method = (CompiledMethod class>>#new:)
+ 				ifTrue: [^self error: 'Compiler code size discrepancy']
+ 				ifFalse: [ex pass]].
+ 	stack position ~= (method numTemps + 1) ifTrue:
+ 		[^self error: 'Compiler stack discrepancy'].
+ 	encoder methodStreamPosition ~= (method size - trailer size) ifTrue:
+ 		[^self error: 'Compiler code size discrepancy'].
+ 	method needsFrameSize: stack size - method numTemps.
+ 	method properties: properties.
+ 	^method!

Item was changed:
  Object subclass: #SpurBootstrap
+ 	instanceVariableNames: 'oldHeap newHeap oldHeapSize newHeapSize oldHeapNumObjs newHeapNumObjs map reverseMap classToIndex oldInterpreter lastClassTablePage literalMap methodClasses installedPrototypes sizeSym rehashSym classMetaclass imageTypes'
- 	instanceVariableNames: 'oldHeap newHeap oldHeapSize newHeapSize oldHeapNumObjs newHeapNumObjs map reverseMap classToIndex oldInterpreter lastClassTablePage literalMap methodClasses installedPrototypes sizeSym rehashSym classMetaclass imageType'
  	classVariableNames: 'ImageHeaderFlags ImageName ImageScreenSize TransformedImage'
  	poolDictionaries: 'VMObjectIndices'
  	category: 'Cog-Bootstrapping'!
  
  !SpurBootstrap commentStamp: 'eem 9/11/2013 05:45' prior: 0!
  SpurBootstrap bootstraps an image in SpurMemoryManager format from a Squeak V3 + closures format.
  
  e.g.
  	(SpurBootstrap32 new on: '/Users/eliot/Cog/startreader.image')
  		transform;
  		launch
  
  Bootstrap issues:
  - should it implement a deterministic Symbol identityHash? This means set a Symbol's identityHash at instance creation time
    based on its string hash so that e.g. MethodDIctionary instances have a deterministic order and don't need to be rehashed on load.
  - should it collapse ContextPart and MethodContext down onto Context (and perhaps eliminate BlockContext)?
  
  Instance Variables
  	classToIndex:			<Dictionary>
  	lastClassTablePage:	<Integer>
  	map:					<Dictionary>
  	methodClasses:		<Set>
  	newHeap:				<SpurMemoryManager>
  	oldHeap:				<NewObjectMemory>
  	oldInterpreter:			<StackInterpreterSimulator>
  	reverseMap:			<Dictionary>
  	symbolMap:				<Dictionary>
  
  classToIndex
  	- oldClass to new classIndex map
  
  lastClassTablePage
  	- oop in newHeap of last classTable page.  U<sed in validation to filter-out class table.
  
  methodClasses
  	- cache of methodClassAssociations for classes in which modified methods are installed
  
  map
  	- oldObject to newObject map
  
  newHeap
  	- the output, bootstrapped image
  
  oldHeap
  	- the input, image
  
  oldInterpreter
  	- the interpreter associated with oldHeap, needed for a hack to grab WeakArray
  
  reverseMap
  	- newObject to oldObject map
  
  symbolMap
  	- symbol toi symbol oop in oldHeap, used to map prototype methdos to methods in oldHeap!

Item was added:
+ ----- Method: SpurBootstrap class>>BytecodeEncoderPROTOTYPEsizeCallPrimitive: (in category 'method prototypes') -----
+ BytecodeEncoderPROTOTYPEsizeCallPrimitive: primitiveIndex
+ 	^self sizeOpcodeSelector: #genCallPrimitive: withArguments: {primitiveIndex}!

Item was added:
+ ----- Method: SpurBootstrap class>>CompiledMethodPROTOTYPEnumLiterals (in category 'method prototypes') -----
+ CompiledMethodPROTOTYPEnumLiterals
+ 	"Answer the number of literals used by the receiver."
+ 	^self header bitAnd: 65535!

Item was added:
+ ----- Method: SpurBootstrap class>>CompiledMethodPROTOTYPEprimitive (in category 'method prototypes') -----
+ CompiledMethodPROTOTYPEprimitive
+ 	"Answer the primitive index associated with the receiver.
+ 	 Zero indicates that this is not a primitive method."
+ 	| initialPC |
+ 	^(self header anyMask: 65536) "Is the hasPrimitive? flag set?"
+ 		ifTrue: [(self at: (initialPC := self initialPC) + 1) + ((self at: initialPC + 2) bitShift: 8)]
+ 		ifFalse: [0]!

Item was added:
+ ----- Method: SpurBootstrap class>>CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive: (in category 'method prototypes old squeak') -----
+ CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex
+ 	"Since this method refers to ClassVariables things are easier if it lives in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive:flag: (in category 'method prototypes old squeak') -----
+ CompiledMethodclassOLDSQUEAKPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex flag: flag
+ 	"Since this method refers to ClassVariables things are easier if it lives in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>CompiledMethodclassPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive: (in category 'method prototypes') -----
+ CompiledMethodclassPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex
+ 	"Since this method refers to ClassVariables things are easier if it lives in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>CompiledMethodclassPROTOTYPEnewBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive:flag: (in category 'method prototypes') -----
+ CompiledMethodclassPROTOTYPEnewBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex flag: flag
+ 	"Since this method refers to ClassVariables things are easier if it lives in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>EncoderForV3PlusClosuresPROTOTYPEgenCallPrimitive: (in category 'method prototypes') -----
+ EncoderForV3PlusClosuresPROTOTYPEgenCallPrimitive: primitiveIndex
+ 	"Since this method has inst var refs the prototype must live in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>EncoderForV3PlusClosuresclassPROTOTYPEbytecodeSize: (in category 'method prototypes') -----
+ EncoderForV3PlusClosuresclassPROTOTYPEbytecodeSize: bytecode
+ 	"Answer the number of bytes in the bytecode."
+ 	bytecode <= 125 ifTrue:
+ 		[^1].
+ 	bytecode >= 176 ifTrue:
+ 		[^1].
+ 	bytecode >= 160 ifTrue: "long jumps"
+ 		[^2].
+ 	bytecode >= 144 ifTrue: "short jumps"
+ 		[^1].
+ 	"extensions"
+ 	bytecode >= 128 ifTrue:
+ 		[^#(2 2 2 2 3 2 2 1 1 1 2 3 3 3 3 4) at: bytecode - 127].
+ 	^nil!

Item was added:
+ ----- Method: SpurBootstrap class>>EncoderForV3PlusClosuresclassPROTOTYPEcallPrimitiveCode (in category 'method prototypes') -----
+ EncoderForV3PlusClosuresclassPROTOTYPEcallPrimitiveCode
+ 	"139	11101111	iiiiiiii jjjjjjjj	Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
+ 	^139!

Item was added:
+ ----- Method: SpurBootstrap class>>InstructionClientPROTOTYPEcallPrimitive: (in category 'method prototypes') -----
+ InstructionClientPROTOTYPEcallPrimitive: pimIndex
+ 	"V3PlusClosures:	139 10001011	iiiiiiii   jjjjjjjj  Call Primitive #iiiiiiii + (jjjjjjjj * 256)
+ 	 NewsqueakV4:		249 11111001	iiiiiiii   jjjjjjjj  Call Primitive #iiiiiiii + (jjjjjjjj * 256)
+ 	 SistaV1:			248 11111000 iiiiiiii mjjjjjjj  Call Primitive #iiiiiiii + ( jjjjjjj * 256)
+ 							m=1 means inlined primitive, no hard return after execution."!

Item was added:
+ ----- Method: SpurBootstrap class>>InstructionStreamPROTOTYPEinterpretV3ClosuresExtension:in:for: (in category 'method prototypes') -----
+ InstructionStreamPROTOTYPEinterpretV3ClosuresExtension: offset in: method for: client
+ 	"Since this method has inst var refs the prototype must live in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>MethodNodeOLDSQUEAKPROTOTYPEgenerate: (in category 'method prototypes old squeak') -----
+ MethodNodeOLDSQUEAKPROTOTYPEgenerate: trailerBytes
+ 	"Since this method has inst var refs the prototype must live in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>MethodNodePROTOTYPEgenerate:using: (in category 'method prototypes') -----
+ MethodNodePROTOTYPEgenerate: trailer using: aCompiledMethodClass
+ 	"Since this method has inst var refs the prototype must live in the actual class."
+ 
+ 	<indirect>!

Item was added:
+ ----- Method: SpurBootstrap class>>bootstrapOldSqueakImage: (in category 'utilities') -----
+ bootstrapOldSqueakImage: imageFileBaseName
+ 	"Try asnd bootstrap a pre-CompiledMethodTrailer Squeak image."
+ 	self bootstrapImage: imageFileBaseName type: #('squeak' 'old squeak')!

Item was changed:
  ----- Method: SpurBootstrap>>allPrototypeMethods (in category 'method prototypes') -----
  allPrototypeMethods
+ 	^imageTypes
+ 		inject: (SpurBootstrap class organization listAtCategoryNamed: #'method prototypes')
+ 		into: [:prototypes :type|
+ 			prototypes, (SpurBootstrap class organization listAtCategoryNamed: #'method prototypes ', type)]!
- 	^ (SpurBootstrap class organization listAtCategoryNamed: #'method prototypes'),
- 	(SpurBootstrap class organization listAtCategoryNamed: #'method prototypes ', imageType)!

Item was changed:
  ----- Method: SpurBootstrap>>bootstrapImage:type: (in category 'public access') -----
+ bootstrapImage: imageName type: typeNameOrArrayOfTypeNames
+ 	"type can be:
+ 		- 'squeak'
+ 		- {'old squeak' 'squeak' }
- bootstrapImage: imageName type: typeName
- 	"type can be: 
- 		- 'squeak' 
  		- 'pharo'
  		- it might be 'newspeak', if needed (but is not implemented)"
+ 	imageTypes := typeNameOrArrayOfTypeNames isArray
+ 						ifTrue: [typeNameOrArrayOfTypeNames]
+ 						ifFalse: [{typeNameOrArrayOfTypeNames}].
- 	imageType := typeName.
  	self bootstrapImage: imageName
  	!

Item was changed:
  ----- Method: SpurBootstrap>>classNameForPrototypeMethod: (in category 'method prototypes') -----
  classNameForPrototypeMethod: protoMethod
  	| protoSelector |
  	protoSelector := protoMethod selector.
+ 	#('OLDSQUEAKPROTOTYPE' 'SQUEAKPROTOTYPE' 'PHAROPROTOTYPE' 'PROTOTYPE') do:
- 	#('SQUEAKPROTOTYPE' 'PHAROPROTOTYPE' 'PROTOTYPE') do:
  		[:prototype| | index |
+ 		(index := protoSelector indexOfSubCollection: prototype) ~= 0 ifTrue:
- 		(index := protoSelector indexOfSubCollection: 'PROTOTYPE') ~= 0 ifTrue:
  			[^(protoSelector first: index - 1) asSymbol]].
  	self error: 'really??'!

Item was changed:
  ----- Method: SpurBootstrap>>clone:classIndex: (in category 'bootstrap image') -----
  clone: oldObj classIndex: classIndex
  	| newObj |
  	newObj := newHeap
+ 				allocateSlots: (((oldHeap isCompiledMethod: oldObj) and: [(oldInterpreter primitiveIndexOf: oldObj) > 0])
+ 								ifTrue: [(oldHeap byteSizeOf: oldObj) + 3 + self wordSize - 1 // self wordSize]
+ 								ifFalse: [oldHeap numSlotsOf: oldObj])
- 				allocateSlots: (oldHeap numSlotsOf: oldObj)
  				format: (self newFormatFor: oldObj)
  				classIndex: classIndex.
  	reverseMap at: newObj put: oldObj.
  	^map at: oldObj put: newObj!

Item was changed:
  ----- Method: SpurBootstrap>>cloneMethodProxy: (in category 'bootstrap methods') -----
  cloneMethodProxy: proxy "<VMCompiledMethodProxy>"
  	| bytes newMethod |
  	bytes := proxy size - proxy initialPC + 1.
  	newMethod := CompiledMethod
  						newMethod: bytes
  						header: proxy header.
+ 	1 to: proxy numLiterals - 1 do:
+ 		[:i| newMethod literalAt: i put: (proxy literalAt: i)].
+ 	newMethod
+ 		literalAt: proxy numLiterals
+ 		put: (Smalltalk bindingOf: #Character).
- 	false
- 		ifTrue:
- 			[1 to: proxy numLiterals - 2 do:
- 				[:i| | literal |
- 				literal := (proxy literalAt: i) oop.
- 				literal := (oldHeap isIntegerObject: literal)
- 							ifTrue: [oldHeap integerValueOf: literal]
- 							ifFalse: ['literal', i printString].
- 				newMethod literalAt: i put: literal].
- 			newMethod
- 				literalAt: proxy numLiterals - 1
- 					put: (oldHeap stringOf: (proxy literalAt: proxy numLiterals - 1) oop) asSymbol;
- 				literalAt: proxy numLiterals
- 					put: (Smalltalk bindingOf: #Character)]
- 		ifFalse:
- 			[1 to: proxy numLiterals - 1 do:
- 				[:i| newMethod literalAt: i put: (proxy literalAt: i)].
- 			newMethod
- 				literalAt: proxy numLiterals
- 				put: (Smalltalk bindingOf: #Character)].
  	proxy initialPC to: proxy size do:
  		[:i| newMethod at: i put: (proxy at: i)].
  	^newMethod!

Item was added:
+ ----- Method: SpurBootstrap>>convertOldMethodHeader: (in category 'bootstrap image') -----
+ convertOldMethodHeader: methodHeader
+ 	^newHeap integerObjectOf:
+ 		   ((oldInterpreter argumentCountOfMethodHeader: methodHeader) << 24)
+ 		+ ((oldInterpreter temporaryCountOfMethodHeader: methodHeader) << 18)
+ 		+ ((oldInterpreter methodHeaderIndicatesLargeFrame: methodHeader) ifTrue: [1 << 17] ifFalse: [0])
+ 		+ ((oldInterpreter methodHeaderHasPrimitive: methodHeader) ifTrue: [1 << 16] ifFalse: [0])
+ 		+ (oldHeap literalCountOfMethodHeader: methodHeader)!

Item was changed:
  ----- Method: SpurBootstrap>>fillInCompiledMethod:from: (in category 'bootstrap image') -----
  fillInCompiledMethod: newObj from: oldObj
+ 	| firstByteIndex primIndex |
+ 	self fillInPointerObject: newObj from: oldObj.
+ 	"Now convert the COmpiledMethod's format.  First write the header in tye new format"
+ 	newHeap
+ 		storePointerUnchecked: 0
+ 		ofObject: newObj
+ 		withValue: (self convertOldMethodHeader: (oldHeap fetchPointer: 0 ofObject: oldObj)).
+ 	"Then if necessary prepend the callPrimitive: bytecode"
+ 	(primIndex := oldInterpreter primitiveIndexOf: oldObj) > 0
+ 		ifTrue:
+ 			[firstByteIndex := oldHeap lastPointerOf: oldObj.
+ 			 newHeap
+ 				storeByte: firstByteIndex + 0 ofObject: newObj withValue: 139;
+ 				storeByte: firstByteIndex + 1 ofObject: newObj withValue: (primIndex bitAnd: 255);
+ 				storeByte: firstByteIndex + 2 ofObject: newObj withValue: (primIndex bitShift: -8).
+ 			 firstByteIndex to: (oldHeap numBytesOf: oldObj) - 1 do:
+ 				[:i|
+ 				newHeap storeByte: i + 3 ofObject: newObj withValue: (oldHeap fetchByte: i ofObject: oldObj)]]
+ 		ifFalse:
+ 			[(oldHeap lastPointerOf: oldObj) / oldHeap wordSize to: (oldHeap numSlotsOf: oldObj) - 1 do:
+ 				[:i|
+ 				newHeap storeLong32: i ofObject: newObj withValue: (oldHeap fetchLong32: i ofObject: oldObj)]]!
- 	self fillInBitsObject: newObj from: oldObj.
- 	self fillInPointerObject: newObj from: oldObj!

Item was removed:
- ----- Method: SpurBootstrap>>findLiteral: (in category 'bootstrap methods') -----
- findLiteral: aLiteral
- 	| symbolOop smalltalk array |
- 	aLiteral isString ifTrue:
- 		[^self stringFor: aLiteral].
- 	aLiteral isFloat ifTrue:
- 		[^oldInterpreter floatObjectOf: aLiteral].
- 	aLiteral isArray ifTrue:
- 		[^self cloneArrayLiteral: aLiteral].
- 	self assert: aLiteral isVariableBinding.
- 	symbolOop := self findSymbol: aLiteral key.
- 	smalltalk := oldHeap splObj: 8.
- 	array := oldHeap fetchPointer: 1 ofObject: smalltalk.
- 	self assert: (oldHeap isArray: array).
- 	0 to: (oldHeap numSlotsOf: array) - 1 do:
- 		[:i| | bindingOrNil |
- 		bindingOrNil := oldHeap fetchPointer: i ofObject: array.
- 		(bindingOrNil ~= oldHeap nilObject
- 		 and: [symbolOop = (oldHeap fetchPointer: KeyIndex ofObject: bindingOrNil)
- 		 and: [aLiteral key == #Smalltalk
- 				ifTrue:
- 					[(oldHeap fetchPointer: ValueIndex ofObject: bindingOrNil) = smalltalk]
- 				ifFalse:
- 					[oldInterpreter
- 						classNameOf: (oldHeap fetchPointer: ValueIndex ofObject: bindingOrNil)
- 						Is: aLiteral key]]]) ifTrue:
- 			[^bindingOrNil]].
- 	self error: 'couldn''t find literal ', aLiteral printString!

Item was added:
+ ----- Method: SpurBootstrap>>findLiteral:inClass: (in category 'bootstrap methods') -----
+ findLiteral: aLiteral inClass: classOop
+ 	| bindingOrNil |
+ 	aLiteral isString ifTrue:
+ 		[^self stringFor: aLiteral].
+ 	aLiteral isFloat ifTrue:
+ 		[^oldInterpreter floatObjectOf: aLiteral].
+ 	aLiteral isArray ifTrue:
+ 		[^self cloneArrayLiteral: aLiteral].
+ 	self assert: aLiteral isVariableBinding.
+ 	bindingOrNil := self interpreter: oldInterpreter
+ 						object: classOop
+ 						perform: (self findSymbol: #bindingOf:)
+ 						withArguments: {self findSymbol: aLiteral key}.
+ 	bindingOrNil ~= oldHeap nilObject ifTrue:
+ 		[^bindingOrNil].
+ 	self error: 'couldn''t find literal ', aLiteral printString!

Item was changed:
  ----- Method: SpurBootstrap>>initialize (in category 'initialize-release') -----
  initialize
  	super initialize.
+ 	imageTypes := {'squeak'}. "By default, image is Squeak (so Eliot does not kick me :P)"!
- 	imageType := 'squeak'. "By default, image is Squeak (so Eliot does not kick me :P)"!

Item was changed:
  ----- Method: SpurBootstrap>>installableMethodFor:selector:className:isMeta: (in category 'bootstrap methods') -----
  installableMethodFor: aCompiledMethod selector: selector className: className isMeta: isMeta
  	"Create a sourceless method to install in the bootstrapped image.  It will allow the
  	 bootstrap to limp along until the relevant transformed Monticello package is loaded."
+ 	| compiledMethodClass methodClassBinding methodClass sourcelessMethod bytes newMethod |
- 	| compiledMethodClass sourcelessMethod bytes newMethod |
  	compiledMethodClass := self findClassNamed: (self findSymbol: #CompiledMethod).
+ 	methodClassBinding := self methodClassBindingForClassName: className isMeta: isMeta.
+ 	methodClass := oldHeap fetchPointer: ValueIndex ofObject: methodClassBinding.
  	"the prototypes have source pointers.  the Character methods to be replaced don't."
  	sourcelessMethod := aCompiledMethod trailer hasSourcePointer
  							ifTrue: [aCompiledMethod copyWithTempsFromMethodNode: aCompiledMethod methodNode]
  							ifFalse: [aCompiledMethod].
  	bytes := sourcelessMethod size - sourcelessMethod initialPC + 1.
  	newMethod := self
  					interpreter: oldInterpreter
  					object: compiledMethodClass
  					perform: (self findSymbol: #newMethod:header:)
  					withArguments: { oldHeap integerObjectOf: bytes.
  									   oldHeap integerObjectOf: sourcelessMethod header }.
  	1 to: sourcelessMethod numLiterals - 2 do:
  		[:i| | literal oop |
  		literal := sourcelessMethod literalAt: i.
  		oop := (literal isLiteral or: [literal isVariableBinding])
  					ifTrue:
  						[literal isInteger
  							ifTrue: [oldHeap integerObjectOf: literal]
+ 							ifFalse: [literalMap
+ 										at: literal
+ 										ifAbsent: [self findLiteral: literal
+ 														inClass: methodClass]]]
- 							ifFalse: [literalMap at: literal ifAbsent: [self findLiteral: literal]]]
  					ifFalse: "should be a VMObjectProxy"
  						[literal oop].
  		oldHeap storePointer: i ofObject: newMethod withValue: oop].
  	oldHeap
  		storePointer: sourcelessMethod numLiterals - 1
  		ofObject: newMethod
  		withValue: (selector isSymbol
  						ifTrue: [self findSymbol: selector]
  						ifFalse: [selector oop]);
  		storePointer: sourcelessMethod numLiterals
  		ofObject: newMethod
+ 		withValue: methodClass.
- 		withValue: (self methodClassForClassName: className
- 						isMeta: isMeta).
  	sourcelessMethod initialPC to: sourcelessMethod size do:
  		[:i|
  		oldHeap storeByte: i - 1 ofObject: newMethod withValue: (sourcelessMethod byteAt: i)].
  	^newMethod!

Item was added:
+ ----- Method: SpurBootstrap>>methodClassBindingForClassName:isMeta: (in category 'bootstrap methods') -----
+ methodClassBindingForClassName: classNameSymbol isMeta: isMeta 
+ 	| class |
+ 	class := self findClassNamed: (literalMap at: classNameSymbol).
+ 	isMeta ifTrue: [class := oldHeap fetchClassOfNonImm: class].
+ 	^self interpreter: oldInterpreter
+ 		object: class
+ 		perform: (self findSymbol: #binding)
+ 		withArguments: #()!

Item was removed:
- ----- Method: SpurBootstrap>>methodClassForClassName:isMeta: (in category 'bootstrap methods') -----
- methodClassForClassName: classNameSymbol isMeta: isMeta 
- 	| class |
- 	class := self findClassNamed: (literalMap at: classNameSymbol).
- 	isMeta ifTrue: [class := oldHeap fetchClassOfNonImm: class].
- 	methodClasses do:
- 		[:mca|
- 		class = (oldHeap fetchPointer: ValueIndex ofObject: mca) ifTrue:
- 			[^mca]].
- 	oldHeap allObjectsDo:
- 		[:o| | methodClassAssociation |
- 		(oldHeap isCompiledMethod: o) ifTrue:
- 			[methodClassAssociation := oldInterpreter methodClassAssociationOf: o.
- 			 class == (oldHeap fetchPointer: ValueIndex ofObject: methodClassAssociation) ifTrue:
- 				[methodClasses add: methodClassAssociation.
- 				 ^methodClassAssociation]]].
- 	self error: 'could not find methodClassAssociation for ', classNameSymbol, (isMeta ifTrue: [' class'] ifFalse:[''])!

Item was changed:
  ----- Method: SpurBootstrap>>prototypeClassNameMetaSelectorMethodDo: (in category 'method prototypes') -----
  prototypeClassNameMetaSelectorMethodDo: quaternaryBlock
  	"Evaluate aBlock with class name, class is meta, method and selector.
  	 For now find methods in class-side category #'method prototypes'.
  	 Scheme could be extended to have different protocols for different
  	 Squeak/Pharo versions."
  	self allPrototypeMethods do:
  		[:protoSelector| | method className isMeta |
  		method := SpurBootstrap class >> protoSelector.
  		className := self classNameForPrototypeMethod: method.
  		(isMeta := className endsWith: 'class') ifTrue:
  			[className := (className allButLast: 5) asSymbol].
+ 		(method pragmaAt: #indirect) ifNotNil:
+ 			[method := (isMeta
+ 							ifTrue: [(Smalltalk classNamed: className) class]
+ 							ifFalse: [Smalltalk classNamed: className]) >> protoSelector].
  		quaternaryBlock
  			value: className
  			value: isMeta
  			value: (self selectorForPrototypeMethod: method)
  			value: method]!

Item was changed:
  ----- Method: SpurBootstrap>>rehashImage (in category 'bootstrap image') -----
  rehashImage
  	"Rehash all collections in newHeap.
  	 Find out which classes implement rehash, entering a 1 against their classIndex in rehashFlags.
  	 Enumerate all objects, rehashing those whose class has a bit set in rehashFlags."
+ 	| n sim rehashFlags dotDate |
- 	| n sim rehashFlags |
  	sim := StackInterpreterSimulator onObjectMemory: newHeap.
  	sim 
  		setImageHeaderFlagsFrom: oldInterpreter getImageHeaderFlags;
  		imageName: 'spur image';
  		assertValidExecutionPointersAtEachStep: false..
  	newHeap coInterpreter: sim.
  	sim bootstrapping: true.
  	sim initializeInterpreter: 0.
  	sim instVarNamed: 'methodDictLinearSearchLimit' put: SmallInteger maxVal.
  
  	newHeap
  		setHashBitsOf: newHeap nilObject to: 1;
  		setHashBitsOf: newHeap falseObject to: 2;
  		setHashBitsOf: newHeap trueObject to: 3.
  
  	rehashFlags := ByteArray new: newHeap numClassTablePages * newHeap classTablePageSize.
  	n := 0.
  	newHeap classTableObjectsDo:
  		[:class| | classIndex |
  		sim messageSelector: (map at: rehashSym).
  		"Lookup rehash but don't be fooled by ProtoObject>>rehash, which is just ^self."
  		((sim lookupMethodNoMNUEtcInClass: class) = 0
  		 and: [(sim isQuickPrimitiveIndex: (sim primitiveIndexOf: (sim instVarNamed: 'newMethod'))) not]) ifTrue:
  			[n := n + 1.
  			 classIndex := newHeap rawHashBitsOf: class.
  			 rehashFlags
  				at: classIndex >> 3 + 1
  				put: ((rehashFlags at: classIndex >> 3 + 1)
  						bitOr: (1 << (classIndex bitAnd: 7)))]].
  	Transcript cr; print: n; nextPutAll: ' classes understand rehash. rehashing instances...'; flush.
+ 	dotDate := Time now asSeconds.
  	n := 0.
  	self withExecutableInterpreter: sim
  		do: [sim setBreakSelector: 'error:'.
  			 "don't rehash twice (actually without limit), so don't rehash any new objects created."
  			 newHeap allExistingOldSpaceObjectsDo:
  				[:o| | classIndex |
  				classIndex := newHeap classIndexOf: o.
  				((rehashFlags at: classIndex >> 3 + 1) anyMask: 1 << (classIndex bitAnd: 7)) ifTrue:
+ 					[Time now asSeconds > dotDate ifTrue:
+ 					 	[Transcript nextPut: $.; flush.
+ 						 dotDate := Time now asSeconds].
- 					[(n := n + 1) \\ 16 = 0 ifTrue:
- 					 	[Transcript nextPut: $.; flush].
  					 "2845 = n ifTrue: [self halt]."
  					 "Rehash an object if its size is > 0.
  					  Symbol implements rehash, but let's not waste time rehashing it; in Squeak
  					  up to 2013 symbols are kept in a set which will get reashed anyway..
  					  Don't rehash empty collections; they may be large for a reason and rehashing will shrink them."
  					 ((sim addressCouldBeClassObj: o)
  					   or: [(self interpreter: sim
  							object: o
  							perform: (map at: sizeSym)
  							withArguments: #()) = (newHeap integerObjectOf: 0)]) ifFalse:
  						[self interpreter: sim
  							object: o
  							perform: (map at: rehashSym)
  							withArguments: #()]]]]!

Item was changed:
  ----- Method: SpurBootstrap>>validate (in category 'bootstrap image') -----
  validate
  	| p n duplicates maxClassIndex savedEndOfMemory |
  	self assert: (reverseMap at: newHeap specialObjectsOop) = oldHeap specialObjectsOop.
  	self assert: (map at: oldHeap specialObjectsOop) = newHeap specialObjectsOop.
  	self assert: (reverseMap at: newHeap classTableRootObj ifAbsent: []) isNil.
  
  	duplicates := { 3. newHeap arrayClassIndexPun. newHeap weakArrayClassIndexPun }.
  	maxClassIndex := classToIndex inject: 0 into: [:a :b| a max: b].
  	self assert: ((newHeap arrayClassIndexPun to: maxClassIndex) select:
  					[:idx| | classObj |
  					(classObj := newHeap classOrNilAtIndex: idx) ~= newHeap nilObject
  					and: [(newHeap classIndexOf: classObj) = (newHeap rawHashBitsOf: classObj)]]) isEmpty.
  	0 to: maxClassIndex do:
  		[:index| | classObj |
  		(index <= newHeap tagMask
  		 and: [index > newHeap isForwardedObjectClassIndexPun]) ifTrue:
  			[(classObj := newHeap classOrNilAtIndex: index) = newHeap nilObject
  				ifTrue:
  					[self assert: (classToIndex keyAtValue: index ifAbsent: []) isNil]
  				ifFalse:
  					[self assert: (newHeap classIndexOf: classObj) ~= (newHeap rawHashBitsOf: classObj).
  					(duplicates includes: index) ifFalse:
  						[self assert: (newHeap rawHashBitsOf: classObj) = index]]]].
  	classToIndex keysAndValuesDo:
  		[:oldClass :idx|
  		self assert: (newHeap rawHashBitsOf: (map at: oldClass)) = idx. 
  		self assert: oldClass = (reverseMap at: (newHeap classAtIndex: idx))].
  	n := 0.
  	savedEndOfMemory := newHeap endOfMemory.
  	newHeap setEndOfMemory: newHeap freeOldSpaceStart.
  	newHeap allObjectsDo:
  		[:o|
  		(o <= newHeap trueObject
  		 or: [o > lastClassTablePage]) ifTrue:
  			[self assert: (reverseMap includesKey: o).
  			 self assert: (newHeap fetchClassOfNonImm: o) = (map at: (oldHeap fetchClassOfNonImm: (reverseMap at: o)))].
  		n := n + 1.
  		p := o].
  	newHeap setEndOfMemory: savedEndOfMemory.
  	self touch: p.
+ 	self assert: (n between: map size and: map size + ((imageTypes includes: 'squeak')
- 	self assert: (n between: map size and: map size + (imageType = 'squeak'
  														ifTrue: [6]
  														ifFalse: [8])). "+ 6 or 8 is room for freelists & classTable"
  
  	"check some class properties to ensure the format changes are correct"
  	self assert: (newHeap fixedFieldsOfClassFormat: (newHeap formatOfClass: newHeap classArray)) = 0.
  	self assert: (newHeap instSpecOfClassFormat: (newHeap formatOfClass: newHeap classArray)) = newHeap arrayFormat!



More information about the Vm-dev mailing list