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

commits at source.squeak.org commits at source.squeak.org
Fri Sep 6 00:16:58 UTC 2013


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

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

Name: Cog-eem.72
Author: eem
Time: 5 September 2013, 5:16:44.576 pm
UUID: 54b8e936-886e-42ec-8e5e-3442901c6107
Ancestors: Cog-eem.71

Map class format (instSpec) from old to new encoding.

Add to the class side of SpurBootstrap prototypes for image
methods that must change to function with the new image format.

Next step is for the bootstrap to install these methods appropriately.

=============== Diff against Cog-eem.71 ===============

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEidentityHash (in category 'method prototypes') -----
+ BehaviorPROTOTYPEidentityHash
+ 	"Answer a SmallInteger whose value is related to the receiver's identity.
+ 	This method must not be overridden.
+ 	Primitive. Fails if the receiver is not a Behavior. Essential.
+ 	See Object documentation whatIsAPrimitive.
+ 
+ 	Do not override."
+ 
+ 	<primitive: 175>
+ 	self primitiveFailed!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEinstSize (in category 'method prototypes') -----
+ BehaviorPROTOTYPEinstSize
+ 	"Answer the number of named instance variables
+ 	(as opposed to indexed variables) of the receiver.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>"
+ 	^format bitAnd: 16rFFFF!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEisBits (in category 'method prototypes') -----
+ BehaviorPROTOTYPEisBits
+ 	"Answer whether the receiver contains just bits (not pointers).
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 		 0 = 0 sized objects (UndefinedObject True False et al)
+ 		 1 = non-indexable objects with inst vars (Point et al)
+ 		 2 = indexable objects with no inst vars (Array et al)
+ 		 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		 4 = weak indexable objects with inst vars (WeakArray et al)
+ 		 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		 6,7,8 unused
+ 		 9 (?) 64-bit indexable
+ 		 10 - 11 32-bit indexable
+ 		 12 - 15 16-bit indexable
+ 		 16 - 23 byte indexable
+ 		 24 - 31 compiled method"
+ 	^self instSpec >= 9!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEisBytes (in category 'method prototypes') -----
+ BehaviorPROTOTYPEisBytes
+ 	"Answer whether the receiver has 8-bit instance variables.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 		 0 = 0 sized objects (UndefinedObject True False et al)
+ 		 1 = non-indexable objects with inst vars (Point et al)
+ 		 2 = indexable objects with no inst vars (Array et al)
+ 		 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		 4 = weak indexable objects with inst vars (WeakArray et al)
+ 		 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		 6,7,8 unused
+ 		 9 (?) 64-bit indexable
+ 		 10 - 11 32-bit indexable
+ 		 12 - 15 16-bit indexable
+ 		 16 - 23 byte indexable
+ 		 24 - 31 compiled method"
+ 	^self instSpec >= 16!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEisVariable (in category 'method prototypes') -----
+ BehaviorPROTOTYPEisVariable
+ 	"Answer whether the receiver has indexable variables.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 		 0 = 0 sized objects (UndefinedObject True False et al)
+ 		 1 = non-indexable objects with inst vars (Point et al)
+ 		 2 = indexable objects with no inst vars (Array et al)
+ 		 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		 4 = weak indexable objects with inst vars (WeakArray et al)
+ 		 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		 6,7,8 unused
+ 		 9 (?) 64-bit indexable
+ 		 10 - 11 32-bit indexable
+ 		 12 - 15 16-bit indexable
+ 		 16 - 23 byte indexable
+ 		 24 - 31 compiled method"
+ 	| instSpec |
+ 	instSpec := self instSpec.
+ 	^instSpec >= 2 and: [instSpec ~= 5]!

