VM Maker: VMMaker.oscog-cb.2446.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-cb.2446.mcz

commits-2
 
ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2446.mcz

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

Name: VMMaker.oscog-cb.2446
Author: cb
Time: 4 October 2018, 9:25:25.340169 am
UUID: 84e13efd-8051-4c71-be83-7fed69c55a0b
Ancestors: VMMaker.oscog-cb.2445

Split the VMParameter primitive in 3 methods in Slang. I did it because of jump false size overflow on V3PlusClosure BC set, but it also look nicer.

Add code to monitor the longest segment allocation pause (parameter 74).

=============== Diff against VMMaker.oscog-cb.2445 ===============

Item was added:
+ ----- Method: FilePluginSimulator>>dir_EntryLookup: (in category 'simulation') -----
+ dir_EntryLookup: pathString _: pathStringLength _: entryNameString _: entryNameStringLength _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
+ "sqInt dir_EntryLookup(char *pathString, sqInt pathStringLength, char *nameString, sqInt nameStringLength,
+ /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
+        sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt *posixPermissions, sqInt *isSymlink)"
+ | result pathName entryName |
+ pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
+ entryName := ((0 to: entryNameStringLength - 1) collect: [:i| (entryNameString at: i) asCharacter]) as: ByteString.
+ result := self primLookupEntryIn: pathName name: entryName.
+ result ifNil: [^DirNoMoreEntries].
+ result isInteger ifTrue:
+ [result > 1 ifTrue:
+ [interpreterProxy primitiveFailFor: result].
+ ^DirBadPath].
+ name replaceFrom: 1 to: result first size with: result first startingAt: 1.
+ nameLength at: 0 put: result first size.
+ creationDate at: 0 put: (result at: 2).
+ modificationDate at: 0 put: (result at: 3).
+ isDirectory at: 0 put: (result at: 4).
+ sizeIfFile at: 0 put: (result at: 5).
+ posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
+ isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
+ ^DirEntryFound!

Item was removed:
- ----- Method: FilePluginSimulator>>dir_EntryLookup:_:_:_:_:_:_:_:_:_:_:_: (in category 'simulation') -----
- dir_EntryLookup: pathString _: pathStringLength _: entryNameString _: entryNameStringLength _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
- "sqInt dir_EntryLookup(char *pathString, sqInt pathStringLength, char *nameString, sqInt nameStringLength,
- /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
-        sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt *posixPermissions, sqInt *isSymlink)"
- | result pathName entryName |
- pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
- entryName := ((0 to: entryNameStringLength - 1) collect: [:i| (entryNameString at: i) asCharacter]) as: ByteString.
- result := self primLookupEntryIn: pathName name: entryName.
- result ifNil: [^DirNoMoreEntries].
- result isInteger ifTrue:
- [result > 1 ifTrue:
- [interpreterProxy primitiveFailFor: result].
- ^DirBadPath].
- name replaceFrom: 1 to: result first size with: result first startingAt: 1.
- nameLength at: 0 put: result first size.
- creationDate at: 0 put: (result at: 2).
- modificationDate at: 0 put: (result at: 3).
- isDirectory at: 0 put: (result at: 4).
- sizeIfFile at: 0 put: (result at: 5).
- posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
- isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
- ^DirEntryFound!

Item was added:
+ ----- Method: FilePluginSimulator>>dir_Lookup: (in category 'simulation') -----
+ dir_Lookup: pathString _: pathStringLength _: index _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
+ "sqInt dir_Lookup( char *pathString, sqInt pathStringLength, sqInt index,
+ /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
+   sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt * posixPermissions, sqInt *isSymlink)"
+ | result pathName |
+ pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
+ result := self primLookupEntryIn: pathName index: index.
+ result ifNil: [^DirNoMoreEntries].
+ result isInteger ifTrue:
+ [result > 1 ifTrue:
+ [interpreterProxy primitiveFailFor: result].
+ ^DirBadPath].
+ name replaceFrom: 1 to: result first size with: result first startingAt: 1.
+ nameLength at: 0 put: result first size.
+ creationDate at: 0 put: (result at: 2).
+ modificationDate at: 0 put: (result at: 3).
+ isDirectory at: 0 put: (result at: 4).
+ sizeIfFile at: 0 put: (result at: 5).
+ posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
+ isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
+ ^DirEntryFound!

Item was removed:
- ----- Method: FilePluginSimulator>>dir_Lookup:_:_:_:_:_:_:_:_:_:_: (in category 'simulation') -----
- dir_Lookup: pathString _: pathStringLength _: index _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
- "sqInt dir_Lookup( char *pathString, sqInt pathStringLength, sqInt index,
- /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
-   sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt * posixPermissions, sqInt *isSymlink)"
- | result pathName |
- pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
- result := self primLookupEntryIn: pathName index: index.
- result ifNil: [^DirNoMoreEntries].
- result isInteger ifTrue:
- [result > 1 ifTrue:
- [interpreterProxy primitiveFailFor: result].
- ^DirBadPath].
- name replaceFrom: 1 to: result first size with: result first startingAt: 1.
- nameLength at: 0 put: result first size.
- creationDate at: 0 put: (result at: 2).
- modificationDate at: 0 put: (result at: 3).
- isDirectory at: 0 put: (result at: 4).
- sizeIfFile at: 0 put: (result at: 5).
- posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
- isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
- ^DirEntryFound!

