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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 3 22:07:30 UTC 2013


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

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

Name: VMMaker.oscog-eem.345
Author: eem
Time: 3 September 2013, 3:04:58.943 pm
UUID: f2561367-9c5d-4639-826b-6957ffa55c9f
Ancestors: VMMaker.oscog-eem.344

Add more protocol to SpurMemoryManager.  Bootstrap launch now
gets to goodContextSize: in StackInterpreter>>loadInitialContext:.

This now needs a change to the base code since Large/SmallContextSize
includes baseheaderSize, and SpurMemoryManager baseHeaderSize
~= ObjectMemory baseHeaderSize.

Start replacing some is(Non)IntegerObject:'s with is(Non)Immediate:,
specifically in StackInterpreter>>isSingleContext:.

Make sure all initializeCompactClassIndices initialize all compact
class indices ;).

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

Item was changed:
  ----- Method: NewspeakInterpreter class>>initializeCompactClassIndices (in category 'initialization') -----
  initializeCompactClassIndices
  	"Initialize indices for compact classes we are going to depend on being compact.
  	 The VI allows classes to become compact and become uncompact.  For efficiency
  	 the VM assumes certain classes are compact with particular indices."
  
  	"Smalltalk compactClassesArray"
  	"{Array. LargePositiveInteger. Float. MethodContext. } collect: [:c| c -> c indexIfCompact]"
  
  	ClassArrayCompactIndex := 3.
  	ClassLargeNegativeIntegerCompactIndex := 0. "Currently PseudoContext class"
  	ClassLargePositiveIntegerCompactIndex := 5.
  	ClassFloatCompactIndex := 6.
+ 	ClassBlockClosureCompactIndex := 0 "12". "Prospective.  May still be TranslatedMethod class"
- 	ClassBlockClosureCompactIndex := 0 "12". "Prospective.  Currently TranslatedMethod class"
  	ClassByteStringCompactIndex := 11.
  	ClassBlockContextCompactIndex := 13.
+ 	ClassMethodContextCompactIndex := 14.
+ 
+ 	ClassByteArrayCompactIndex := 0.
+ 	ClassMessageCompactIndex := 0.
+ 	ClassBitmapCompactIndex := 0!
- 	ClassMethodContextCompactIndex := 14!

Item was changed:
  ----- Method: ObjectMemory class>>initializeCompactClassIndices (in category 'initialization') -----
  initializeCompactClassIndices
  	"Initialize indices for compact classes we are going to depend on being compact.
  	 The VI allows classes to become compact and become uncompact.  For efficiency
  	 the VM assumes certain classes are compact with particular indices."
  
  	"Smalltalk compactClassesArray"
  	"{Array. LargePositiveInteger. Float. MethodContext. } collect: [:c| c -> c indexIfCompact]"
  
  	ClassArrayCompactIndex := 3.
  	ClassLargeNegativeIntegerCompactIndex := 4. "Was PseudoContext class"
  	ClassLargePositiveIntegerCompactIndex := 5.
  	ClassFloatCompactIndex := 6.
+ 	ClassBlockClosureCompactIndex := 0 "12". "Prospective.  May still be TranslatedMethod class"
- 	ClassBlockClosureCompactIndex := 0 "12". "Prospective.  Currently TranslatedMethod class"
  	ClassByteStringCompactIndex := 11.
  	ClassBlockContextCompactIndex := 13.
+ 	ClassMethodContextCompactIndex := 14.
+ 
+ 	ClassByteArrayCompactIndex := 0.
+ 	ClassMessageCompactIndex := 0.
+ 	ClassBitmapCompactIndex := 0!
- 	ClassMethodContextCompactIndex := 14!

Item was added:
+ ----- Method: ObjectMemory>>isImmediate: (in category 'interpreter access') -----
+ isImmediate: anOop
+ 	^self isIntegerObject: anOop!

