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

commits at source.squeak.org commits at source.squeak.org
Sat May 21 19:25:34 UTC 2016


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

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

Name: Cog-eem.323
Author: eem
Time: 21 May 2016, 12:25:21.445269 pm
UUID: 4e20a484-a807-44c1-a1e8-b78954ba7ec1
Ancestors: Cog-tpr.322

Complete the Spur bootstrap for Cuis 4.2. 3+4=7.

Update some older prototypes to reflect the current state of code in Squeak 5.

=============== Diff against Cog-tpr.322 ===============

Item was changed:
  ----- 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."
  	| method pc |
  	nArgs > 15 ifTrue:
  		[^self error: 'Cannot compile -- too many arguments'].
  	nTemps > 63 ifTrue:
  		[^self error: 'Cannot compile -- too many temporary variables'].	
+ 	nLits > 32768 ifTrue:
- 	nLits > 65535 ifTrue:
  		[^self error: 'Cannot compile -- too many literals'].
  
  	method := 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]).
  	primitiveIndex > 0 ifTrue:
  		[pc := method initialPC.
  		 method
  			at: pc + 0 put: method encoderClass callPrimitiveCode;
  			at: pc + 1 put: (primitiveIndex bitAnd: 16rFF);
  			at: pc + 2 put: (primitiveIndex bitShift: -8)].
  	^method!

Item was changed:
  ----- 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."
  	| method pc |
  	nArgs > 15 ifTrue:
  		[^self error: 'Cannot compile -- too many arguments'].
  	nTemps > 63 ifTrue:
  		[^self error: 'Cannot compile -- too many temporary variables'].	
+ 	nLits > 32768 ifTrue:
- 	nLits > 65535 ifTrue:
  		[^self error: 'Cannot compile -- too many literals'].
  
  	method := 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]).
  	primitiveIndex > 0 ifTrue:
  		[pc := method initialPC.
  		 method
  			at: pc + 0 put: method encoderClass callPrimitiveCode;
  			at: pc + 1 put: (primitiveIndex bitAnd: 16rFF);
  			at: pc + 2 put: (primitiveIndex bitShift: -8)].
  	^method!