Item was added:
+ ----- Method: InterpreterPlugin>>strncpy: (in category 'simulation support') -----
+ strncpy: aString _: bString _: n
+ <doNotGenerate>
+ ^interpreterProxy strncpy: aString _: bString _: n!

Item was removed:
- ----- Method: InterpreterPlugin>>strncpy:_:_: (in category 'simulation support') -----
- strncpy: aString _: bString _: n
- <doNotGenerate>
- ^interpreterProxy strncpy: aString _: bString _: n!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>memmove: (in category 'simulation only') -----
+ memmove: destAddress _: sourceAddress _: bytes
+ <doNotGenerate>
+ | dst src  |
+ dst := destAddress asInteger.
+ src := sourceAddress asInteger.
+ "Emulate the c library memmove function"
+ self assert: bytes \\ 4 = 0.
+ destAddress > sourceAddress
+ ifTrue:
+ [bytes - 4 to: 0 by: -4 do:
+ [:i| self long32At: dst + i put: (self long32At: src + i)]]
+ ifFalse:
+ [0 to: bytes - 4 by: 4 do:
+ [:i| self long32At: dst + i put: (self long32At: src + i)]]!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>memmove:_:_: (in category 'simulation only') -----
- memmove: destAddress _: sourceAddress _: bytes
- <doNotGenerate>
- | dst src  |
- dst := destAddress asInteger.
- src := sourceAddress asInteger.
- "Emulate the c library memmove function"
- self assert: bytes \\ 4 = 0.
- destAddress > sourceAddress
- ifTrue:
- [bytes - 4 to: 0 by: -4 do:
- [:i| self long32At: dst + i put: (self long32At: src + i)]]
- ifFalse:
- [0 to: bytes - 4 by: 4 do:
- [:i| self long32At: dst + i put: (self long32At: src + i)]]!

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

Item was changed:
  ----- Method: SpurMemoryManager>>growOldSpaceByAtLeast: (in category 'growing/shrinking memory') -----
  growOldSpaceByAtLeast: minAmmount
  "Attempt to grow memory by at least minAmmount.
  Answer the size of the new segment, or nil if the attempt failed."
+ | ammount headroom total start interval |
- | ammount headroom total |
  <var: #segInfo type: #'SpurSegmentInfo *'>
  "statGrowMemory counts attempts, not successes."
  statGrowMemory := statGrowMemory + 1."we need to include overhead for a new object header plus the segment bridge."
  ammount := minAmmount + (self baseHeaderSize * 2 + self bridgeSize).
  "round up to the nearest power of two."
  ammount := 1 << (ammount - 1) highBit.
  "and grow by at least growHeadroom."
  ammount := ammount max: growHeadroom.
 
  "Now apply the maxOldSpaceSize limit, if one is in effect."
  maxOldSpaceSize > 0 ifTrue:
  [total := segmentManager totalBytesInSegments.
  total >= maxOldSpaceSize ifTrue:
  [^nil].
  headroom := maxOldSpaceSize - total.
  headroom < ammount ifTrue:
  [headroom < (minAmmount + (self baseHeaderSize * 2 + self bridgeSize)) ifTrue:
  [^nil].
  ammount := headroom]].
 
+ start := coInterpreter ioUTCMicrosecondsNow.
  ^(segmentManager addSegmentOfSize: ammount) ifNotNil:
  [:segInfo|
  self assimilateNewSegment: segInfo.
  "and add the new free chunk to the free list; done here
   instead of in assimilateNewSegment: for the assert"
  self addFreeChunkWithBytes: segInfo segSize - self bridgeSize at: segInfo segStart.
  self assert: (self addressAfter: (self objectStartingAt: segInfo segStart))
  = (segInfo segLimit - self bridgeSize).
  self checkFreeSpace: GCModeFreeSpace.
  segmentManager checkSegments.
+ interval := coInterpreter ioUTCMicrosecondsNow - start.
+ interval > statMaxAllocSegmentTime ifTrue: [statMaxAllocSegmentTime := interval].
  segInfo segSize]!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  "We can put all initializations that set something to 0 or to false here.
  In C all global variables are initialized to 0, and 0 is false."
  remapBuffer := Array new: RemapBufferSize.
  remapBufferCount := extraRootCount := 0. "see below"
  freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  checkForLeaks := 0.
  needGCFlag := signalLowSpace := marking := false.
  becomeEffectsFlags := gcPhaseInProgress := 0.
  statScavenges := statIncrGCs := statFullGCs := 0.
