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

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

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

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

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

Name: VMMaker.oscog-eem.724
Author: eem
Time: 20 May 2014, 5:14:34.356 am
UUID: 30e942d9-0d06-42d3-8f9a-893dbdee37c2
Ancestors: VMMaker.oscog-eem.723

Slang/general:
VMBIGENDIAN must *not* be defined during generation.  It
should be taken from platforms/??/vm/sqConfig.h.  This should
go a long way to fixing Doug's issues on PPC.

Spur:
Don't mark on allInstances/allObjects.  Use a class var to
mark the choice so we can turn it back on if desired.

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

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

Item was changed:
  ----- Method: SpurMemoryManager class>>initialize (in category 'class initialization') -----
  initialize
  "SpurMemoryManager initialize"
  BitsPerByte := 8.
 
  "An obj stack is a stack of objects stored in a hidden root slot, such as
  the markStack or the ephemeronQueue.  It is a linked list of segments,
  with the hot end at the head of the list.  It is a word object.  The stack
  pointer is in ObjStackTopx and 0 means empty.  The list goes through
  ObjStackNextx. We don't want to shrink objStacks, since they're used
  in GC and its good to keep their memory around.  So unused pages
  created by popping emptying pages are kept on the ObjStackFreex list.
  ObjStackNextx must be the last field for swizzleObjStackAt:."
  ObjStackPageSlots := 4092. "+ double header = 16k bytes per page in 32-bits"
  ObjStackTopx := 0.
  ObjStackMyx := 1.
  ObjStackFreex := 2.
  ObjStackNextx := 3.
  ObjStackFixedSlots := 4.
  ObjStackLimit := ObjStackPageSlots - ObjStackFixedSlots.
  "There are currently three obj stacks, the mark stack, the weaklings and the ephemeron queue."
  MarkStackRootIndex := self basicNew classTableRootSlots.
  WeaklingStackRootIndex := MarkStackRootIndex + 1.
  EphemeronQueueRootIndex := MarkStackRootIndex + 2.
 
  CheckObjectOverwrite := true.
+ MarkObjectsForEnumerationPrimitives := false.
 
  "The remap buffer support is for compatibility; Spur doesn't GC during allocation.
  Eventually this should die."
  RemapBufferSize := 25.
 
  "Extra roots are for plugin support."
  ExtraRootsSize := 2048 "max. # of external roots"!

Item was changed:
  ----- Method: SpurMemoryManager>>allInstancesOf: (in category 'primitive support') -----
  allInstancesOf: aClass
  "Attempt to answer an array of all objects, excluding those that may
  be garbage collected as a side effect of allocating the result array.
  If no memory is available answer the number of instances as a SmallInteger.
  Since objects are at least 16 bytes big, and the largest SmallInteger covers
  1/4 of the address space, the count can never overflow."
  | classIndex freeChunk ptr start limit count bytes |
  classIndex := self rawHashBitsOf: aClass.
  (classIndex = 0
  or: [aClass ~~ (self classOrNilAtIndex: classIndex)]) ifTrue:
  [freeChunk := self allocateSlots: 0 format: self arrayFormat classIndex: ClassArrayCompactIndex.
  ^freeChunk].