Item was added:
+ ----- Method: MethodNode>>MethodNodePROTOTYPEgenerate:using:ifQuick: (in category '*Cog-method prototypes') -----
+ MethodNodePROTOTYPEgenerate: trailer using: aCompiledMethodClass ifQuick: methodBlock
+ 	| v |
+ 	(primitive = 0 and: [arguments size = 0 and: [block isQuick]]) ifFalse:
+ 		[^self].
+ 	v := block code.
+ 	v < 0 ifTrue:
+ 		[^self].
+ 	v = LdSelf ifTrue:
+ 		[^methodBlock value: (aCompiledMethodClass toReturnSelfTrailerBytes: trailer)].
+ 	(v between: LdTrue and: LdMinus1 + 3) ifTrue:
+ 		[^methodBlock value: (aCompiledMethodClass toReturnConstant: v - LdSelf trailerBytes: trailer)].
+ 	v < ((CodeBases at: LdInstType) + (CodeLimits at: LdInstType)) ifTrue:
+ 		[^methodBlock value: (aCompiledMethodClass toReturnField: v trailerBytes: trailer)].
+ 	v // 256 = 1 ifTrue:
+ 		[^methodBlock value: (aCompiledMethodClass toReturnField: v \\ 256 trailerBytes: trailer)]!

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 rehashSym sizeSym |
  	rehashSym := map at: (self findSymbol: #rehash).
  	sizeSym := map at: (self findSymbol: #size).
  	sim := StackInterpreterSimulator 
  				onObjectMemory: newHeap 
  				options: #(ObjectMemory #Spur32BitMemoryManager).
  	sim 
  		setImageHeaderFlagsFrom: oldInterpreter getImageHeaderFlags;
  		imageName: 'spur image';
  		assertValidExecutionPointersAtEachStep: false..
  	newHeap coInterpreter: sim.
  	sim bootstrapping: true.
  	sim initializeInterpreter: 0.
  	sim instVarNamed: 'methodDictLinearSearchLimit' put: SmallInteger maxVal.
+ 	(imageTypes includes: 'cuis') ifTrue:
+ 		[newHeap scavenger growRememberedSet]. "Rehashing a 4.2 Cuis image overflows the 768 element high tide."
  	
  	sim redirectTranscriptToHost.
  
  	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: rehashSym.
  		"Lookup rehash but don't be fooled by ProtoObject>>rehash, which is just ^self."
  		((sim lookupOrdinaryNoMNUEtcInClass: 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].
  					 "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: sizeSym
  							withArguments: #()) = (newHeap integerObjectOf: 0)]) ifFalse:
  						[self interpreter: sim
  							object: o
  							perform: rehashSym
  							withArguments: #()]]]]!

Item was added:
+ ----- Method: SpurBootstrapCuisPrototypes>>ArrayPROTOTYPEcreateMethod:class:header: (in category 'method prototypes') -----
+ ArrayPROTOTYPEcreateMethod: numberOfBytesForAllButTrailer class: aCompiledMethodClass header: headerWord 
+ 	| meth delta |
+ 	meth := aCompiledMethodClass newMethod: numberOfBytesForAllButTrailer + self size header: headerWord.
+ 	"copy the trailer data"
+ 	delta := meth size - self size.
+ 	1 to: self size do:
+ 		[:i | meth at: delta + i put: (self at: i)].
+ 	^meth!

Item was added:
+ ----- Method: SpurBootstrapCuisPrototypes>>MethodNodePROTOTYPEgenerate:using:ifQuick: (in category 'method prototypes') -----
+ MethodNodePROTOTYPEgenerate: trailer using: aCompiledMethodClass ifQuick: methodBlock
+ 	<indirect>!

Item was changed:
  ----- Method: SpurBootstrapPrototypes>>ArrayPROTOTYPEelementsForwardIdentityTo: (in category 'method prototypes') -----
  ArrayPROTOTYPEelementsForwardIdentityTo: otherArray
  	"This primitive performs a bulk mutation, causing all pointers to the elements of the
  	 receiver to be replaced by pointers to the corresponding elements of otherArray.
  	 The identityHashes remain with the pointers rather than with the objects so that
  	 the objects in this array should still be properly indexed in any existing hashed
  	 structures after the mutation."
  	<primitive: 72 error: ec>
+ 	ec == #'bad receiver' ifTrue:
+ 		[^self error: 'receiver must be of class Array'].
+ 	ec == #'bad argument' ifTrue:
+ 		[^self error: (otherArray class == Array
+ 						ifTrue: ['arg must be of class Array']
+ 						ifFalse: ['receiver and argument must have the same size'])].
+ 	ec == #'inappropriate operation' ifTrue:
+ 		[^self error: 'can''t become immediates such as SmallIntegers or Characters'].
+ 	ec == #'no modification' ifTrue:
+ 		[^self error: 'can''t become immutable objects'].
+ 	ec == #'object is pinned' ifTrue:
+ 		[^self error: 'can''t become pinned objects'].
+ 	ec == #'insufficient object memory' ifTrue:
+ 		[Smalltalk garbageCollect < 1048576 ifTrue:
+ 			[Smalltalk growMemoryByAtLeast: 1048576].
+ 		 ^self elementsForwardIdentityTo: otherArray].
  	self primitiveFailed!

Item was changed:
  ----- Method: SpurBootstrapPrototypes>>ArrayPROTOTYPEelementsForwardIdentityTo:copyHash: (in category 'method prototypes') -----
  ArrayPROTOTYPEelementsForwardIdentityTo: otherArray copyHash: copyHash
  	"This primitive performs a bulk mutation, causing all pointers to the elements of the
  	 receiver to be replaced by pointers to the corresponding elements of otherArray.
  	 If copyHash is true, the identityHashes remain with the pointers rather than with the
  	 objects so that the objects in the receiver should still be properly indexed in any
  	 existing hashed structures after the mutation.  If copyHash is false, then the hashes
  	 of the objects in otherArray remain unchanged.  If you know what you're doing this
  	 may indeed be what you want."
  	<primitive: 249 error: ec>
+ 	ec == #'bad receiver' ifTrue:
+ 		[^self error: 'receiver must be of class Array'].
+ 	ec == #'bad argument' ifTrue:
+ 		[^self error: (otherArray class == Array
+ 						ifTrue: ['arg must be of class Array']
+ 						ifFalse: ['receiver and argument must have the same size'])].
+ 	ec == #'inappropriate operation' ifTrue:
+ 		[^self error: 'can''t become immediates such as SmallIntegers or Characters'].
+ 	ec == #'no modification' ifTrue:
+ 		[^self error: 'can''t become immutable objects'].
+ 	ec == #'object is pinned' ifTrue:
+ 		[^self error: 'can''t become pinned objects'].
+ 	ec == #'insufficient object memory' ifTrue:
+ 		[Smalltalk garbageCollect < 1048576 ifTrue:
+ 			[Smalltalk growMemoryByAtLeast: 1048576].
+ 		 ^self elementsForwardIdentityTo: otherArray copyHash: copyHash].
  	self primitiveFailed!

Item was changed:
  ----- Method: SpurBootstrapSqueakFamilyPrototypes>>InstructionPrinterPROTOTYPEcallPrimitive: (in category 'method prototypes') -----
  InstructionPrinterPROTOTYPEcallPrimitive: index
+ 	"Print the callPrimitive bytecode."
- 	"Print the callPrimitive."
  
+ 	self print: 'callPrimitive: ' , index printString!
- 	self print: 'callPrimtive: ' , index printString!



More information about the Vm-dev mailing list