+ statMaxAllocSegmentTime := 0.
  statMarkUsecs := statSweepUsecs := statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statCompactionUsecs := statGCEndUsecs := gcSweepEndUsecs := 0.
  statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  statGrowMemory := statShrinkMemory := statRootTableCount := statAllocatedBytes := 0.
  statRootTableOverflows := statMarkCount := statCompactPassCount := statCoalesces := 0.
 
  "We can initialize things that are allocated but are lazily initialized."
  unscannedEphemerons := SpurContiguousObjStack new.
 
  "we can initialize things that are virtual in C."
  scavenger := SpurGenerationScavenger simulatorClass new manager: self; yourself.
  segmentManager := SpurSegmentManager simulatorClass new manager: self; yourself.
  compactor := self class compactorClass simulatorClass new manager: self; yourself.
 
  "We can also initialize here anything that is only for simulation."
  heapMap := CogCheck32BitHeapMap new.
 
  "N.B. We *don't* initialize extraRoots because we don't simulate it."
  maxOldSpaceSize := self class initializationOptions
  ifNotNil: [:initOpts| initOpts at: #maxOldSpaceSize ifAbsent: [0]]
  ifNil: [0]!

Item was added:
+ ----- Method: SpurMemoryManager>>memcpy: (in category 'simulation') -----
+ memcpy: destAddress _: sourceAddress _: bytes
+ "For SpurGenerationScavenger>>copyToFutureSpace:bytes:. N.B. If ranges overlap, must use memmove."
+ <doNotGenerate>
+ self deny: ((destAddress <= sourceAddress and: [destAddress asInteger + bytes > sourceAddress])
+ or: [sourceAddress <= destAddress and: [sourceAddress asInteger + bytes > destAddress]]).
+ ^self memmove: destAddress _: sourceAddress _: bytes!

Item was removed:
- ----- Method: SpurMemoryManager>>memcpy:_:_: (in category 'simulation') -----
- memcpy: destAddress _: sourceAddress _: bytes
- "For SpurGenerationScavenger>>copyToFutureSpace:bytes:. N.B. If ranges overlap, must use memmove."
- <doNotGenerate>
- self deny: ((destAddress <= sourceAddress and: [destAddress asInteger + bytes > sourceAddress])
- or: [sourceAddress <= destAddress and: [sourceAddress asInteger + bytes > destAddress]]).
- ^self memmove: destAddress _: sourceAddress _: bytes!

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

Item was added:
+ ----- Method: SpurMemoryManager>>statMaxAllocSegmentTime: (in category 'accessing') -----
+ statMaxAllocSegmentTime: aValue
+ statMaxAllocSegmentTime := aValue!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveAllVMParameters: (in category 'system control primitives') -----
+ primitiveAllVMParameters: paramsArraySize
+ "See primitiveVMParameter method comment"
+
+ | result |
+ result := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: paramsArraySize.
+ objectMemory storePointerUnchecked: 0 ofObject: result withValue: (self positiveMachineIntegerFor: objectMemory oldSpaceSize).
+ objectMemory storePointerUnchecked: 1 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory newSpaceSize).
+ objectMemory storePointerUnchecked: 2 ofObject: result withValue: (self positiveMachineIntegerFor: objectMemory totalMemorySize).
+ "objectMemory storePointerUnchecked: 3 ofObject: result withValue: objectMemory nilObject was allocationCount".
+ "objectMemory storePointerUnchecked: 4 ofObject: result withValue: objectMemory nilObject allocationsBetweenGCs".
+ objectMemory storePointerUnchecked: 5 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory tenuringThreshold).
+ objectMemory storePointerUnchecked: 6 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statFullGCs).
+ objectMemory storePointerUnchecked: 7 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statFullGCUsecs + 500 // 1000).
+ objectMemory
+ storePointerUnchecked: 8
+ ofObject: result
+ withValue: (objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory statScavenges]
+ ifFalse: [objectMemory statIncrGCs])).
+ objectMemory
+ storePointerUnchecked: 9
+ ofObject: result
+ withValue: (objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory statScavengeGCUsecs]
+ ifFalse: [objectMemory statIncrGCUsecs]) + 500 // 1000).
+ objectMemory storePointerUnchecked: 10 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statTenures).
+ "JITTER VM info unused; 11 - 14/12 - 15 available for reuse"
+ 11 to: 18 do:
+ [:i | objectMemory storePointerUnchecked: i ofObject: result withValue: ConstZero].
+ objectMemory storePointerUnchecked: 15 ofObject: result withValue: (objectMemory positive64BitIntegerFor: statIdleUsecs).
+ (SistaVM and: [self isCog]) ifTrue:
+ [objectMemory storePointerUnchecked: 16 ofObject: result withValue: (objectMemory floatObjectOf: self getCogCodeZoneThreshold)].
+ objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory
+ storePointerUnchecked: 17 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statCompactionUsecs + 500 // 1000);
+ storePointerUnchecked: 18 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory scavengeThresholdAsExtent)].
+ objectMemory storePointerUnchecked: 19 ofObject: result withValue: (objectMemory positive64BitIntegerFor: self ioUTCStartMicroseconds).
+ objectMemory storePointerUnchecked: 20 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory rootTableCount).
+ objectMemory storePointerUnchecked: 21 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statRootTableOverflows).
+ objectMemory storePointerUnchecked: 22 ofObject: result withValue: (objectMemory integerObjectOf: extraVMMemory).
+ objectMemory storePointerUnchecked: 23 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory shrinkThreshold).
+ objectMemory storePointerUnchecked: 24 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory growHeadroom).
+ objectMemory storePointerUnchecked: 25 ofObject: result withValue: (objectMemory integerObjectOf: self ioHeartbeatMilliseconds).
+ objectMemory storePointerUnchecked: 26 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMarkCount).
+ objectMemory storePointerUnchecked: 27 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSweepCount).
+ objectMemory storePointerUnchecked: 28 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMkFwdCount).
+ objectMemory storePointerUnchecked: 29 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statCompMoveCount).
+ objectMemory storePointerUnchecked: 30 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statGrowMemory).
+ objectMemory storePointerUnchecked: 31 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statShrinkMemory).
+ objectMemory storePointerUnchecked: 32 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statRootTableCount).
+ objectMemory hasSpurMemoryManagerAPI ifTrue: "was statAllocationCount"
+ [objectMemory storePointerUnchecked: 33 ofObject: result withValue: (objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes)].
+ objectMemory storePointerUnchecked: 34 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSurvivorCount).
+ objectMemory storePointerUnchecked: 35 ofObject: result withValue: (objectMemory integerObjectOf: (self microsecondsToMilliseconds: objectMemory statGCEndUsecs)).
+ objectMemory storePointerUnchecked: 36 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSpecialMarkCount).
+ objectMemory storePointerUnchecked: 37 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statIGCDeltaUsecs + 500 // 1000).
+ objectMemory storePointerUnchecked: 38 ofObject: result withValue: (objectMemory integerObjectOf: statPendingFinalizationSignals).
+ objectMemory storePointerUnchecked: 39 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory wordSize).
+ objectMemory storePointerUnchecked: 40 ofObject: result withValue: (objectMemory integerObjectOf: self imageFormatVersion).
+ objectMemory storePointerUnchecked: 41 ofObject: result withValue: (objectMemory integerObjectOf: numStackPages).
+ objectMemory storePointerUnchecked: 42 ofObject: result withValue: (objectMemory integerObjectOf: desiredNumStackPages).
+ objectMemory storePointerUnchecked: 43 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory edenBytes).
+ objectMemory storePointerUnchecked: 44 ofObject: result withValue: (objectMemory integerObjectOf: desiredEdenBytes).
+ objectMemory storePointerUnchecked: 45 ofObject: result withValue: self getCogCodeSize.
+ objectMemory storePointerUnchecked: 46 ofObject: result withValue: self getDesiredCogCodeSize.
+ objectMemory storePointerUnchecked: 47 ofObject: result withValue: self getCogVMFlags.
+ objectMemory storePointerUnchecked: 48 ofObject: result withValue: (objectMemory integerObjectOf: self ioGetMaxExtSemTableSize).
+ "50 & 51 (49 & 50) reserved for parameters that persist in the image"
+ objectMemory storePointerUnchecked: 51 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory rootTableCapacity).
+ objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory
+ storePointerUnchecked: 52 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory numSegments);
+ storePointerUnchecked: 53 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory freeSize);
+ storePointerUnchecked: 54 ofObject: result withValue: (objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio)].
+ objectMemory storePointerUnchecked: 55 ofObject: result withValue: (self positive64BitIntegerFor: statProcessSwitch).
+ objectMemory storePointerUnchecked: 56 ofObject: result withValue: (self positive64BitIntegerFor: statIOProcessEvents).
+ objectMemory storePointerUnchecked: 57 ofObject: result withValue: (self positive64BitIntegerFor: statForceInterruptCheck).
+ objectMemory storePointerUnchecked: 58 ofObject: result withValue: (self positive64BitIntegerFor: statCheckForEvents).
+ objectMemory storePointerUnchecked: 59 ofObject: result withValue: (self positive64BitIntegerFor: statStackOverflow).
+ objectMemory storePointerUnchecked: 60 ofObject: result withValue: (self positive64BitIntegerFor: statStackPageDivorce).
+ objectMemory storePointerUnchecked: 61 ofObject: result withValue: self getCodeCompactionCount.
+ objectMemory storePointerUnchecked: 62 ofObject: result withValue: self getCodeCompactionMSecs.
+ objectMemory storePointerUnchecked: 63 ofObject: result withValue: self getCogMethodCount.
+ objectMemory storePointerUnchecked: 64 ofObject: result withValue: self getCogVMFeatureFlags.
+ objectMemory storePointerUnchecked: 65 ofObject: result withValue: (objectMemory integerObjectOf: self stackPageByteSize).
+ objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory
+ storePointerUnchecked: 66 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory maxOldSpaceSize)].
+ objectMemory storePointerUnchecked: 67 ofObject: result withValue: (objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping).
+ objectMemory storePointerUnchecked: 68 ofObject: result withValue: (objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping).
+ objectMemory
+ storePointerUnchecked: 69
+ ofObject: result
+ withValue: (objectMemory integerObjectOf: (self cCode: 'VM_PROXY_MAJOR' inSmalltalk: [self class vmProxyMajorVersion])).
+ objectMemory
+ storePointerUnchecked: 70
+ ofObject: result
+ withValue: (objectMemory integerObjectOf: (self cCode: 'VM_PROXY_MINOR' inSmalltalk: [self class vmProxyMinorVersion])).
+ objectMemory storePointerUnchecked: 71 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMarkUsecs + 500 // 1000).
+ objectMemory storePointerUnchecked: 72 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statSweepUsecs + 500 // 1000).
+ objectMemory storePointerUnchecked: 73 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000).
+ objectMemory beRootIfOld: result.
+ self pop: 1 thenPush: result.
+ ^nil!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveGetVMParameter: (in category 'system control primitives') -----
+ primitiveGetVMParameter: arg
+ "See primitiveVMParameter method comment"
+ | result |
+ result := objectMemory nilObject.
+ arg = 1 ifTrue: [result := self positiveMachineIntegerFor: objectMemory oldSpaceSize].
+ arg = 2 ifTrue: [result := objectMemory integerObjectOf: objectMemory newSpaceSize].
+ arg = 3 ifTrue: [result := self positiveMachineIntegerFor: objectMemory totalMemorySize].
+ arg = 4 ifTrue: [result := objectMemory nilObject "was allocationCount"].
+ arg = 5 ifTrue: [result := objectMemory nilObject "was allocationsBetweenGCs"].
+ arg = 6 ifTrue: [result := objectMemory integerObjectOf: objectMemory tenuringThreshold].
+ arg = 7 ifTrue: [result := objectMemory integerObjectOf: objectMemory statFullGCs].
+ arg = 8 ifTrue: [result := objectMemory integerObjectOf: objectMemory statFullGCUsecs + 500 // 1000].
+ arg = 9 ifTrue: [result := objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory statScavenges]
+ ifFalse: [objectMemory statIncrGCs])].
+ arg = 10 ifTrue: [result := objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory statScavengeGCUsecs]
+ ifFalse: [objectMemory statIncrGCUsecs]) + 500 // 1000].
+ arg = 11 ifTrue: [result := objectMemory integerObjectOf: objectMemory statTenures].
+ (arg between: 12 and: 15) ifTrue: [result := ConstZero]. "Was JITTER VM info"
+ arg = 16 ifTrue: [result := self positive64BitIntegerFor: statIdleUsecs].
+ arg = 17 ifTrue: [result := (SistaVM and: [self isCog])
+ ifTrue: [objectMemory floatObjectOf: self getCogCodeZoneThreshold]
+ ifFalse: [ConstZero]].
+ arg = 18 ifTrue: [result := objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory integerObjectOf: objectMemory statCompactionUsecs + 500 // 1000]
+ ifFalse: [ConstZero]].
+ arg = 19 ifTrue: [result := objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory integerObjectOf: objectMemory scavengeThresholdAsExtent]
+ ifFalse: [ConstZero]].
+ arg = 20 ifTrue: [result := objectMemory positive64BitIntegerFor: self ioUTCStartMicroseconds].
+ arg = 21 ifTrue: [result := objectMemory integerObjectOf: objectMemory rootTableCount].
+ arg = 22 ifTrue: [result := objectMemory integerObjectOf: objectMemory statRootTableOverflows].
+ arg = 23 ifTrue: [result := objectMemory integerObjectOf: extraVMMemory].
+ arg = 24 ifTrue: [result := objectMemory integerObjectOf: objectMemory shrinkThreshold].
+ arg = 25 ifTrue: [result := objectMemory integerObjectOf: objectMemory growHeadroom].
+ arg = 26 ifTrue: [result := objectMemory integerObjectOf: self ioHeartbeatMilliseconds].
+ arg = 27 ifTrue: [result := objectMemory integerObjectOf: objectMemory statMarkCount].
+ arg = 28 ifTrue: [result := objectMemory integerObjectOf: objectMemory statSweepCount].
+ arg = 29 ifTrue: [result := objectMemory integerObjectOf: objectMemory statMkFwdCount].
+ arg = 30 ifTrue: [result := objectMemory integerObjectOf: objectMemory statCompMoveCount].
+ arg = 31 ifTrue: [result := objectMemory integerObjectOf: objectMemory statGrowMemory].
+ arg = 32 ifTrue: [result := objectMemory integerObjectOf: objectMemory statShrinkMemory].
+ arg = 33 ifTrue: [result := objectMemory integerObjectOf: objectMemory statRootTableCount].
+ arg = 34 ifTrue: [result := objectMemory hasSpurMemoryManagerAPI "was statAllocationCount"
+ ifTrue: [objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes]
+ ifFalse: [objectMemory nilObject]].
+ arg = 35 ifTrue: [result := objectMemory integerObjectOf: objectMemory statSurvivorCount].
+ arg = 36 ifTrue: [result := objectMemory integerObjectOf: (self microsecondsToMilliseconds: objectMemory statGCEndUsecs)].
+ arg = 37 ifTrue: [result := objectMemory integerObjectOf: objectMemory statSpecialMarkCount].
+ arg = 38 ifTrue: [result := objectMemory integerObjectOf: objectMemory statIGCDeltaUsecs + 500 // 1000].
+ arg = 39 ifTrue: [result := objectMemory integerObjectOf: statPendingFinalizationSignals].
+ arg = 40 ifTrue: [result := objectMemory integerObjectOf: objectMemory wordSize].
+ arg = 41 ifTrue: [result := objectMemory integerObjectOf: self imageFormatVersion].
+ arg = 42 ifTrue: [result := objectMemory integerObjectOf: numStackPages].
+ arg = 43 ifTrue: [result := objectMemory integerObjectOf: desiredNumStackPages].
+ arg = 44 ifTrue: [result := objectMemory integerObjectOf: objectMemory edenBytes].
+ arg = 45 ifTrue: [result := objectMemory integerObjectOf: desiredEdenBytes].
+ arg = 46 ifTrue: [result := self getCogCodeSize].
+ arg = 47 ifTrue: [result := self getDesiredCogCodeSize].
+ arg = 48 ifTrue: [result := self getCogVMFlags].
+ arg = 49 ifTrue: [result := objectMemory integerObjectOf: self ioGetMaxExtSemTableSize].
+ arg = 52 ifTrue: [result := objectMemory integerObjectOf: objectMemory rootTableCapacity].
+ (arg = 53
+ and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory numSegments].
+ (arg = 54
+ and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory freeSize].
+ (arg = 55
+ and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ [result := objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio].
+ arg = 56 ifTrue: [result := self positive64BitIntegerFor: statProcessSwitch].
+ arg = 57 ifTrue: [result := self positive64BitIntegerFor: statIOProcessEvents].
+ arg = 58 ifTrue: [result := self positive64BitIntegerFor: statForceInterruptCheck].
+ arg = 59 ifTrue: [result := self positive64BitIntegerFor: statCheckForEvents].
+ arg = 60 ifTrue: [result := self positive64BitIntegerFor: statStackOverflow].
+ arg = 61 ifTrue: [result := self positive64BitIntegerFor: statStackPageDivorce].
+ arg = 62 ifTrue: [result := self getCodeCompactionCount].
+ arg = 63 ifTrue: [result := self getCodeCompactionMSecs].
+ arg = 64 ifTrue: [result := self getCogMethodCount].
+ arg = 65 ifTrue: [result := self getCogVMFeatureFlags].
+ arg = 66 ifTrue: [result := objectMemory integerObjectOf: self stackPageByteSize].
+ (arg = 67
+ and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory maxOldSpaceSize].
+ arg = 68 ifTrue: [result := objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping].
+ arg = 69 ifTrue: [result := objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping].
+ arg = 70 ifTrue: [result := self integerObjectOf: (self cCode: 'VM_PROXY_MAJOR' inSmalltalk: [self class vmProxyMajorVersion])].
+ arg = 71 ifTrue: [result := self integerObjectOf: (self cCode: 'VM_PROXY_MINOR' inSmalltalk: [self class vmProxyMinorVersion])].
+ arg = 72 ifTrue: [result := objectMemory integerObjectOf: objectMemory statMarkUsecs + 500 // 1000].
+ arg = 73 ifTrue: [result := objectMemory integerObjectOf: objectMemory statSweepUsecs + 500 // 1000].
+ arg = 74 ifTrue: [result := objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000].
+ self pop: 2 thenPush: result.
+ ^nil!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveSetVMParameter:arg: (in category 'system control primitives') -----
+ primitiveSetVMParameter: index arg: arg
+ "See primitiveVMParameter method comment"
+ | result |
+ "assume failure, then set success for handled indices"
+ self primitiveFailFor: PrimErrBadArgument.
+ objectMemory hasSpurMemoryManagerAPI ifFalse:
+ [index = 5 ifTrue: "Was:
+ result := allocationsBetweenGCs.
+ allocationsBetweenGCs := arg."
+ "Ignore for now, because old images won't start up otherwise.
+ See 44 & 45 for eden size setting."
+ [result := objectMemory nilObject.
+ self initPrimCall]].
+ index = 6 ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory tenuringThreshold.
+ primFailCode := objectMemory tenuringThreshold: arg].
+ index = 11 ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory statTenures.
+ arg >= 0 ifTrue:
+ [objectMemory statTenures: arg.
+ self initPrimCall]].
+ (SistaVM and: [self isCog and: [index = 17]]) ifTrue:
+ [result := objectMemory floatObjectOf: self getCogCodeZoneThreshold.
+ primFailCode := self setCogCodeZoneThreshold: (self noInlineLoadFloatOrIntFrom: arg)].
+ index = 23 ifTrue:
+ [result := objectMemory integerObjectOf: extraVMMemory.
+ extraVMMemory := arg.
+ self initPrimCall].
+ index = 24 ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory shrinkThreshold.
+ arg > 0 ifTrue:
+ [objectMemory shrinkThreshold: arg.
+ self initPrimCall]].
+ index = 25 ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory growHeadroom.
+ arg > 0 ifTrue:
+ [objectMemory growHeadroom: arg.
+ self initPrimCall]].
+ index = 26 ifTrue:
+ [arg >= 0 ifTrue: "0 turns off the heartbeat"
+ [result := objectMemory integerObjectOf: self ioHeartbeatMilliseconds.
+ self ioSetHeartbeatMilliseconds: arg.
+ self initPrimCall]].
+ (index = 34 and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:"was statAllocationCount; now statAllocatedBytes"
+ [arg >= 0 ifTrue:
+ [result := objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes.
+ objectMemory setCurrentAllocatedBytesTo: arg.
+ self initPrimCall]].
+ index = 43 ifTrue:
+ [(arg >= 0 and: [arg <= 65535]) ifTrue:
+ [result := objectMemory integerObjectOf: desiredNumStackPages.
+ desiredNumStackPages := arg.
+ self initPrimCall]].
+ index = 45 ifTrue:
+ [(arg >= 0) ifTrue:
+ [result := objectMemory integerObjectOf: desiredEdenBytes.
+ desiredEdenBytes := arg.
+ self initPrimCall]].
+ (index = 47 and: [self isCog]) ifTrue:
+ [(arg >= 0 and: [arg <= self maxCogCodeSize]) ifTrue:
+ [result := objectMemory integerObjectOf: self getDesiredCogCodeSize.
+ self setDesiredCogCodeSize: arg.
+ self initPrimCall]].
+ index = 48 ifTrue:
+ [(arg >= 0) ifTrue:
+ [result := objectMemory integerObjectOf: self getCogVMFlags.
+ self initPrimCall. "i.e. setCogVMFlags: can fail"
+ self setCogVMFlags: arg]].
+ index = 49 ifTrue:
+ [(arg >= 0 and: [arg <= 65535]) ifTrue:
+ [result := objectMemory integerObjectOf: self ioGetMaxExtSemTableSize.
+ self initPrimCall. "i.e. ioSetMaxExtSemTableSize: is allowed to fail"
+ self setMaxExtSemSizeTo: arg]].
+
+ (index = 55
+ and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ [result := objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio.
+ primFailCode := objectMemory setHeapGrowthToSizeGCRatio: (self noInlineLoadFloatOrIntFrom: arg)].
+
+ (index = 67
+ and: [arg >= 0
+ and: [objectMemory hasSpurMemoryManagerAPI]]) ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory maxOldSpaceSize.
+ primFailCode := objectMemory setMaxOldSpaceSize: arg].
+
+ index = 68 ifTrue:
+ [result := objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping.
+ self initPrimCall. "i.e. statAverageLivePagesWhenMapping: is allowed to fail"
+ stackPages statAverageLivePagesWhenMapping: (self noInlineLoadFloatOrIntFrom: arg)].
+
+ (index = 69
+ and: [arg >= 0]) ifTrue:
+ [result := objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping.
+ stackPages statMaxPageCountWhenMapping: arg.
+ self initPrimCall].
+
+ (index = 74
+ and: [arg >= 0]) ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000.
+ stackPages statMaxAllocSegmentTime: arg. "usually 0"
+ self initPrimCall].
+
+ self successful ifTrue:
+ [self pop: 3 thenPush: result.  "return old value"
+ ^nil].
+
+ self primitiveFailFor: PrimErrInappropriate  "attempting to write a read-only or non-existent parameter"!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
(excessive size, no diff calculated)

