VM Maker: VMMaker.oscog-eem.2454.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.2454.mcz

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

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

Name: VMMaker.oscog-eem.2454
Author: eem
Time: 12 October 2018, 12:25:47.804334 pm
UUID: 1a484e25-1628-4326-8054-8d4fbbbc3d65
Ancestors: VMMaker.oscog-eem.2453

General:
Correct a slip in primitiveVMParameter; statMaxAllocSegmentTime is Spur only.
Rewrite primitiveGetVMParameter: & primitiveSetVMParameter:arg: as case statements.

Slang:
Consequently fix a bug with various generate*AsArgument:on:indent: forms that failed to output anything if they did constant folding that folded down to a nil block.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateIfFalseAsArgument:on:indent: (in category 'C translation') -----
  generateIfFalseAsArgument: msgNode on: aStream indent: level
  "Generate the C code for this message onto the given stream."
 
  (self nilOrBooleanConstantReceiverOf: msgNode receiver)
  ifNil:
  ["Eliminate double-negatives"
  (msgNode receiver isSend and: [msgNode receiver selector == #not]) ifTrue:
  [^self generateIfTrueAsArgument: (TSendNode new
  setSelector: msgNode selector
  receiver: msgNode receiver receiver
  arguments: msgNode args
  isBuiltInOp: msgNode isBuiltinOperator)
  on: aStream
  indent: level].
  aStream nextPutAll: '(!!('.
  msgNode receiver emitCCodeAsArgumentOn: aStream level: 0 generator: self.
  aStream nextPut: $); crtab: level + 1; nextPut: $?; space.
  msgNode args last emitCCodeAsArgumentOn: aStream level: level + 2 generator: self.
  aStream crtab: level + 1; nextPutAll: ': 0)']
  ifNotNil:
  [:const|
+ const
+ ifFalse: [msgNode args first emitCCodeAsArgumentOn: aStream level: level generator: self]
+ ifTrue: [aStream nextPutAll: (self cLiteralFor: nil)]]!
- const ifFalse:
- [msgNode args first emitCCodeAsArgumentOn: aStream level: level generator: self]]!

Item was changed:
  ----- Method: CCodeGenerator>>generateIfNotNilAsArgument:on:indent: (in category 'C translation') -----
  generateIfNotNilAsArgument: msgNode on: aStream indent: level
  "Generate the C code for this message onto the given stream."
 
  (self isNilConstantReceiverOf: msgNode)
  ifFalse:
  [aStream nextPut: $(.
  msgNode receiver emitCCodeAsArgumentOn: aStream level: level generator: self.
  aStream crtab: level + 1; nextPut: $?; space.
  msgNode args first emitCCodeAsArgumentOn: aStream level: level + 2 generator: self.
+ aStream crtab: level + 1; nextPutAll: ': 0)']
+ ifTrue:
+ [aStream nextPutAll: (self cLiteralFor: nil)]!
- aStream crtab: level + 1; nextPutAll: ': 0)']!

Item was changed:
  ----- Method: CCodeGenerator>>generateIfTrueAsArgument:on:indent: (in category 'C translation') -----
  generateIfTrueAsArgument: msgNode on: aStream indent: level
  "Generate the C code for this message onto the given stream."
 
  (self nilOrBooleanConstantReceiverOf: msgNode receiver)
  ifNil:
  [aStream nextPut: $(.
  msgNode receiver emitCCodeAsArgumentOn: aStream level: level generator: self.
  aStream crtab: level + 1; nextPut: $?; space.
  msgNode args first emitCCodeAsArgumentOn: aStream level: level + 2 generator: self.
  aStream crtab: level + 1; nextPutAll: ': 0)']
  ifNotNil:
  [:const|
+ const
+ ifTrue: [msgNode args first emitCCodeAsArgumentOn: aStream level: level generator: self]
+ ifFalse: [aStream nextPutAll: (self cLiteralFor: nil)]]!
- const ifTrue:
- [msgNode args first emitCCodeAsArgumentOn: aStream level: level generator: self]]!

