VM Maker: VMMaker.oscog-eem.364.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.364.mcz

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

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

Name: VMMaker.oscog-eem.364
Author: eem
Time: 10 September 2013, 3:42:08.277 pm
UUID: 2a628f01-d6c9-449e-83a4-f5a861f30d46
Ancestors: VMMaker.oscog-eem.363

Implement store check and hence define isRemembered bit as bit 29.

Impement SpurMemoryManager>>eeInstantiateClassIndex:format:numSlots:.

More isIntegerObject: => isImmediate:.

Spur image now runs to primitiveBeCursor (1929 bytecodes in my
test image), which fails.

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

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>byteAt:put: (in category 'memory access') -----
+ byteAt: byteAddress put: byte
+ | lowBits long longAddress |
+ lowBits := byteAddress bitAnd: 3.
+ longAddress := byteAddress - lowBits.
+ long := self longAt: longAddress.
+ long := (lowBits caseOf: {
+ [0] -> [ (long bitAnd: 16rFFFFFF00) bitOr: byte ].
+ [1] -> [ (long bitAnd: 16rFFFF00FF) bitOr: (byte bitShift: 8) ].
+ [2] -> [ (long bitAnd: 16rFF00FFFF) bitOr: (byte bitShift: 16)  ].
+ [3] -> [ (long bitAnd: 16r00FFFFFF) bitOr: (byte bitShift: 24)  ]
+ }).
+ self assert: (self cheapAddressCouldBeObj: longAddress).
+ self longAt: longAddress put: long.
+ ^byte!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>long32At: (in category 'memory access') -----
+ long32At: byteAddress
+ "Answer the 32-bit word at byteAddress which must be 0 mod 4."
+
+ ^self longAt: byteAddress!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>isWordsNonImm: (in category 'header access') -----
+ isWordsNonImm: objOop
+ "Answer if the argument contains only indexable words (no oops). See comment in formatOf:"
+
+ ^(self formatOf: objOop) = self firstLongFormat!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>isWordsNonImm: (in category 'header access') -----
+ isWordsNonImm: objOop
+ "Answer if the argument contains only indexable words (no oops). See comment in formatOf:"
+
+ ^(self formatOf: objOop) between: self firstLongFormat and: self firstLongFormat + 1!

Item was changed:
  VMClass subclass: #SpurGenerationScavenger
  instanceVariableNames: 'coInterpreter manager memory eden futureSpace pastSpace rememberedSet rememberedSetSize'
+ classVariableNames: 'RememberedSetLimit RememberedSetRedZone'
- classVariableNames: ''
  poolDictionaries: ''
  category: 'VMMaker-SpurMemoryManager'!

Item was added:
+ ----- Method: SpurGenerationScavenger class>>initialize (in category 'class initialization') -----
+ initialize
+ "SpurGenerationScavenger initialize"
+ RememberedSetLimit := 4096.
+ RememberedSetRedZone := 1024 * 3!

Item was added:
+ ----- Method: SpurGenerationScavenger>>initialize (in category 'initialization') -----
+ initialize
+ rememberedSet := CArrayAccessor on: (Array new: RememberedSetLimit).
+ rememberedSetSize := 0!