Item was added:
+ ----- Method: VMClass>>memcpy: (in category 'C library simulation') -----
+ memcpy: dString _: sString _: bytes
+ <doNotGenerate>
+ "implementation of memcpy(3). N.B. If ranges overlap, must use memmove."
+ (dString isString or: [sString isString]) ifFalse:
+ [| destAddress sourceAddress |
+ dString class == ByteArray ifTrue:
+ [ByteString adoptInstance: dString.
+ ^[self memcpy: dString _: sString _: bytes] ensure:
+ [ByteArray adoptInstance: dString]].
+ destAddress := dString asInteger.
+ sourceAddress := sString asInteger.
+ self deny: ((destAddress <= sourceAddress and: [destAddress + bytes > sourceAddress])
+ or: [sourceAddress <= destAddress and: [sourceAddress + bytes > destAddress]])].
+ dString isString
+ ifTrue:
+ [1 to: bytes do:
+ [:i| | v |
+ v := sString isString
+ ifTrue: [sString at: i]
+ ifFalse: [Character value: (self byteAt: sString + i - 1)].
+ dString at: i put: v]]
+ ifFalse:
+ [1 to: bytes do:
+ [:i| | v |
+ v := sString isString
+ ifTrue: [(sString at: i) asInteger]
+ ifFalse: [self byteAt: sString + i - 1].
+ self byteAt: dString + i - 1 put: v]].
+ ^dString!