Item was changed:
  ----- Method: CCodeGenerator>>generateIfTrueIfFalseAsArgument:on:indent: (in category 'C translation') -----
  generateIfTrueIfFalseAsArgument: msgNode on: aStream indent: level
  "Generate the C code for this message onto the given stream."
 
  (self nilOrBooleanConstantReceiverOf: msgNode receiver)
  ifNil:
  [(self tryToCollapseBothArmsOfConditionalExpression: msgNode on: aStream indent: level) ifFalse:
  [aStream nextPut: $(.
  msgNode receiver emitCCodeAsExpressionOn: aStream level: level generator: self.
  aStream crtab: level + 1; nextPut: $?; space.
  msgNode args first emitCCodeAsArgumentOn: aStream level: level + 2 generator: self.
  aStream crtab: level + 1; nextPut: $:; space.
  msgNode args last emitCCodeAsArgumentOn: aStream level: level + 2 generator: self.
  aStream nextPut: $)]]
  ifNotNil:
  [:const|
+ (const
+ ifTrue: [msgNode args first]
+ ifFalse: [msgNode args last])
+ emitCCodeAsArgumentOn: aStream level: level generator: self]!
- (const ifTrue: [msgNode args first] ifFalse: [msgNode args last])
- emitCCodeAsArgumentOn: aStream level: level generator: self]!

Item was changed:
  ----- 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 hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory
+ storePointerUnchecked: 73 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000)].
+
- objectMemory storePointerUnchecked: 73 ofObject: result withValue: (objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000).
  objectMemory beRootIfOld: result.
+ self methodReturnValue: result!
- self pop: 1 thenPush: result.
- ^nil!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveGetVMParameter: (in category 'system control primitives') -----
  primitiveGetVMParameter: arg