Item was added:
+ ----- Method: ObjectMemory>>isNonImmediate: (in category 'interpreter access') -----
+ isNonImmediate: anOop
+ 	^self isNonIntegerObject: anOop!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>byteAt: (in category 'memory access') -----
+ byteAt: byteAddress
+ 	| lowBits long |
+ 	lowBits := byteAddress bitAnd: 3.
+ 	long := self longAt: byteAddress - lowBits.
+ 	^(lowBits caseOf: {
+ 		[0] -> [ long ].
+ 		[1] -> [ long bitShift: -8  ].
+ 		[2] -> [ long bitShift: -16 ].
+ 		[3] -> [ long bitShift: -24 ]
+ 	}) bitAnd: 16rFF!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>isNonImmediate: (in category 'object testing') -----
+ isNonImmediate: oop 
+ 	^(oop bitAnd: 3) = 0!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>isNonImmediate: (in category 'object testing') -----
+ isNonImmediate: oop 
+ 	^(oop bitAnd: 7) = 0!

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

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeCompactClassIndices (in category 'class initialization') -----
  initializeCompactClassIndices
  	"Reuse the compact class indices to name known classIndices.
  	 This helps reduce the churn in the interpreters."
  	"c.f. SpurBootstrap>>defineKnownClassIndices"
  	ClassLargeNegativeIntegerCompactIndex := 32.
  	ClassLargePositiveIntegerCompactIndex := 33.
  	ClassFloatCompactIndex := 34.
  
  	ClassMessageCompactIndex := 35.
  	ClassMethodContextCompactIndex := 36.
+ 	ClassBlockContextCompactIndex := 0.
  	ClassBlockClosureCompactIndex := 37.
  
  	ClassByteArrayCompactIndex := 50.
  	ClassArrayCompactIndex := 51.
  	ClassByteStringCompactIndex := 52.
  	ClassBitmapCompactIndex := 53!

Item was changed:
  ----- Method: SpurMemoryManager>>classAtIndex: (in category 'class table') -----
  classAtIndex: classIndex
+ 	| classTablePage |
+ 	classTablePage := self fetchPointer: classIndex >> self classTableMajorIndexShift
+ 							ofObject: classTableRootObj.
+ 	^self
+ 		fetchPointer: (classIndex bitAnd: self classTableMinorIndexMask)
+ 		ofObject: classTablePage!
- 	| majorIndex minorIndex page |
- 	majorIndex := classIndex >> self classTableMajorIndexShift.
- 	minorIndex := classIndex bitAnd: self classTableMinorIndexMask.
- 	self assert: (majorIndex between: 0 and: (self numSlotsOf: classTableRootObj) - 1).
- 	page := self fetchPointer: majorIndex ofObject: classTableRootObj.
- 	^self fetchPointer: minorIndex ofObject: page!

Item was added:
+ ----- Method: SpurMemoryManager>>compactIndexOfClass: (in category 'class membership') -----
+ compactIndexOfClass: objOop
+ 	^self hashBitsOf: objOop!

Item was added:
+ ----- Method: SpurMemoryManager>>fetchClassOfNonInt: (in category 'object access') -----
+ fetchClassOfNonInt: objOop 
+ 	| classIndex |
+ 	classIndex := self classIndexOf: objOop.
+ 	^self classAtIndex: classIndex!

Item was added:
+ ----- Method: SpurMemoryManager>>firstByteFormat (in category 'header format') -----
+ firstByteFormat
+ 	^16!

Item was added:
+ ----- Method: SpurMemoryManager>>firstFixedField: (in category 'object access') -----
+ firstFixedField: objOop
+ 	<returnTypeC: #'void *'>
+ 	^ self pointerForOop: objOop + self baseHeaderSize!

Item was added:
+ ----- Method: SpurMemoryManager>>firstLongFormat (in category 'header format') -----
+ firstLongFormat
+ 	^10!

Item was added:
+ ----- Method: SpurMemoryManager>>firstShortFormat (in category 'header format') -----
+ firstShortFormat
+ 	^12!

Item was changed:
  ----- Method: SpurMemoryManager>>formatMask (in category 'header format') -----
  formatMask
+ 	"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"
  	^16r1f!