Item was removed:
- ----- Method: VMClass>>memcpy:_:_: (in category 'C library simulation') -----
- memcpy: dString _: sString _: bytes
- <doNotGenerate>
- "implementation of memcpy(3). N.B. If ranges overlap, must use memmove."
- (dString isString or: [sString isString]) ifFalse:
- [| destAddress sourceAddress |
- dString class == ByteArray ifTrue:
- [ByteString adoptInstance: dString.
- ^[self memcpy: dString _: sString _: bytes] ensure:
- [ByteArray adoptInstance: dString]].
- destAddress := dString asInteger.
- sourceAddress := sString asInteger.
- self deny: ((destAddress <= sourceAddress and: [destAddress + bytes > sourceAddress])
- or: [sourceAddress <= destAddress and: [sourceAddress + bytes > destAddress]])].
- dString isString
- ifTrue:
- [1 to: bytes do:
- [:i| | v |
- v := sString isString
- ifTrue: [sString at: i]
- ifFalse: [Character value: (self byteAt: sString + i - 1)].
- dString at: i put: v]]
- ifFalse:
- [1 to: bytes do:
- [:i| | v |
- v := sString isString
- ifTrue: [(sString at: i) asInteger]
- ifFalse: [self byteAt: sString + i - 1].
- self byteAt: dString + i - 1 put: v]].
- ^dString!