+ "See primitiveVMParameter method comment.
+ N.B. written as a returning case to avoid branch limits in the V3 bytecode set."
+ arg caseOf: {
+ [1]  -> [^self positiveMachineIntegerFor: objectMemory oldSpaceSize].
+ [2]  -> [^objectMemory integerObjectOf: objectMemory newSpaceSize].
+ [3]  -> [^self positiveMachineIntegerFor: objectMemory totalMemorySize].
+ [6]  -> [^objectMemory integerObjectOf: objectMemory tenuringThreshold].
+ [7]  -> [^objectMemory integerObjectOf: objectMemory statFullGCs].
+ [8]  -> [^objectMemory integerObjectOf: objectMemory statFullGCUsecs + 500 // 1000].
+ [9]  -> [^objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory statScavenges]
+ ifFalse: [objectMemory statIncrGCs])].
+ [10] -> [^objectMemory integerObjectOf: (objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory statScavengeGCUsecs]
+ ifFalse: [objectMemory statIncrGCUsecs]) + 500 // 1000].
+ [11] -> [^objectMemory integerObjectOf: objectMemory statTenures].
+ [12] -> [^ConstZero]. "Was JITTER VM info"
+ [13] -> [^ConstZero]. "Was JITTER VM info"
+ [14] -> [^ConstZero]. "Was JITTER VM info"
+ [15] -> [^ConstZero]. "Was JITTER VM info"
+ [16] -> [^self positive64BitIntegerFor: statIdleUsecs].
+ [17] -> [^(SistaVM and: [self isCog])
+ ifTrue: [objectMemory floatObjectOf: self getCogCodeZoneThreshold]
+ ifFalse: [ConstZero]].
+ [18] -> [^objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory integerObjectOf: objectMemory statCompactionUsecs + 500 // 1000]
+ ifFalse: [ConstZero]].
+ [19] -> [^objectMemory hasSpurMemoryManagerAPI
+ ifTrue: [objectMemory integerObjectOf: objectMemory scavengeThresholdAsExtent]
+ ifFalse: [ConstZero]].
+ [20] -> [^objectMemory positive64BitIntegerFor: self ioUTCStartMicroseconds].
+ [21] -> [^objectMemory integerObjectOf: objectMemory rootTableCount].
+ [22] -> [^objectMemory integerObjectOf: objectMemory statRootTableOverflows].
+ [23] -> [^objectMemory integerObjectOf: extraVMMemory].
+ [24] -> [^objectMemory integerObjectOf: objectMemory shrinkThreshold].
+ [25] -> [^objectMemory integerObjectOf: objectMemory growHeadroom].
+ [26] -> [^objectMemory integerObjectOf: self ioHeartbeatMilliseconds].
+ [27] -> [^objectMemory integerObjectOf: objectMemory statMarkCount].
+ [28] -> [^objectMemory integerObjectOf: objectMemory statSweepCount].
+ [29] -> [^objectMemory integerObjectOf: objectMemory statMkFwdCount].
+ [30] -> [^objectMemory integerObjectOf: objectMemory statCompMoveCount].
+ [31] -> [^objectMemory integerObjectOf: objectMemory statGrowMemory].
+ [32] -> [^objectMemory integerObjectOf: objectMemory statShrinkMemory].
+ [33] -> [^objectMemory integerObjectOf: objectMemory statRootTableCount].
+ [34] -> [^objectMemory hasSpurMemoryManagerAPI ifTrue:"was statAllocationCount"
+ [objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes]].
+ [35] -> [^objectMemory integerObjectOf: objectMemory statSurvivorCount].
+ [36] -> [^objectMemory integerObjectOf: (self microsecondsToMilliseconds: objectMemory statGCEndUsecs)].
+ [37] -> [^objectMemory integerObjectOf: objectMemory statSpecialMarkCount].
+ [38] -> [^objectMemory integerObjectOf: objectMemory statIGCDeltaUsecs + 500 // 1000].
+ [39] -> [^objectMemory integerObjectOf: statPendingFinalizationSignals].
+ [40] -> [^objectMemory integerObjectOf: objectMemory wordSize].
+ [41] -> [^objectMemory integerObjectOf: self imageFormatVersion].
+ [42] -> [^objectMemory integerObjectOf: numStackPages].
+ [43] -> [^objectMemory integerObjectOf: desiredNumStackPages].
+ [44] -> [^objectMemory integerObjectOf: objectMemory edenBytes].
+ [45] -> [^objectMemory integerObjectOf: desiredEdenBytes].
+ [46] -> [^self getCogCodeSize].
+ [47] -> [^self getDesiredCogCodeSize].
+ [48] -> [^self getCogVMFlags].
+ [49] -> [^objectMemory integerObjectOf: self ioGetMaxExtSemTableSize].
+ [52] -> [^objectMemory integerObjectOf: objectMemory rootTableCapacity].
+ [53] -> [^objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory integerObjectOf: objectMemory numSegments]].
+ [54] -> [^objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory integerObjectOf: objectMemory freeSize]].
+ [55] -> [^objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio]].
+ [56] -> [^self positive64BitIntegerFor: statProcessSwitch].
+ [57] -> [^self positive64BitIntegerFor: statIOProcessEvents].
+ [58] -> [^self positive64BitIntegerFor: statForceInterruptCheck].
+ [59] -> [^self positive64BitIntegerFor: statCheckForEvents].
+ [60] -> [^self positive64BitIntegerFor: statStackOverflow].
+ [61] -> [^self positive64BitIntegerFor: statStackPageDivorce].
+ [62] -> [^self getCodeCompactionCount].
+ [63] -> [^self getCodeCompactionMSecs].
+ [64] -> [^self getCogMethodCount].
+ [65] -> [^self getCogVMFeatureFlags].
+ [66] -> [^objectMemory integerObjectOf: self stackPageByteSize].
+ [67] -> [^objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory integerObjectOf: objectMemory maxOldSpaceSize]].
+ [68] -> [^objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping].
+ [69] -> [^objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping].
+ [70] -> [^self integerObjectOf: (self cCode: 'VM_PROXY_MAJOR' inSmalltalk: [self class vmProxyMajorVersion])].
+ [71] -> [^self integerObjectOf: (self cCode: 'VM_PROXY_MINOR' inSmalltalk: [self class vmProxyMinorVersion])].
+ [72] -> [^objectMemory integerObjectOf: objectMemory statMarkUsecs + 500 // 1000].
+ [73] -> [^objectMemory integerObjectOf: objectMemory statSweepUsecs + 500 // 1000].
+ [74] -> [^objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000]] }
+ otherwise: [^nil]!
- "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 changed:
  ----- Method: StackInterpreterPrimitives>>primitiveSetVMParameter:arg: (in category 'system control primitives') -----
+ primitiveSetVMParameter: index arg: argOop
- primitiveSetVMParameter: index arg: arg
  "See primitiveVMParameter method comment"