Item was added:
+ ----- Method: SpurGenerationScavenger>>remember: (in category 'store check') -----
+ remember: objOop
+ rememberedSetSize < RememberedSetLimit
+ ifTrue:
+ [rememberedSet at: rememberedSetSize put: objOop.
+ (rememberedSetSize := rememberedSetSize + 1) >= RememberedSetRedZone ifTrue:
+ [manager scheduleScavenge]]
+ ifFalse:
+ [self error: 'remembered set overflow' "for now"]!

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

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionary
  "SpurMemoryManager initializeWithOptions: Dictionary new"
 
  self initBytesPerWord: (self == SpurMemoryManager
  ifTrue: [optionsDictionary at: #BytesPerWord ifAbsent: [4]]
  ifFalse: [self wordSize]).
  BytesPerOop := optionsDictionary at: #BytesPerOop ifAbsent: [BytesPerWord].
 
  self initializeSpecialObjectIndices.
  self initializeCompactClassIndices.
  self initializePrimitiveErrorCodes.
+ self initializeObjectHeaderConstants.
+
+ SpurGenerationScavenger initialize!
- self initializeObjectHeaderConstants!

Item was added:
+ ----- Method: SpurMemoryManager>>cheapAddressCouldBeObj: (in category 'debug support') -----
+ cheapAddressCouldBeObj: address
+ ^(address bitAnd: self baseHeaderSize - 1) = 0
+  and: [address >= scavenger eden start
+  and: [address <= freeOldSpaceStart]]!

Item was added:
+ ----- Method: SpurMemoryManager>>eeInstantiateClassIndex:format:numSlots: (in category 'allocation') -----
+ eeInstantiateClassIndex: knownClassIndex format: objFormat numSlots: numSlots
+ "Instantiate an instance of a compact class.  ee stands for execution engine and
+ implies that this allocation will *NOT* cause a GC.  N.B. the instantiated object
+ IS NOT FILLED and must be completed before returning it to Smalltalk. Since this
+ call is used in routines that do just that we are safe.  Break this rule and die in GC."
+ <inline: true>
+ self assert: (numSlots > 0 and: [knownClassIndex ~= 0]).
+ self assert: (objFormat < self firstByteFormat
+ ifTrue: [objFormat]
+ ifFalse: [objFormat bitAnd: self byteFormatMask])
+ = (self instSpecOfClass: (self knownClassAtIndex: knownClassIndex)).
+ ^self allocateSlots: numSlots format: objFormat classIndex: knownClassIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>headerForSlots:format:classIndex: (in category 'header format') -----
  headerForSlots: numSlots format: formatField classIndex: classIndex
  "The header format in LSB is
  MSB: | 8: numSlots | (on a byte boundary)
  | 2 bits |
  | 22: identityHash | (on a word boundary)
+ | 3 bits | (msb <-> lsb = ?,?,isRemembered
- | 3 bits |
  | 5: format | (on a byte boundary)
  | 2 bits |
  | 22: classIndex | (on a word boundary) : LSB
  The remaining bits (7) need to be used for
  isGrey
  isMarked
+ isRemembered (bit 29)
- isRemembered
  isPinned
  isImmutable
  leaving 2 unused bits."
  <returnTypeC: #usqLong>
  ^ (numSlots << self numSlotsFullShift)
  + (formatField << self formatShift)
  + classIndex!

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

Item was added:
+ ----- Method: SpurMemoryManager>>instSpecOfClass: (in category 'object format') -----
+ instSpecOfClass: classPointer
+ "This is the same as the field stored in every object header"
+
+ ^self instSpecOfClassFormat: (self formatOfClass: classPointer)!

Item was changed:
  ----- Method: SpurMemoryManager>>isIntegerObject: (in category 'object testing') -----
  isIntegerObject: oop
+ "This list records the valid senders of isIntegerObject: as we replace uses of
+  isIntegerObject: by isImmediate: where appropriate."
  (#( makeBaseFrameFor:
  quickFetchInteger:ofObject:
  frameOfMarriedContext:
  addressCouldBeClassObj:
  isMarriedOrWidowedContext:
  shortPrint:
  bytecodePrimAt
  commonAt:
  loadFloatOrIntFrom:
  positive32BitValueOf:
  primitiveExternalCall
+ checkedIntegerValueOf:
+ bytecodePrimAtPut
+ commonAtPut:) includes: thisContext sender method selector) ifFalse:
- checkedIntegerValueOf:) includes: thisContext sender method selector) ifFalse:
  [self halt].
  ^(oop bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>isNonIntegerObject: (in category 'object testing') -----
+ isNonIntegerObject: oop
+ "This list records the valid senders of isNonIntegerObject: as we replace uses of
+  isNonIntegerObject: by isNonImmediate: where appropriate."
+ (#() includes: thisContext sender method selector) ifFalse:
+ [self halt].
+ ^(oop bitAnd: 1) = 0!

Item was added:
+ ----- Method: SpurMemoryManager>>isRemembered: (in category 'header access') -----
+ isRemembered: objOop
+ self flag: #endianness.
+ ^((self longAt: objOop) >> self rememberedBitShift bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>isWords: (in category 'object testing') -----
+ isWords: oop
+ "Answer if the argument contains only indexable words (no oops). See comment in formatOf:"
+
+ ^(self isNonImmediate: oop)
+  and: [self isWordsNonImm: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>isWordsNonImm: (in category 'header access') -----
+ isWordsNonImm: objOop
+ "Answer if the argument contains only indexable words (no oops). See comment in formatOf:"
+
+ ^self subclassResponsibility!

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

Item was added:
+ ----- Method: SpurMemoryManager>>possibleRootStoreInto:value: (in category 'store check') -----
+ possibleRootStoreInto: destObj value: valueOop
+ (#( storePointer:ofObject:withValue:) includes: thisContext sender method selector) ifFalse:
+ [self halt].
+ (self isRemembered: destObj) ifFalse:
+ [scavenger remember: destObj.
+ self setIsRememberedOf: destObj to: true]!

Item was added:
+ ----- Method: SpurMemoryManager>>rememberedBitShift (in category 'header format') -----
+ rememberedBitShift
+ "lsb of 3-bit field above format (little endian)"
+ ^29!

Item was added:
+ ----- Method: SpurMemoryManager>>setIsRememberedOf:to: (in category 'header access') -----
+ setIsRememberedOf: objOop to: aBoolean
+ self flag: #endianness.
+ self longAt: objOop
+ put: (aBoolean
+ ifTrue: [(self longAt: objOop) bitOr: 1 << self rememberedBitShift]
+ ifFalse: [(self longAt: objOop) bitAnd: (1 << self rememberedBitShift) bitInvert32])!

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

Item was added:
+ ----- Method: SpurMemoryManager>>storeByte:ofObject:withValue: (in category 'object access') -----
+ storeByte: byteIndex ofObject: oop withValue: valueByte
+ ^self byteAt: oop + BaseHeaderSize + byteIndex put: valueByte!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimAtPut (in category 'common selector sends') -----
  bytecodePrimAtPut
  "BytecodePrimAtPut will only succeed if the receiver is in the atCache.
  Otherwise it will fail so that the more general primitiveAtPut will put it in the
  cache after validating that message lookup results in a primitive response."
  | index rcvr atIx value |
  value := self internalStackTop.
  index := self internalStackValue: 1.
  rcvr := self internalStackValue: 2.
+ ((objectMemory isImmediate: rcvr) not
- ((objectMemory isIntegerObject: rcvr) not
  and: [objectMemory isIntegerObject: index]) ifTrue:
  [atIx := (rcvr bitAnd: AtCacheMask) + AtPutBase.  "Index into atPutCache"
  (atCache at: atIx+AtCacheOop) = rcvr ifTrue:
  [self commonVariable: rcvr at: (objectMemory integerValueOf: index) put: value cacheIndex: atIx.
  self successful ifTrue:
  [self fetchNextBytecode.
  ^self internalPop: 3 thenPush: value].
  self initPrimCall]].
 
  messageSelector := self specialSelector: 17.
  argumentCount := 2.
  self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>commonAtPut: (in category 'indexing primitive support') -----
  commonAtPut: stringy
  "This code is called if the receiver responds primitively to at:Put:.
  If this is so, it will be installed in the atPutCache so that subsequent calls of at:
  or  next may be handled immediately in bytecode primitive routines."
  | value index rcvr atIx |
  value := self stackTop.
  self initPrimCall.
  rcvr := self stackValue: 2.
+ (objectMemory isNonImmediate: rcvr) ifFalse:
- (objectMemory isNonIntegerObject: rcvr) ifFalse:
  [^self primitiveFailFor: PrimErrInappropriate].
  index := self stackValue: 1.
  "No need to test for large positive integers here.  No object has 1g elements"
  (objectMemory isIntegerObject: index) ifFalse:
  [^self primitiveFailFor: PrimErrBadArgument].
  index := objectMemory integerValueOf: index.
 
  "NOTE:  The atPut-cache, since it is specific to the non-super response to #at:Put:.
  Therefore we must determine that the message is #at:Put: (not, eg, #basicAt:Put:),
  and that the send is not a super-send, before using the at-cache."
  (messageSelector = (self specialSelector: 17)
  and: [lkupClass = (objectMemory fetchClassOfNonImm: rcvr)])
  ifTrue:
  ["OK -- look in the at-cache"
  atIx := (rcvr bitAnd: AtCacheMask) + AtPutBase.  "Index into atPutCache"
  (atCache at: atIx+AtCacheOop) = rcvr ifFalse:
  ["Rcvr not in cache.  Attempt to install it..."
  (self install: rcvr inAtCache: atCache at: atIx string: stringy) ifFalse:
  [self assert: (objectMemory isContextNonInt: rcvr).
  self initPrimCall.
  ^self primitiveContextAtPut]].
  self successful ifTrue:
  [self commonVariable: rcvr at: index put: value cacheIndex: atIx].
  self successful ifTrue:
  [^ self pop: argumentCount+1 thenPush: value]].
 
  "The slow but sure way..."
  self initPrimCall.
  stringy
  ifTrue: [self stObject: rcvr at: index put: (self asciiOfCharacter: value)]
  ifFalse: [self stObject: rcvr at: index put: value].
  self successful ifTrue:
  [^ self pop: argumentCount+1 thenPush: value]!