Item was added:
+ ----- Method: VMClass>>memmove: (in category 'C library simulation') -----
+ memmove: destAddress _: sourceAddress _: bytes
+ <doNotGenerate>
+ | dst src  |
+ dst := destAddress asInteger.
+ src := sourceAddress asInteger.
+ "Emulate the c library memmove function"
+ self assert: bytes \\ 4 = 0.
+ destAddress > sourceAddress
+ ifTrue:
+ [bytes - 4 to: 0 by: -4 do:
+ [:i| self longAt: dst + i put: (self longAt: src + i)]]
+ ifFalse:
+ [0 to: bytes - 4 by: 4 do:
+ [:i| self longAt: dst + i put: (self longAt: src + i)]]!

Item was removed:
- ----- Method: VMClass>>memmove:_:_: (in category 'C library simulation') -----
- memmove: destAddress _: sourceAddress _: bytes
- <doNotGenerate>
- | dst src  |
- dst := destAddress asInteger.
- src := sourceAddress asInteger.
- "Emulate the c library memmove function"
- self assert: bytes \\ 4 = 0.
- destAddress > sourceAddress
- ifTrue:
- [bytes - 4 to: 0 by: -4 do:
- [:i| self longAt: dst + i put: (self longAt: src + i)]]
- ifFalse:
- [0 to: bytes - 4 by: 4 do:
- [:i| self longAt: dst + i put: (self longAt: src + i)]]!