+ | arg result |
+
+ "argOop read & checks; in most cases this is an integer parameter.  In some it is either an integer or a Float"
+ (index = 17 or: [index = 55 or: [index = 68]])
+ ifTrue:
+ [((objectMemory isFloatInstance: argOop)
+  or: [objectMemory isIntegerObject: argOop]) ifFalse:
+ [^self primitiveFailFor: PrimErrBadArgument]]
+ ifFalse:
+ [(objectMemory isIntegerObject: argOop) ifFalse:
+ [^self primitiveFailFor: PrimErrBadArgument].
+ arg := objectMemory integerValueOf: argOop].
+
- | result |
  "assume failure, then set success for handled indices"
  self primitiveFailFor: PrimErrBadArgument.
+ index caseOf: {
+ [5] -> [objectMemory hasSpurMemoryManagerAPI ifFalse:
+ ["Was:
+ result := allocationsBetweenGCs.
+ allocationsBetweenGCs := arg."
+ "Ignore for now, because old images won't start up otherwise.
+ See 45 for eden size setting."
+ result := objectMemory nilObject.
+ self initPrimCall]].
+ [6] -> [result := objectMemory integerObjectOf: objectMemory tenuringThreshold.
+ primFailCode := objectMemory tenuringThreshold: arg].
+ [11] -> [arg >= 0 ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory statTenures.
+ objectMemory statTenures: arg.
+ self initPrimCall]].
+ [17] -> [(SistaVM and: [self isCog]) ifTrue:
+ [result := objectMemory floatObjectOf: self getCogCodeZoneThreshold.
+ primFailCode := self setCogCodeZoneThreshold: (self noInlineLoadFloatOrIntFrom: argOop)]].
+ [23] -> [result := objectMemory integerObjectOf: extraVMMemory.
+ extraVMMemory := arg.
+ self initPrimCall].
+ [24] -> [arg > 0 ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory shrinkThreshold.
+ objectMemory shrinkThreshold: arg.
+ self initPrimCall]].
+ [25] -> [arg > 0 ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory growHeadroom.
+ objectMemory growHeadroom: arg.
+ self initPrimCall]].
+ [26] -> [arg >= 0 ifTrue: "0 turns off the heartbeat"
+ [result := objectMemory integerObjectOf: self ioHeartbeatMilliseconds.
+ self ioSetHeartbeatMilliseconds: arg.
+ self initPrimCall]].
+ [34] -> [(objectMemory hasSpurMemoryManagerAPI "was statAllocationCount; now statAllocatedBytes"
+  and: [arg >= 0]) ifTrue:
+ [result := objectMemory positive64BitIntegerFor: objectMemory currentAllocatedBytes.
+ objectMemory setCurrentAllocatedBytesTo: arg.
+ self initPrimCall]].
+ [43] -> [(arg between: 0 and: 65535) ifTrue:
+ [result := objectMemory integerObjectOf: desiredNumStackPages.
+ desiredNumStackPages := arg.
+ self initPrimCall]].
+ [45] -> [arg >= 0 ifTrue:
+ [result := objectMemory integerObjectOf: desiredEdenBytes.
+ desiredEdenBytes := arg.
+ self initPrimCall]].
+ [47] -> [(self isCog
+  and: [arg between: 0 and: self maxCogCodeSize]) ifTrue:
+ [result := objectMemory integerObjectOf: self getDesiredCogCodeSize.
+ self setDesiredCogCodeSize: arg.
+ self initPrimCall]].
+ [48] -> [arg >= 0 ifTrue:
+ [result := objectMemory integerObjectOf: self getCogVMFlags.
+ self initPrimCall. "i.e. setCogVMFlags: can fail"
+ self setCogVMFlags: arg]].
+ [49] -> [(arg between: 0 and: 65535) ifTrue:
+ [result := objectMemory integerObjectOf: self ioGetMaxExtSemTableSize.
+ self initPrimCall. "i.e. ioSetMaxExtSemTableSize: is allowed to fail"
+ self setMaxExtSemSizeTo: arg]].
+ [55] -> [objectMemory hasSpurMemoryManagerAPI ifTrue:
+ [result := objectMemory floatObjectOf: objectMemory getHeapGrowthToSizeGCRatio.
+ primFailCode := objectMemory setHeapGrowthToSizeGCRatio: (self noInlineLoadFloatOrIntFrom: argOop)]].
+ [67] -> [(arg >= 0
+  and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory maxOldSpaceSize.
+ primFailCode := objectMemory setMaxOldSpaceSize: arg]].
+ [68] -> [result := objectMemory floatObjectOf: stackPages statAverageLivePagesWhenMapping.
+ self initPrimCall. "i.e. statAverageLivePagesWhenMapping: is allowed to fail"
+ stackPages statAverageLivePagesWhenMapping: (self noInlineLoadFloatOrIntFrom: argOop)].
+ [69] -> [arg >= 0 ifTrue:
+ [result := objectMemory integerObjectOf: stackPages statMaxPageCountWhenMapping.
+ stackPages statMaxPageCountWhenMapping: arg.
+ self initPrimCall]].
+ [74] -> [(arg >= 0
+  and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ [result := objectMemory integerObjectOf: objectMemory statMaxAllocSegmentTime + 500 // 1000.
+ stackPages statMaxAllocSegmentTime: arg. "usually 0"
+ self initPrimCall]] }
+ otherwise: [].
- 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]].
 