+ MarkObjectsForEnumerationPrimitives ifTrue:
+ [self markObjects]. "may not want to revive objects unnecessarily; but marking is sloooow."
- self markObjects. "don't want to revive objects unnecessarily."
  freeChunk := self allocateLargestFreeChunk.
  ptr := start := freeChunk + self baseHeaderSize.
  limit := self addressAfter: freeChunk.
  count := 0.
  self allHeapEntitiesDo:
  [:obj| "continue enumerating even if no room so as to unmark all objects."
+ (MarkObjectsForEnumerationPrimitives
+ ifTrue: [self isMarked: obj]
+ ifFalse: [true]) ifTrue:
- (self isMarked: obj) ifTrue:
  [(self isNormalObject: obj)
  ifTrue:
+ [MarkObjectsForEnumerationPrimitives ifTrue:
+ [self setIsMarkedOf: obj to: false].
- [self setIsMarkedOf: obj to: false.
  (self classIndexOf: obj) = classIndex ifTrue:
  [count := count + 1.
  ptr < limit ifTrue:
  [self longAt: ptr put: obj.
  ptr := ptr + self bytesPerSlot]]]
  ifFalse:
  [(self isSegmentBridge: obj) ifFalse:
  [self setIsMarkedOf: obj to: false]]]].
  self assert: self allObjectsUnmarked.
  self assert: (self isEmptyObjStack: markStack).
  self emptyObjStack: weaklingStack.
  (count > (ptr - start / self bytesPerSlot) "not enough room"
  or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  [self freeObject: freeChunk.
  ^self integerObjectOf: count].
  count < self numSlotsMask ifTrue:
  [| smallObj |
  smallObj := self allocateSlots: count format: self arrayFormat classIndex: ClassArrayCompactIndex.
  0 to: count - 1 do:
  [:i|
  self storePointerUnchecked: i ofObject: smallObj withValue: (self fetchPointer: i ofObject: freeChunk)].
  self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  self beRootIfOld: smallObj.
  self checkFreeSpace.
  ^smallObj].
  bytes := self largeObjectBytesForSlots: count.
  start := self startOfObject: freeChunk.
  self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  totalFreeOldSpace := totalFreeOldSpace - bytes.
  self setOverflowNumSlotsOf: freeChunk to: count.
  self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  self possibleRootStoreInto: freeChunk.
  self checkFreeSpace.
  self runLeakCheckerForFullGC: false.
  ^freeChunk
 
  !

Item was changed:
  ----- Method: SpurMemoryManager>>allObjects (in category 'primitive support') -----
  allObjects
  "Attempt to answer an array of all objects, excluding those that may
  be garbage collected as a side effect of allocating the result array.
  If no memory is available answer the number of objects as a SmallInteger.
  Since objects are at least 16 bytes big, and the largest SmallInteger covers
  1/4 of the address space, the count can never overflow."
  | freeChunk ptr start limit count bytes |
+ MarkObjectsForEnumerationPrimitives ifTrue:
+ [self markObjects]. "may not want to revive objects unnecessarily; but marking is sloooow."
- self markObjects. "don't want to revive objects unnecessarily."
  freeChunk := self allocateLargestFreeChunk.
  ptr := start := freeChunk + self baseHeaderSize.
  limit := self addressAfter: freeChunk.
  count := 0.
  self allHeapEntitiesDo:
  [:obj| "continue enumerating even if no room so as to unmark all objects."
+ (MarkObjectsForEnumerationPrimitives
+ ifTrue: [self isMarked: obj]
+ ifFalse: [true]) ifTrue:
- (self isMarked: obj) ifTrue:
  [(self isNormalObject: obj)
  ifTrue:
+ [MarkObjectsForEnumerationPrimitives ifTrue:
+ [self setIsMarkedOf: obj to: false].
- [self setIsMarkedOf: obj to: false.
  count := count + 1.
  ptr < limit ifTrue:
  [self longAt: ptr put: obj.
  ptr := ptr + self bytesPerSlot]]
  ifFalse:
  [(self isSegmentBridge: obj) ifFalse:
  [self setIsMarkedOf: obj to: false]]]].
  self assert: self allObjectsUnmarked.
  self assert: (self isEmptyObjStack: markStack).
  self emptyObjStack: weaklingStack.
  self assert: count >= self numSlotsMask.
  (count > (ptr - start / self bytesPerSlot) "not enough room"
  or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  [self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  self checkFreeSpace.
  ^self integerObjectOf: count].
  bytes := self largeObjectBytesForSlots: count.
  start := self startOfObject: freeChunk.
  self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  totalFreeOldSpace := totalFreeOldSpace - bytes.
  self setOverflowNumSlotsOf: freeChunk to: count.
  self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  self possibleRootStoreInto: freeChunk.
  self checkFreeSpace.
  self runLeakCheckerForFullGC: false.
  ^freeChunk
 
  !

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForCogit:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForCogit: cogitClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  "Answer the code generator for translating the cogit."
 
  | cg aClass cogitClasses apicg |
  cg := self createCogitCodeGenerator.
 
  cg vmClass: cogitClass.
  initializeClasses ifTrue:
  [{ cogitClass. self interpreterClass. self interpreterClass objectMemoryClass } do:
  [:cgc|
  (cgc respondsTo: #initializeWithOptions:)
  ifTrue: [cgc initializeWithOptions: optionsDictionary]
  ifFalse: [cgc initialize]]].
 
  cogitClasses := OrderedCollection new.
  aClass := cogitClass.
  [cogitClasses addFirst: aClass.
  aClass ~~ Cogit
  and: [aClass inheritsFrom: Cogit]] whileTrue:
  [aClass := aClass superclass].
  cogitClasses addFirst: VMClass.
  cogitClasses addAllLast: ((cogitClass ancilliaryClasses: optionsDictionary) reject: [:class| class isStructClass]).
  cogitClasses do: [:cgc| cg addClass: cgc].
  cg addStructClasses: (cg structClassesForTranslationClasses: cogitClasses).
 
  getAPIMethods ifTrue:
  [apicg := self
  buildCodeGeneratorForInterpreter: self interpreterClass
  includeAPIMethods: false
  initializeClasses: false.
  cg apiMethods: apicg selectAPIMethods].
 
+ cg removeConstant: #VMBIGENDIAN. "this should be defined in platforms/??/vm/sqConfig.h"
+
  ^cg!

Item was changed:
  ----- Method: VMMaker>>buildCodeGeneratorForInterpreter:includeAPIMethods:initializeClasses: (in category 'generate sources') -----
  buildCodeGeneratorForInterpreter: interpreterClass includeAPIMethods: getAPIMethods initializeClasses: initializeClasses
  "Answer the code generator for translating the interpreter."
 
  | cg theClass interpreterClasses apicg |
  interpreterClasses := OrderedCollection new.
 
  initializeClasses ifTrue:
  [interpreterClass initializeWithOptions: optionsDictionary].
 
  (cg := self createCodeGenerator) vmClass: interpreterClass.
 
  theClass := interpreterClass.
  [theClass ~~ VMClass] whileTrue:
  [interpreterClasses addFirst: theClass.
  theClass := theClass superclass].
 
  cg vmClass objectMemoryClass ifNotNil:
  [:objectMemoryClass|
  theClass := objectMemoryClass.
  [theClass ~~ VMClass] whileTrue:
  [interpreterClasses addFirst: theClass.
  theClass := theClass superclass]].
 
  interpreterClasses addFirst: VMClass.
  interpreterClasses addAllLast: (cg nonStructClassesForTranslationClasses: interpreterClasses).
 
  initializeClasses ifTrue:
  [interpreterClasses do:
  [:ic|
  (ic respondsTo: #initializeWithOptions:)
  ifTrue: [ic initializeWithOptions: optionsDictionary]
  ifFalse: [ic initialize]].
  (cg structClassesForTranslationClasses: interpreterClasses) do:
  [:structClass| structClass initialize]].
 
  cg addStructClasses: (cg structClassesForTranslationClasses: interpreterClasses).
 
  interpreterClasses do: [:ic| cg addClass: ic].
 
  (getAPIMethods
  and: [self interpreterClass needsCogit]) ifTrue:
  [apicg := self
  buildCodeGeneratorForCogit: self cogitClass
  includeAPIMethods: false
  initializeClasses: false.
  cg apiMethods: apicg selectAPIMethods].
 
+ cg removeConstant: #VMBIGENDIAN. "this should be defined in platforms/??/vm/sqConfig.h"
+
  ^cg!

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.724.mcz

David T. Lewis
 
On Tue, May 20, 2014 at 12:15:35PM +0000, [hidden email] wrote:

>  
> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.724.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-eem.724
> Author: eem
> Time: 20 May 2014, 5:14:34.356 am
> UUID: 30e942d9-0d06-42d3-8f9a-893dbdee37c2
> Ancestors: VMMaker.oscog-eem.723
>
> Slang/general:
> VMBIGENDIAN must *not* be defined during generation.  It
> should be taken from platforms/??/vm/sqConfig.h.  This should
> go a long way to fixing Doug's issues on PPC.
>

For sure VMBIGENDIAN should not be generated from slang. But more generally,
it is available at runtime via Interpreter>>isBigEnder, so the declaration
in sqConfig.h should not be required either.

Dave

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-eem.724.mcz

Eliot Miranda-2
 
Hi David,


On Tue, May 20, 2014 at 4:03 PM, David T. Lewis <[hidden email]> wrote:

On Tue, May 20, 2014 at 12:15:35PM +0000, [hidden email] wrote:
>
> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.724.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-eem.724
> Author: eem
> Time: 20 May 2014, 5:14:34.356 am
> UUID: 30e942d9-0d06-42d3-8f9a-893dbdee37c2
> Ancestors: VMMaker.oscog-eem.723
>
> Slang/general:
> VMBIGENDIAN must *not* be defined during generation.  It
> should be taken from platforms/??/vm/sqConfig.h.  This should
> go a long way to fixing Doug's issues on PPC.
>

For sure VMBIGENDIAN should not be generated from slang. But more generally,
it is available at runtime via Interpreter>>isBigEnder, so the declaration
in sqConfig.h should not be required either.

IMO isBigEnder is a cruel joke:

isBigEnder
"Answer true (non-zero) if running on a big endian machine."
| endianness anInt cString len i |
<var: 'cString' type: 'char *'>
<var: 'endianness' declareC: 'static sqInt endianness = -1'>
(endianness == -1) ifFalse: [^ endianness]. "answer cached value"
len := self cCode: 'sizeof(anInt)'
inSmalltalk: [^ (Smalltalk endianness == #little) not].
cString := self cCode: '(char *) &anInt' inSmalltalk: [].
i := 0.
[i < len] whileTrue:
[cString at: i put: i.
i := i + 1].
endianness :=  anInt bitAnd: 255.
^ endianness

This simply isn't usable for something like testing the numArgs in a frame to decide on pushTemp: whether to fetch the temp from the arguments side of the frame or the temporary side of the frame.  It is also unnecessarily complex, with the cacheing on first use.  Now every test of endianness (which is in 99.9999999% of cases constant throughout a program's run) involves at least two tests, is the cache valid? followed by what's the value of the cache?.

So I deleted it from Cog and instead use VMBIGENDIAN directly.  If we care about performance (and VM writes should), we don't want to fetch a constant value and test it, ever.  We want the value tested at compile time.

--
best,
Eliot