Item was added:
+ ----- Method: VMClass>>strcat: (in category 'C library simulation') -----
+ strcat: aString _: bString
+ <doNotGenerate>
+ "implementation of strcat(3)"
+ ^(self asString: aString), (self asString: bString)!

Item was removed:
- ----- Method: VMClass>>strcat:_: (in category 'C library simulation') -----
- strcat: aString _: bString
- <doNotGenerate>
- "implementation of strcat(3)"
- ^(self asString: aString), (self asString: bString)!

Item was added:
+ ----- Method: VMClass>>strncmp: (in category 'C library simulation') -----
+ strncmp: aString _: bString _: n
+ <doNotGenerate>
+ "implementation of strncmp(3)"
+ bString isString ifTrue:
+ [1 to: n do:
+ [:i|
+ (aString at: i) asCharacter ~= (bString at: i) ifTrue:
+ [^i]].
+ ^0].
+ 1 to: n do:
+ [:i| | v |
+ v := (aString at: i) asInteger - (self byteAt: bString + i - 1).
+ v ~= 0 ifTrue: [^v]].
+ ^0!

Item was removed:
- ----- Method: VMClass>>strncmp:_:_: (in category 'C library simulation') -----
- strncmp: aString _: bString _: n
- <doNotGenerate>
- "implementation of strncmp(3)"
- bString isString ifTrue:
- [1 to: n do:
- [:i|
- (aString at: i) asCharacter ~= (bString at: i) ifTrue:
- [^i]].
- ^0].
- 1 to: n do:
- [:i| | v |
- v := (aString at: i) asInteger - (self byteAt: bString + i - 1).
- v ~= 0 ifTrue: [^v]].
- ^0!