Item was added:
+ ----- Method: SpurBootstrap class>>CharacterPROTOTYPEasciiValue (in category 'method prototypes') -----
+ CharacterPROTOTYPEasciiValue
+ 	<primitive: 171>
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: SpurBootstrap class>>CharacterclassPROTOTYPEvalue: (in category 'method prototypes') -----
+ CharacterclassPROTOTYPEvalue: anInteger
+ 	<primitive: 170>
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: SpurBootstrap class>>ClassBuilderPROTOTYPEformat:variable:words:pointers:weak: (in category 'method prototypes') -----
+ ClassBuilderPROTOTYPEformat: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
+ 	"Compute the format for the given instance specfication.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 		 0 = 0 sized objects (UndefinedObject True False et al)
+ 		 1 = non-indexable objects with inst vars (Point et al)
+ 		 2 = indexable objects with no inst vars (Array et al)
+ 		 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 		 4 = weak indexable objects with inst vars (WeakArray et al)
+ 		 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 		 6,7,8 unused
+ 		 9 (?) 64-bit indexable
+ 		 10 - 11 32-bit indexable
+ 		 12 - 15 16-bit indexable
+ 		 16 - 23 byte indexable
+ 		 24 - 31 compiled method"
+ 	| instSpec |
+ 	instSpec := isWeak
+ 					ifTrue: [4]
+ 					ifFalse:
+ 						[isPointers
+ 							ifTrue:
+ 								[isVar
+ 									ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
+ 									ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
+ 							ifFalse: [isWords ifTrue: [12] ifFalse: [16]]].
+ 	^instSpec << 16 + nInstVars!

Item was added:
+ ----- Method: SpurBootstrap class>>ProtoObjectPROTOTYPEscaledIdentityHash (in category 'method prototypes') -----
+ ProtoObjectPROTOTYPEscaledIdentityHash
+ 	"For identityHash values returned by primitive 75, answer
+ 	 such values times 2^18.  Otherwise, match the existing
+ 	 identityHash implementation"
+ 
+ 	^self identityHash * 256 "bitShift: 8"!

Item was added:
+ ----- Method: SpurBootstrap class>>SmallIntegerPROTOTYPEasCharacter (in category 'method prototypes') -----
+ SmallIntegerPROTOTYPEasCharacter
+ 	<primitive: 170>
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: SpurBootstrap class>>SmalltalkImagePROTOTYPEmaxIdentityHash (in category 'method prototypes') -----
+ SmalltalkImagePROTOTYPEmaxIdentityHash
+ 	"Answer the maximum identityHash value supported by the VM."
+ 	<primitive: 176>
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: SpurBootstrap class>>SystemDictionaryPROTOTYPEmaxIdentityHash (in category 'method prototypes') -----
+ SystemDictionaryPROTOTYPEmaxIdentityHash
+ 	"Answer the maximum identityHash value supported by the VM."
+ 	<primitive: 176>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: SpurBootstrap>>allocateClassTable (in category 'bootstrap') -----
  allocateClassTable
  	"Allocate the root of the classTable plus enough pages to accomodate all classes in
+ 	 the classToIndex map.  Don't fill in the entries yet; the classes have yet to be cloned."
- 	 the classToIndex map.  Don;t fill in the entries yet; the classes have yet to be cloned."
  	| tableRootSize tableRoot page maxSize numPages |
  	tableRootSize := self classTableSize / newHeap classTablePageSize.
  	tableRoot := newHeap
  					allocateSlots: tableRootSize
  					format: newHeap arrayFormat
  					classIndex: newHeap arrayClassIndexPun.
  	self assert: (newHeap numSlotsOf: tableRoot) = tableRootSize.
  	self assert: (newHeap formatOf: tableRoot) = newHeap arrayFormat.
  	self assert: (newHeap classIndexOf: tableRoot) = newHeap arrayClassIndexPun.
  	newHeap nilFieldsOf: tableRoot.
  	"first page is strong"
  	page := newHeap
  					allocateSlots: newHeap classTablePageSize
  					format: newHeap arrayFormat
  					classIndex: newHeap arrayClassIndexPun.
  	self assert: (newHeap numSlotsOf: page) = newHeap classTablePageSize.
  	self assert: (newHeap formatOf: tableRoot) = newHeap arrayFormat.
  	self assert: (newHeap classIndexOf: tableRoot) = newHeap arrayClassIndexPun.
+ 	self assert: (newHeap objectAfter: tableRoot limit: newHeap freeStart) = page.
- 	self assert: (newHeap objectAfter: tableRoot limit: newHeap freeStart) = page..
  	lastClassTablePage := page.
  	newHeap nilFieldsOf: page.
  	newHeap storePointer: 0 ofObject: tableRoot withValue: page.
  	newHeap classTableRootObj: tableRoot.
  	maxSize := classToIndex inject: 0 into: [:a :b| a max: b].
  	numPages := (maxSize + newHeap classTableMinorIndexMask / newHeap classTablePageSize) truncated.
  	2 to: numPages do:
  		[:i|
  		page := newHeap
  					allocateSlots: newHeap classTablePageSize
  					format: newHeap weakArrayFormat
  					classIndex: newHeap weakArrayClassIndexPun.
  		self assert: (newHeap numSlotsOf: page) = newHeap classTablePageSize.
  		self assert: (newHeap formatOf: page) = newHeap weakArrayFormat.
  		self assert: (newHeap classIndexOf: page) = newHeap weakArrayClassIndexPun.
  		newHeap nilFieldsOf: page.
  		newHeap storePointer: i - 1 ofObject: tableRoot withValue: page.
  		self assert: (newHeap objectAfter: (newHeap fetchPointer: i - 2 ofObject: tableRoot)  limit: newHeap freeStart) = page.
  		lastClassTablePage := page]!

Item was changed:
  ----- Method: SpurBootstrap>>fillInPointerObject:from: (in category 'bootstrap') -----
  fillInPointerObject: newObj from: oldObj
  	0 to: (oldHeap lastPointerOf: oldObj) / oldHeap bytesPerWord - 1 do:
  		[:i| | oldValue newValue |
  		oldValue := oldHeap fetchPointer: i ofObject: oldObj.
  		newValue := (oldHeap isIntegerObject: oldValue)
  						ifTrue: [oldValue]
  						ifFalse:
  							[map at: oldValue ifAbsent:
  								[oldValue = oldHeap characterTable
  									ifTrue: [newHeap nilObject]
  									ifFalse:
  										[self assert: (oldHeap fetchClassOfNonImm: oldValue) = oldHeap classCharacter.
  										 newHeap characterObjectOf:
  											(oldHeap integerValueOf:
  												(oldHeap fetchPointer: CharacterValueIndex ofObject: oldValue))]]].
  		newHeap
  			storePointerUnchecked: i
  			ofObject: newObj
+ 			withValue: newValue].
+ 	(classToIndex includesKey: oldObj) ifTrue:
+ 		[newHeap
+ 			storePointerUnchecked: InstanceSpecificationIndex
+ 			ofObject: newObj
+ 			withValue: (self newClassFormatFor: oldObj)]!
- 			withValue: newValue]!

Item was added:
+ ----- Method: SpurBootstrap>>newClassFormatFor: (in category 'bootstrap') -----
+ newClassFormatFor: oldClassObj
+ 	"OLD: 		<2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
+ 	 NEW: 		<5 bits inst spec><16 bits inst size>"
+ 	| oldFormat instSize newInstSpec |
+ 	oldFormat := oldHeap formatOfClass: oldClassObj. "N.B. SmallInteger with tag bit cleared"
+ 	oldFormat := oldFormat >> 1.
+ 	instSize := ((oldFormat bitShift: -10) bitAnd: 16rC0) + ((oldFormat bitShift: -1) bitAnd: 16r3F) - 1.
+ 	newInstSpec := #(0 1 2 3 4 5 6 7 16 16 16 16 24 24 24 24) at: ((oldFormat bitShift: -7) bitAnd: 16rF) + 1.
+ 	^newHeap integerObjectOf: newInstSpec << 16 + instSize!



More information about the Vm-dev mailing list