Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2555.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2555 Author: eem Time: 6 September 2019, 12:55:40.085336 pm UUID: 4c3d555e-9970-4e10-9620-8011a7a63e4b Ancestors: VMMaker.oscog-nice.2554 Implement discarding methods with machine code primitives on toggling primitiveDoMixedArithmetic. Next up, adding primitiveDoMixedArithmetic as a flag saved in the image header. =============== Diff against VMMaker.oscog-nice.2554 =============== Item was added: + ----- Method: CoInterpreter>>divorceAMachineCodeFrameWithMachineCodePrimitiveMethodIn: (in category 'frame access') ----- + divorceAMachineCodeFrameWithMachineCodePrimitiveMethodIn: aStackPage + "Divorce at most one frame in the current page (since the divorce may cause the page to be split) + and answer whether a frame was divorced." + <var: #aStackPage type: #'StackPage *'> + | theFP calleeFP theSP theContext | + <var: #aStackPage type: #'StackPage *'> + <var: #theFP type: #'char *'> + <var: #calleeFP type: #'char *'> + <var: #theSP type: #'char *'> + + theFP := aStackPage headFP. + theSP := aStackPage headSP. + theSP := theSP + objectMemory wordSize. "theSP points at hottest item on frame's stack" + + [((self isMachineCodeFrame: theFP) + and: [cogit cogMethodHasMachineCodePrim: (self mframeHomeMethod: theFP)]) ifTrue: + [theContext := self ensureFrameIsMarried: theFP SP: theSP. + self externalDivorceFrame: theFP andContext: theContext. + ^true]. + calleeFP := theFP. + theFP := self frameCallerFP: theFP. + theFP ~= 0] whileTrue: + ["theSP points at stacked hottest item on frame's stack" + theSP := self frameCallerSP: calleeFP]. + + ^false! Item was added: + ----- Method: CoInterpreter>>divorceMachineCodeFramesWithMachineCodePrimitiveMethod (in category 'frame access') ----- + divorceMachineCodeFramesWithMachineCodePrimitiveMethod + | divorcedSome | + [stackPage ~= 0 ifTrue: "This is needed for the assert in externalDivorceFrame:andContext:" + [stackPages markStackPageMostRecentlyUsed: stackPage]. + "Slang can't currently cope with the lack of the variable here. + Something to do with the preceding statement. Take it out + and the code is good. leave it in and we get do { ... } while(l1:)" + divorcedSome := self divorceSomeFramesWithMachineCodePrimitiveMethod. + divorcedSome] whileTrue! Item was added: + ----- Method: CoInterpreter>>divorceSomeFramesWithMachineCodePrimitiveMethod (in category 'frame access') ----- + divorceSomeFramesWithMachineCodePrimitiveMethod + "Divorce at most one frame (since the divorce may cause the containing + page to be split) and answer whether a frame was divorced." + <var: #cogMethod type: #'CogMethod *'> + | divorcedSome | + <var: #aPage type: #'StackPage *'> + divorcedSome := false. + 0 to: numStackPages - 1 do: + [:i| | aPage | + aPage := stackPages stackPageAt: i. + (stackPages isFree: aPage) ifFalse: + ["this to avoid assert in externalDivorceFrame:andContext:" + stackPages markStackPageMostRecentlyUsed: stackPage. + (self divorceAMachineCodeFrameWithMachineCodePrimitiveMethodIn: aPage) ifTrue: + [divorcedSome := true]]]. + ^divorcedSome! Item was added: + ----- Method: CoInterpreter>>ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs (in category 'frame access') ----- + ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs + "Map all native pcs to bytecoded pcs in all contexts that have a method with a cog method with a machine code primitive. + Used to implement flushMethodsWithMachineCodePrimitivesAndContinueAnswering:/vmParameterAt: 75 put: aBool." + <inline: true> + objectMemory allObjectsDo: + [:oop| | methodHeader | + (objectMemory isContextNonImm: oop) ifTrue: + [methodHeader := self rawHeaderOf: (objectMemory fetchPointer: MethodIndex ofObject: oop). + ((self isCogMethodReference: methodHeader) + and: [cogit cogMethodHasMachineCodePrim: (self cCoerceSimple: methodHeader to: #'CogMethod *')]) ifTrue: + [self widowOrForceToBytecodePC: oop]]]! Item was added: + ----- Method: CoInterpreter>>flushMethodsWithMachineCodePrimitivesAndContinueAnswering: (in category 'primitive support') ----- + flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result + "Arrange that any and all cog methods with machine code primitives can be and are discarded. + Hence scan contexts and map their PCs to bytecode PCs if required, and scan frames, divorcing + the frames of activationsif required. The continue execution answering result. THIS MUST BE + INVOKED IN THE CONTEXT OF A PRIMITIVE. It exists to support vmParameterAt:put:." + | activeContext theFrame thePage | + <var: #theFrame type: #'char *'> + <var: #thePage type: #'StackPage *'> + activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer. + self ensurePushedInstructionPointer. + self externalWriteBackHeadFramePointers. + self divorceMachineCodeFramesWithMachineCodePrimitiveMethod. + self ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs. + cogit unlinkSendsToMachineCodePrimitiveMethodsAndFreeIf: true. + + "If flushing led to divorce continue in the interpreter." + (self isStillMarriedContext: activeContext) ifFalse: + [self zeroStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:" + self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext. + "pop bogus machine-code instructionPointer, arguments and receiver" + self pop: argumentCount + 2 thenPush: result. + self siglong: reenterInterpreter jmp: ReturnToInterpreter. + "NOTREACHED"]. + "If not, work out where we are and continue" + theFrame := self frameOfMarriedContext: activeContext. + thePage := stackPages stackPageFor: theFrame. + self assert: thePage headFP = theFrame. + self setStackPageAndLimit: thePage. + self setStackPointersFromPage: thePage. + instructionPointer := self popStack. + self pop: argumentCount + 1 thenPush: result! Item was changed: ----- Method: Cogit>>setHasYoungReferent: (in category 'accessing') ----- setHasYoungReferent: boolean "Written this way to allow reak-pointing in the simulator." <cmacro: '(b) (hasYoungReferent = (b))'> + "boolean ifTrue: + [self halt]." - boolean ifTrue: - [self halt]. "(hasYoungReferent == false and: [boolean == true]) ifTrue: [self halt]." hasYoungReferent := boolean! Item was added: + ----- Method: Cogit>>unlinkIfLinkedSend:pc:toMachineCodePrim: (in category 'in-line cacheing') ----- + unlinkIfLinkedSend: annotation pc: mcpc toMachineCodePrim: ignored + <var: #mcpc type: #'char *'> + <var: #nsSendCache type: #'NSSendCache *'> + | entryPoint | + + NewspeakVM ifTrue: + [| nsSendCache | + annotation = IsNSSendCall ifTrue: + [nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger. + (entryPoint := nsSendCache target) ~= 0 ifTrue: + [ | targetMethod | + targetMethod := entryPoint - cmNoCheckEntryOffset. + (self cogMethodHasMachineCodePrim: targetMethod) ifTrue: + [self voidNSSendCache: nsSendCache]]. + ^0 "keep scanning"]]. + + (self isPureSendAnnotation: annotation) ifTrue: + [entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger. + entryPoint > methodZoneBase ifTrue: "It's a linked send." + [self targetMethodAndSendTableFor: entryPoint annotation: annotation into: + [:targetMethod :sendTable| + (self cogMethodHasMachineCodePrim: targetMethod) ifTrue: + [self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]]. + + ^0 "keep scanning"! Item was added: + ----- Method: Cogit>>unlinkSendsToMachineCodePrimitiveMethodsAndFreeIf: (in category 'jit - api') ----- + unlinkSendsToMachineCodePrimitiveMethodsAndFreeIf: freeIfTrue + <api> + "Unlink all sends in cog methods to methods with a machine code + primitive, and free machine code primitive methods if freeIfTrue. + To avoid having to scan PICs, free any and all PICs" + | cogMethod freedSomething | + <var: #cogMethod type: #'CogMethod *'> + methodZoneBase ifNil: [^self]. + codeModified := freedSomething := false. + cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'. + [cogMethod < methodZone limitZony] whileTrue: + [cogMethod cmType = CMMethod + ifTrue: + [(freeIfTrue + and: [self cogMethodHasMachineCodePrim: cogMethod]) + ifTrue: + [methodZone freeMethod: cogMethod. + freedSomething := true] + ifFalse: + [self mapFor: cogMethod + performUntil: #unlinkIfLinkedSend:pc:toMachineCodePrim: + arg: 0]] + ifFalse: + [cogMethod cmType = CMClosedPIC ifTrue: + [methodZone freeMethod: cogMethod. + freedSomething := true]]. + cogMethod := methodZone methodAfter: cogMethod]. + freedSomething + ifTrue: [self unlinkSendsToFree] + ifFalse: + [codeModified ifTrue: "After possibly updating inline caches we need to flush the icache." + [processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]! Item was added: + ----- Method: SimpleStackBasedCogit>>cogMethodHasMachineCodePrim: (in category 'in-line cacheing') ----- + cogMethodHasMachineCodePrim: aCogMethod + <api> + <var: 'aCogMethod' type: #'CogMethod *'> + <inline: true> + | primIndex | + primIndex := coInterpreter primitiveIndexOfMethod: aCogMethod methodObject header: aCogMethod objectHeader. + ^(primIndex between: 1 and: MaxCompiledPrimitiveIndex) + and: [(primitiveGeneratorTable at: primIndex) primitiveGenerator notNil]! Item was changed: ----- Method: StackInterpreter class>>declareCVarsIn: (in category 'translation') ----- declareCVarsIn: aCCodeGenerator | vmClass | self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses" vmClass := aCCodeGenerator vmClass. "Generate primitiveTable etc based on vmClass, not just StackInterpreter" aCCodeGenerator addHeaderFile:'<stddef.h> /* for e.g. alloca */'; addHeaderFile:'<setjmp.h>'; addHeaderFile:'<wchar.h> /* for wint_t */'; addHeaderFile:'"vmCallback.h"'; addHeaderFile:'"sqMemoryFence.h"'; addHeaderFile:'"dispdbg.h"'. LowcodeVM ifTrue: [ aCCodeGenerator addHeaderFile:'"sqLowcodeFFI.h"']. vmClass declareInterpreterVersionIn: aCCodeGenerator defaultName: 'Stack'. aCCodeGenerator var: #interpreterProxy type: #'struct VirtualMachine*'. aCCodeGenerator declareVar: #sendTrace type: 'volatile int'; declareVar: #byteCount type: #usqInt. "These need to be pointers or unsigned." self declareC: #(instructionPointer method newMethod) as: #usqInt in: aCCodeGenerator. "These are all pointers; char * because Slang has no support for C pointer arithmetic." self declareC: #(localIP localSP localFP stackPointer framePointer stackLimit breakSelector) as: #'char *' in: aCCodeGenerator. aCCodeGenerator var: #breakSelectorLength declareC: 'sqInt breakSelectorLength = MinSmallInteger'. self declareC: #(stackPage overflowedPage) as: #'StackPage *' in: aCCodeGenerator. aCCodeGenerator removeVariable: 'stackPages'. "this is an implicit receiver in the translated code." "This defines bytecodeSetSelector as 0 if MULTIPLEBYTECODESETS is not defined, for the benefit of the interpreter on slow machines." aCCodeGenerator addConstantForBinding: (self bindingOf: #MULTIPLEBYTECODESETS). MULTIPLEBYTECODESETS == false ifTrue: [aCCodeGenerator removeVariable: 'bytecodeSetSelector']. BytecodeSetHasExtensions == false ifTrue: [aCCodeGenerator removeVariable: 'extA'; removeVariable: 'extB']. aCCodeGenerator var: #methodCache declareC: 'sqIntptr_t methodCache[MethodCacheSize + 1 /* ', (MethodCacheSize + 1) printString, ' */]'. NewspeakVM ifTrue: [aCCodeGenerator var: #nsMethodCache declareC: 'sqIntptr_t nsMethodCache[NSMethodCacheSize + 1 /* ', (NSMethodCacheSize + 1) printString, ' */]'] ifFalse: [aCCodeGenerator removeVariable: #nsMethodCache; removeVariable: 'localAbsentReceiver'; removeVariable: 'localAbsentReceiverOrZero']. AtCacheTotalSize isInteger ifTrue: [aCCodeGenerator var: #atCache declareC: 'sqInt atCache[AtCacheTotalSize + 1 /* ', (AtCacheTotalSize + 1) printString, ' */]']. aCCodeGenerator var: #primitiveTable declareC: 'void (*primitiveTable[MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */])(void) = ', vmClass primitiveTableString. vmClass primitiveTable do: [:symbolOrNot| (symbolOrNot isSymbol and: [symbolOrNot ~~ #primitiveFail]) ifTrue: [(aCCodeGenerator methodNamed: symbolOrNot) ifNotNil: [:tMethod| tMethod returnType: #void]]]. vmClass objectMemoryClass hasSpurMemoryManagerAPI ifTrue: [aCCodeGenerator var: #primitiveAccessorDepthTable type: 'signed char' sizeString: 'MaxPrimitiveIndex + 2 /* ', (MaxPrimitiveIndex + 2) printString, ' */' array: vmClass primitiveAccessorDepthTable] ifFalse: [aCCodeGenerator removeVariable: #primitiveAccessorDepthTable]. aCCodeGenerator var: #displayBits type: #'void *'. self declareC: #(displayWidth displayHeight displayDepth) as: #int in: aCCodeGenerator. aCCodeGenerator var: #primitiveFunctionPointer declareC: 'void (*primitiveFunctionPointer)()'; var: #externalPrimitiveTable declareC: 'void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* ', (MaxExternalPrimitiveTableSize + 1) printString, ' */])(void)'; var: #interruptCheckChain declareC: 'void (*interruptCheckChain)(void) = 0'; var: #showSurfaceFn declareC: 'int (*showSurfaceFn)(sqIntptr_t, int, int, int, int)'; var: #jmpBuf declareC: 'jmp_buf jmpBuf[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'; var: #suspendedCallbacks declareC: 'usqInt suspendedCallbacks[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'; var: #suspendedMethods declareC: 'usqInt suspendedMethods[MaxJumpBuf + 1 /* ', (MaxJumpBuf + 1) printString, ' */]'. self declareCAsUSqLong: #(nextPollUsecs nextWakeupUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs "these are high-frequency enough that they're overflowing quite quickly on modern hardware" statProcessSwitch statIOProcessEvents statForceInterruptCheck statCheckForEvents statStackOverflow statStackPageDivorce statIdleUsecs) in: aCCodeGenerator. aCCodeGenerator var: #nextProfileTick type: #sqLong. aCCodeGenerator var: #reenterInterpreter declareC: 'jmp_buf reenterInterpreter; /* private export */'. LowcodeVM ifTrue: [aCCodeGenerator var: #lowcodeCalloutState type: #'sqLowcodeCalloutState*'. self declareC: #(nativeSP nativeStackPointer shadowCallStackPointer) as: #'char *' in: aCCodeGenerator] ifFalse: [#(lowcodeCalloutState nativeSP nativeStackPointer shadowCallStackPointer) do: [:var| aCCodeGenerator removeVariable: var]]. aCCodeGenerator var: #primitiveDoMixedArithmetic + declareC: 'char primitiveDoMixedArithmetic = 1'.! - declareC: 'sqInt primitiveDoMixedArithmetic = 1'.! Item was changed: ----- Method: StackInterpreter class>>mustBeGlobal: (in category 'translation') ----- mustBeGlobal: var + "Answer if a variable must be global and exported. Used for inst vars that are accessed from VM support code, + and for variables that are initialized to some value (e.g. primitiveDoMixedArithmetic)." - "Answer if a variable must be global and exported. Used for inst vars that are accessed from VM support code." ^(super mustBeGlobal: var) or: [(self objectMemoryClass mustBeGlobal: var) or: [(#('interpreterProxy' 'interpreterVersion' 'inIOProcessEvents' 'sendWheelEvents' 'deferDisplayUpdates' 'extraVMMemory' 'showSurfaceFn' 'displayBits' 'displayWidth' 'displayHeight' 'displayDepth' 'desiredNumStackPages' 'desiredEdenBytes' + 'primitiveDoMixedArithmetic' 'breakLookupClassTag' 'breakSelector' 'breakSelectorLength' 'sendTrace' 'checkAllocFiller' 'checkedPluginName' 'reenterInterpreter' 'suppressHeartbeatFlag' 'ffiExceptionResponse' 'debugCallbackInvokes' 'debugCallbackPath' 'debugCallbackReturns') includes: var) or: [ "This allows slow machines to define bytecodeSetSelector as 0 to avoid the interpretation overhead." MULTIPLEBYTECODESETS not and: [var = 'bytecodeSetSelector']]]]! Item was changed: ----- Method: StackInterpreter>>canContextSwitchIfActivating:header: (in category 'message sending') ----- canContextSwitchIfActivating: theMethod header: methodHeader "Context switch should not be allowed on every method activation. In particular the implementation of ensure: and ifCurtailed: depends on there being no suspension point on failing primitive 198 (primitiveMarkUnwindMethod). slowPrimitiveResponse states ``N.B. This means there is no suspension point on primitive failure which methods such as ensure: and ifCurtailed: rely on.'' Rather than prevent context switch on all primitives but the ones we really need to be suspension points (primitiveSignal et al) we choose to allow context switch for all but primitiveMarkUnwindMethod." | primitiveIndex | <api> <inline: true> primitiveIndex := self primitiveIndexOfMethod: theMethod header: methodHeader. ^self cppIf: true ifTrue: [primitiveIndex ~= 198] "primitiveMarkUnwindMethod" ifFalse: [primitiveIndex = 0 or: [(primitiveIndex between: 85 and: 88) "primitiveSignal primitiveWait primitiveResume primitiveSuspend" + or: [primitiveIndex = 167 "primitiveYield" + or: [primitiveIndex between: 185 and: 186 "primitiveExitCriticalSection primitiveEnterCriticalSection"]]]]! - or: [primitiveIndex = 167]]] "primitiveYield"! Item was added: + ----- Method: StackInterpreter>>flushMethodsWithMachineCodePrimitivesAndContinueAnswering: (in category 'primitive support') ----- + flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result + "In the StackInterpreter this is simply a no op"! Item was changed: ----- Method: StackInterpreter>>primitiveDoMixedArithmetic (in category 'primitive support') ----- primitiveDoMixedArithmetic "If primitiveDoMixedArithmetic is true, then primitive can handle the conversions: SmallInteger arithmeticOp: Float (Small or Boxed) SmallInteger compareOp: Float (Small or Boxed) + Else, the primitive fail in case of mixed arithmetic, and conversion should be performed in the image." - Else, the primitive fail in case of mixed arithmetic, and conversion should be performed at image side" <api> + <cmacro: '() primitiveDoMixedArithmetic'> - <cmacro: '() GIV(primitiveDoMixedArithmetic)'> ^primitiveDoMixedArithmetic! Item was removed: - ----- Method: StackInterpreter>>setPrimitiveDoMixedArithmetic: (in category 'primitive support') ----- - setPrimitiveDoMixedArithmetic: aBool - "See #primitiveDoMixedArithmetic method" - primitiveDoMixedArithmetic = aBool ifFalse: [self flushMethodCache]. - primitiveDoMixedArithmetic := aBool! Item was changed: ----- Method: StackInterpreterPrimitives>>primitiveSetVMParameter:arg: (in category 'system control primitives') ----- primitiveSetVMParameter: index arg: argOop "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 = 75 ifTrue: [ arg := objectMemory booleanValueOf: argOop. self failed ifTrue: [^self primitiveFailFor: PrimErrBadArgument]] ifFalse: [(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]]. "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]]. + [75] -> [| mustFlush | + result := objectMemory booleanObjectOf: self primitiveDoMixedArithmetic. + self initPrimCall. + mustFlush := primitiveDoMixedArithmetic ~= arg. + primitiveDoMixedArithmetic := arg. + mustFlush ifTrue: + [self flushMethodCache. + self flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result + "NOT REACHED (in CoInterpreter)"]] } - [75] -> [result := objectMemory booleanObjectOf: self primitiveDoMixedArithmetic. - self setPrimitiveDoMixedArithmetic: arg. - self initPrimCall] } otherwise: []. self successful ifTrue: [self methodReturnValue: result] "return old value" ifFalse: [self primitiveFailFor: PrimErrInappropriate] "attempting to write a read-only or non-existent parameter"! |
Superb :) I'm very happy to not even have tried to do it Le ven. 6 sept. 2019 à 21:56, <[hidden email]> a écrit :
|
Free forum by Nabble | Edit this page |