Item was added:
+ ----- Method: VMClass>>strncpy: (in category 'C library simulation') -----
+ strncpy: aString _: bString _: n
+ <doNotGenerate>
+ "implementation of strncpy(3)"
+ aString isString
+ ifTrue:
+ [1 to: n do:
+ [:i| | v |
+ v := bString isString
+ ifTrue: [bString at: i]
+ ifFalse: [Character value: (self byteAt: bString + i - 1)].
+ aString at: i put: v.
+ v asInteger = 0 ifTrue: [^aString]]]
+ ifFalse:
+ [1 to: n do:
+ [:i| | v |
+ v := bString isString
+ ifTrue: [(bString at: i) asInteger]
+ ifFalse: [self byteAt: bString + i - 1].
+ self byteAt: aString + i - 1 put: v.
+ v = 0 ifTrue: [^aString]]].
+ ^aString!

Item was removed:
- ----- Method: VMClass>>strncpy:_:_: (in category 'C library simulation') -----
- strncpy: aString _: bString _: n
- <doNotGenerate>
- "implementation of strncpy(3)"
- aString isString
- ifTrue:
- [1 to: n do:
- [:i| | v |
- v := bString isString
- ifTrue: [bString at: i]
- ifFalse: [Character value: (self byteAt: bString + i - 1)].
- aString at: i put: v.
- v asInteger = 0 ifTrue: [^aString]]]
- ifFalse:
- [1 to: n do:
- [:i| | v |
- v := bString isString
- ifTrue: [(bString at: i) asInteger]
- ifFalse: [self byteAt: bString + i - 1].
- self byteAt: aString + i - 1 put: v.
- v = 0 ifTrue: [^aString]]].
- ^aString!