Item was added:
+ ----- Method: SpurMemoryManager>>hashBitsOf: (in category 'header access') -----
+ hashBitsOf: objOop
+ 	self flag: #endianness.
+ 	^(self longAt: objOop) bitAnd: self identityHashHalfWordMask!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
+ 	freeLists := CArrayAccessor on: (Array new: NumFreeLists withAll: 0).
+ 	checkForLeaks := 0.
+ 	needGCFlag := false.
+ 	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new]!
- 	freeLists := CArrayAccessor on: (Array new: NumFreeLists withAll: 0)!

Item was added:
+ ----- Method: SpurMemoryManager>>isBytes: (in category 'object testing') -----
+ isBytes: oop
+ 	"Answer true if the argument contains indexable bytes. See comment in formatOf:"
+ 	"Note: Includes CompiledMethods."
+ 	^(self isNonImmediate: oop) and: [self isBytesNonImm: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>isBytesNonImm: (in category 'object testing') -----
+ isBytesNonImm: objOop
+ 	"Answer true if the argument contains indexable bytes. See comment in formatOf:"
+ 	^(self formatOf: objOop) >= self firstByteFormat!

Item was added:
+ ----- Method: SpurMemoryManager>>isNonImmediate: (in category 'object testing') -----
+ isNonImmediate: oop 
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>leakCheckFullGC (in category 'debug support') -----
+ leakCheckFullGC
+ 	<api>
+ 	^(checkForLeaks bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>lengthOf: (in category 'object access') -----
+ lengthOf: objOop
+ 	"Answer the number of indexable bytes or words in the given object.
+ 	 For a CompiledMethod, the size of the method header (in bytes) should be subtracted from the result."
+ 
+ 	<api>
+ 	| header |
+ 	<var: #header type: #usqLong>
+ 	<inline: true>
+ 	<asmLabel: false> 
+ 	header := self baseHeader: objOop.
+ 	^self lengthOf: objOop baseHeader: header format: (self formatOfHeader: header)!

Item was added:
+ ----- Method: SpurMemoryManager>>lengthOf:baseHeader:format: (in category 'object access') -----
+ lengthOf: objOop baseHeader: header format: fmt 
+ 	<var: #header type: #usqLong>
+ 	"Compatibility; does not really suit the Spur format.
+ 	 Answer the number of indexable bytes or words in the given object.
+ 	 For a CompiledMethod, the size of the method header (in bytes) should
+ 	 be subtracted from the result of this method."
+ 	| numSlots |
+ 	<inline: true>
+ 	<asmLabel: false> 
+ 	numSlots := self numSlotsOf: objOop.
+ 	fmt <= self sixtyFourBitIndexableFormat ifTrue:
+ 		[^numSlots].
+ 	fmt >= self firstByteFormat ifTrue: "bytes, including CompiledMethod"
+ 		[^numSlots << self shiftForWord - (fmt bitAnd: 7)].
+ 	fmt >= self firstShortFormat ifTrue:
+ 		[^numSlots << (self shiftForWord - 1) - (fmt bitAnd: 3)].
+ 	"fmt >= self firstLongFormat"
+ 	^numSlots << (self shiftForWord - 1) - (fmt bitAnd: 1)!

Item was added:
+ ----- Method: SpurMemoryManager>>sixtyFourBitIndexableFormat (in category 'header format') -----
+ sixtyFourBitIndexableFormat
+ 	^9!

Item was added:
+ ----- Method: SpurMemoryManager>>sizeBitsOf: (in category 'object access') -----
+ sizeBitsOf: objOop
+ 	"Answer the number of bytes in the given object, including its base header, rounded up to an integral number of words.
+ 	 Hence, were it not for the fact that zero-sized objects have at least room for a forwarding pointer,
+ 	 objOop + (self sizeBitsOf: objOop) is the address immediately following objOop."
+ 	"Note: byte indexable objects need to have low bits subtracted from this size to find the address beyond the last byte."
+ 	^(self numSlotsOf: objOop) << self shiftForWord + self baseHeaderSize!

Item was changed:
  ----- Method: StackInterpreter>>isSingleContext: (in category 'frame access') -----
  isSingleContext: aContext
+ 	^objectMemory isNonImmediate: (objectMemory fetchPointer: SenderIndex ofObject: aContext)!
- 	^objectMemory isNonIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)!



More information about the Vm-dev mailing list