+ self successful
+ ifTrue: [self methodReturnValue: result]  "return old value"
+ ifFalse: [self primitiveFailFor: PrimErrInappropriate] "attempting to write a read-only or non-existent parameter"!
- (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') -----
  primitiveVMParameter
  "Behaviour depends on argument count:
  0 args: return an Array of VM parameter values;
  1 arg: return the indicated VM parameter;
  2 args: set the VM indicated parameter.
  VM parameters are numbered as follows:
  1 end (v3)/size(Spur) of old-space (0-based, read-only)
  2 end (v3)/size(Spur) of young/new-space (read-only)
  3 end (v3)/size(Spur) of heap (read-only)
  4 nil (was allocationCount (read-only))
  5 nil (was allocations between GCs (read-write)
  6 survivor count tenuring threshold (read-write)
  7 full GCs since startup (read-only)
  8 total milliseconds in full GCs since startup (read-only)
  9 incremental GCs (SqueakV3) or scavenges (Spur) since startup (read-only)
  10 total milliseconds in incremental GCs (SqueakV3) or scavenges (Spur) since startup (read-only)
  11 tenures of surving objects since startup or reset (read-write)
  12-20 were specific to ikp's JITTER VM, now 12-15 are open for use
  16 total microseconds at idle since start-up (if non-zero)
  17 fraction of the code zone to use (Sista only; used to control code zone use to preserve sendAndBranchData on counter tripped callback)
  18 total milliseconds in compaction phase of full GC since start-up (Spur only)
  19 scavenge threshold, the effective size of eden.  When eden fills to the threshold a scavenge is scheduled. Newer Spur VMs only.
  20 utc microseconds at VM start-up (actually at time initialization, which precedes image load).
  21 root/remembered table size (occupancy) (read-only)
  22 root table overflows since startup (read-only)
  23 bytes of extra memory to reserve for VM buffers, plugins, etc (stored in image file header).
  24 memory threshold above which shrinking object memory (rw)
  25 memory headroom when growing object memory (rw)
  26 interruptChecksEveryNms - force an ioProcessEvents every N milliseconds (rw)
  27 number of times mark loop iterated for current IGC/FGC (read-only) includes ALL marking
  28 number of times sweep loop iterated for current IGC/FGC (read-only)
  29 number of times make forward loop iterated for current IGC/FGC (read-only)
  30 number of times compact move loop iterated for current IGC/FGC (read-only)
  31 number of grow memory requests (read-only)
  32 number of shrink memory requests (read-only)
  33 number of root table entries used for current IGC/FGC (read-only)
  34 Spur: bytes allocated in total since start-up or reset (read-write) (Used to be number of allocations done before current IGC/FGC (read-only))
  35 number of survivor objects after current IGC/FGC (read-only)
  36 millisecond clock when current IGC/FGC completed (read-only)
  37 number of marked objects for Roots of the world, not including Root Table entries for current IGC/FGC (read-only)
  38 milliseconds taken by current IGC (read-only)
  39 Number of finalization signals for Weak Objects pending when current IGC/FGC completed (read-only)
  40 BytesPerOop for this image
  41 imageFormatVersion for the VM
  42 number of stack pages in use
  43 desired number of stack pages (stored in image file header, max 65535)
  44 size of eden, in bytes
  45 desired size of eden, in bytes (stored in image file header)
  46 machine code zone size, in bytes (Cog only; otherwise nil)
  47 desired machine code zone size (stored in image file header; Cog only; otherwise nil)
  48 various header flags.  See getCogVMFlags.
  49 max size the image promises to grow the external semaphore table to (0 sets to default, which is 256 as of writing)
  50-51 nil; reserved for VM parameters that persist in the image (such as eden above)
  52 root/remembered table capacity
  53 number of segments (Spur only; otherwise nil)
  54 total size of free old space (Spur only, otherwise nil)
  55 ratio of growth and image size at or above which a GC will be performed post scavenge
  56 number of process switches since startup (read-only)
  57 number of ioProcessEvents calls since startup (read-only)
  58 number of ForceInterruptCheck calls since startup (read-only)
  59 number of check event calls since startup (read-only)
  60 number of stack page overflows since startup (read-only)
  61 number of stack page divorces since startup (read-only)
  62 compiled code compactions since startup (read-only; Cog only; otherwise nil)
  63 total milliseconds in compiled code compactions since startup (read-only; Cog only; otherwise nil)
  64 the number of methods that currently have jitted machine-code
  65 whether the VM supports a certain feature, MULTIPLE_BYTECODE_SETS is bit 0, IMMUTABILITY is bit 1
  66 the byte size of a stack page
  67 the max allowed size of old space (Spur only; nil otherwise; 0 implies no limit except that of the underlying platform)
  68 the average number of live stack pages when scanned by GC (at scavenge/gc/become et al) (read-write)
  69 the maximum number of live stack pages when scanned by GC (at scavenge/gc/become et al) (read-write)
  70 the vmProxyMajorVersion (the interpreterProxy VM_MAJOR_VERSION)
  71 the vmProxyMinorVersion (the interpreterProxy VM_MINOR_VERSION)
  72 total milliseconds in full GCs Mark phase since startup (read-only)
  73 total milliseconds in full GCs Sweep phase since startup (read-only, can be 0 depending on compactors)
+ 74 maximum pause time due to segment allocation
- 74 Maximum pause time due to segment allocation
 
  Note: Thanks to Ian Piumarta for this primitive."
 
+ | paramsArraySize index |
- | paramsArraySize arg index |
  paramsArraySize := 74.
  argumentCount = 0 ifTrue: [^self primitiveAllVMParameters: paramsArraySize].
  argumentCount > 2 ifTrue: [^self primitiveFailFor: PrimErrBadNumArgs].
 
  "index read & checks"
+ index := self stackValue: (argumentCount = 1 ifTrue: [0] ifFalse: [1]).
- index := argumentCount = 1 ifTrue: [self stackTop] ifFalse: [self stackValue: 1].
  (objectMemory isIntegerObject: index) ifFalse: [^self primitiveFailFor: PrimErrBadArgument].
  index := objectMemory integerValueOf: index.
  (index < 1 or: [index > paramsArraySize]) ifTrue: [^self primitiveFailFor: PrimErrBadIndex].
 
+ argumentCount = 1 ifTrue: "read VM parameter; written this way to avoid branch limits in V3 bytecode set"
+ [| result |
+ result := self primitiveGetVMParameter: index.
+ ^self methodReturnValue: (result ifNil: [objectMemory nilObject])].
- argumentCount = 1 ifTrue: "read VM parameter"
- [^self primitiveGetVMParameter: index].
 
- "2nd arg read & checks"
- arg := self stackTop.
- (index = 17 or: [index = 55 or: [index = 68]])
- ifTrue:
- [((objectMemory isFloatInstance: arg)
-  or: [objectMemory isIntegerObject: arg]) ifFalse:
- [^self primitiveFailFor: PrimErrBadArgument]]
- ifFalse:
- [(objectMemory isIntegerObject: arg) ifFalse:
- [^self primitiveFailFor: PrimErrBadArgument].
- arg := objectMemory integerValueOf: arg].
-
  "write a VM parameter"
+ self primitiveSetVMParameter: index arg: self stackTop!
- ^self primitiveSetVMParameter: index arg: arg!