Branch: refs/heads/virtend
Home: https://github.com/OpenSmalltalk/opensmalltalk-vm
Commit: 579d9ed8df21afa7c0b724635e30e6c4cf71a9ed
https://github.com/OpenSmalltalk/opensmalltalk-vm/commit/579d9ed8df21afa7c0…
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: 2023-02-26 (Sun, 26 Feb 2023)
Changed paths:
M platforms/win32/plugins/CameraPlugin/winCameraOps.cpp
Log Message:
-----------
Fix a regression in unbuffered modes of the win32 CameraPlugin introduced in
commit d51c1ac377067d3e469c111a15d85d4aaa187393
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: Mon Feb 13 16:53:35 2023 -0800
CogVM source as per VMMaker.oscog-eem.3306
Add support for mirroring a frame in the CameraPlugin.
Unimplemented on unix.
Branch: refs/heads/Cog
Home: https://github.com/OpenSmalltalk/opensmalltalk-vm
Commit: 7fc935470cc93eefb5457348460ff27a31f16a43
https://github.com/OpenSmalltalk/opensmalltalk-vm/commit/7fc935470cc93eefb5…
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: 2023-02-26 (Sun, 26 Feb 2023)
Changed paths:
M platforms/win32/plugins/CameraPlugin/winCameraOps.cpp
Log Message:
-----------
Fix a regression in unbuffered modes of the win32 CameraPlugin introduced in
commit d51c1ac377067d3e469c111a15d85d4aaa187393
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: Mon Feb 13 16:53:35 2023 -0800
CogVM source as per VMMaker.oscog-eem.3306
Add support for mirroring a frame in the CameraPlugin.
Unimplemented on unix.
Branch: refs/heads/virtend
Home: https://github.com/OpenSmalltalk/opensmalltalk-vm
Commit: 06f14e7c3cee25876ba2b672bf144ddecb44dbfd
https://github.com/OpenSmalltalk/opensmalltalk-vm/commit/06f14e7c3cee25876b…
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: 2023-02-23 (Thu, 23 Feb 2023)
Changed paths:
M src/spur32.cog.lowcode/cogit.h
M src/spur32.cog.lowcode/cogitARMv5.c
M src/spur32.cog.lowcode/cogitIA32.c
M src/spur32.cog/cogit.h
M src/spur32.cog/cogitARMv5.c
M src/spur32.cog/cogitIA32.c
M src/spur32.sista/cogit.h
M src/spur32.sista/cogitARMv5.c
M src/spur32.sista/cogitIA32.c
M src/spur64.cog.lowcode/cogit.h
M src/spur64.cog.lowcode/cogitARMv8.c
M src/spur64.cog.lowcode/cogitX64SysV.c
M src/spur64.cog.lowcode/cogitX64WIN64.c
M src/spur64.cog/cogit.h
M src/spur64.cog/cogitARMv8.c
M src/spur64.cog/cogitX64SysV.c
M src/spur64.cog/cogitX64WIN64.c
M src/spur64.sista/cogit.h
M src/spur64.sista/cogitARMv8.c
M src/spur64.sista/cogitX64SysV.c
M src/spur64.sista/cogitX64WIN64.c
M src/v3.cog/cogit.h
M src/v3.cog/cogitARMv5.c
M src/v3.cog/cogitIA32.c
Log Message:
-----------
CogVM source as per VMMaker.oscog-eem.3308
Oops! Fix 32-bit builds by providing the relevant null genPrimitiveHighResClock32
Branch: refs/heads/Cog
Home: https://github.com/OpenSmalltalk/opensmalltalk-vm
Commit: 5cb56813a7eb7585ccc7d7621d1cfa589eeaa523
https://github.com/OpenSmalltalk/opensmalltalk-vm/commit/5cb56813a7eb7585cc…
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: 2023-02-23 (Thu, 23 Feb 2023)
Changed paths:
M src/spur32.cog.lowcode/cogit.h
M src/spur32.cog.lowcode/cogitARMv5.c
M src/spur32.cog.lowcode/cogitIA32.c
M src/spur32.cog/cogit.h
M src/spur32.cog/cogitARMv5.c
M src/spur32.cog/cogitIA32.c
M src/spur32.sista/cogit.h
M src/spur32.sista/cogitARMv5.c
M src/spur32.sista/cogitIA32.c
M src/spur64.cog.lowcode/cogit.h
M src/spur64.cog.lowcode/cogitARMv8.c
M src/spur64.cog.lowcode/cogitX64SysV.c
M src/spur64.cog.lowcode/cogitX64WIN64.c
M src/spur64.cog/cogit.h
M src/spur64.cog/cogitARMv8.c
M src/spur64.cog/cogitX64SysV.c
M src/spur64.cog/cogitX64WIN64.c
M src/spur64.sista/cogit.h
M src/spur64.sista/cogitARMv8.c
M src/spur64.sista/cogitX64SysV.c
M src/spur64.sista/cogitX64WIN64.c
M src/v3.cog/cogit.h
M src/v3.cog/cogitARMv5.c
M src/v3.cog/cogitIA32.c
Log Message:
-----------
CogVM source as per VMMaker.oscog-eem.3308
Oops! Fix 32-bit builds by providing the relevant null genPrimitiveHighResClock32
Branch: refs/heads/virtend
Home: https://github.com/OpenSmalltalk/opensmalltalk-vm
Commit: bc49ac6581ea1621e9820127f6a00328c180a80b
https://github.com/OpenSmalltalk/opensmalltalk-vm/commit/bc49ac6581ea1621e9…
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: 2023-02-21 (Tue, 21 Feb 2023)
Changed paths:
M platforms/iOS/plugins/CameraPlugin/AVFoundationVideoGrabber.m
Log Message:
-----------
Oops! the ErrorCode parameter for the CameraPlugin is not needed/should not
be implemented (on macos).
Commit: 885b07470d762993a290888eabc847354eb16289
https://github.com/OpenSmalltalk/opensmalltalk-vm/commit/885b07470d762993a2…
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: 2023-02-22 (Wed, 22 Feb 2023)
Changed paths:
M src/plugins/UnixOSProcessPlugin/UnixOSProcessPlugin.c
M src/spur32.cog.lowcode/cogit.h
M src/spur32.cog.lowcode/cogitARMv5.c
M src/spur32.cog.lowcode/cogitIA32.c
M src/spur32.cog.lowcode/cointerp.c
M src/spur32.cog.lowcode/cointerp.h
M src/spur32.cog.lowcode/gcc3x-cointerp.c
M src/spur32.cog/cogit.h
M src/spur32.cog/cogitARMv5.c
M src/spur32.cog/cogitIA32.c
M src/spur32.cog/cointerp.c
M src/spur32.cog/cointerp.h
M src/spur32.cog/cointerpmt.c
M src/spur32.cog/cointerpmt.h
M src/spur32.cog/gcc3x-cointerp.c
M src/spur32.cog/gcc3x-cointerpmt.c
M src/spur32.sista/cogit.h
M src/spur32.sista/cogitARMv5.c
M src/spur32.sista/cogitIA32.c
M src/spur32.sista/cointerp.c
M src/spur32.sista/cointerp.h
M src/spur32.sista/gcc3x-cointerp.c
M src/spur32.stack.lowcode/gcc3x-interp.c
M src/spur32.stack.lowcode/interp.c
M src/spur32.stack/gcc3x-interp.c
M src/spur32.stack/interp.c
M src/spur32.stack/validImage.c
M src/spur64.cog.lowcode/cogit.h
M src/spur64.cog.lowcode/cogitARMv8.c
M src/spur64.cog.lowcode/cogitX64SysV.c
M src/spur64.cog.lowcode/cogitX64WIN64.c
M src/spur64.cog.lowcode/cointerp.c
M src/spur64.cog.lowcode/cointerp.h
M src/spur64.cog.lowcode/gcc3x-cointerp.c
M src/spur64.cog/cogit.h
M src/spur64.cog/cogitARMv8.c
M src/spur64.cog/cogitX64SysV.c
M src/spur64.cog/cogitX64WIN64.c
M src/spur64.cog/cointerp.c
M src/spur64.cog/cointerp.h
M src/spur64.cog/cointerpmt.c
M src/spur64.cog/cointerpmt.h
M src/spur64.cog/gcc3x-cointerp.c
M src/spur64.cog/gcc3x-cointerpmt.c
M src/spur64.sista/cogit.h
M src/spur64.sista/cogitARMv8.c
M src/spur64.sista/cogitX64SysV.c
M src/spur64.sista/cogitX64WIN64.c
M src/spur64.sista/cointerp.c
M src/spur64.sista/cointerp.h
M src/spur64.sista/gcc3x-cointerp.c
M src/spur64.stack.lowcode/gcc3x-interp.c
M src/spur64.stack.lowcode/interp.c
M src/spur64.stack/gcc3x-interp.c
M src/spur64.stack/interp.c
M src/spur64.stack/validImage.c
M src/v3.cog/cogit.h
M src/v3.cog/cogitARMv5.c
M src/v3.cog/cogitIA32.c
M src/v3.cog/cointerp.c
M src/v3.cog/cointerp.h
M src/v3.cog/gcc3x-cointerp.c
M src/v3.stack/gcc3x-interp.c
M src/v3.stack/interp.c
Log Message:
-----------
CogVM source as per VMMaker.oscog-eem.3307/VMConstruction-Plugins-OSProcessPlugin.oscog-eem.76
Implement a machine code primitive for primitiveHighResClock on 64-bit platforms.
This is faster than the fast-call interpreter primitive by 15% on x86_64 and by
480% on ARMv8 (Apple M1).
Have compilePrimitive use methodOrBlockNumArgs rather than argumentCountOf: methodObj.
Fix the type of semaIndices. This should be int. unsigned char risks corruption
if there are more than 256 external semaphores, which could be the case in a
very complex application.
Fix a few sends of stackIntegerValue: that were not followed by the obligatory
interpreterProxy failed check. I lost patience/time, but this really should be
done. In all VMs, proceeding after a primitive has failed without checking for
primitive failure can have disastrous effects (arguments are popped off the
stack that shouldn't be).
Compare: https://github.com/OpenSmalltalk/opensmalltalk-vm/compare/9ac04b3eab5d...88…
Branch: refs/heads/Cog
Home: https://github.com/OpenSmalltalk/opensmalltalk-vm
Commit: 75b01dac3ee745bab2867f1c56fb2790d57ceee2
https://github.com/OpenSmalltalk/opensmalltalk-vm/commit/75b01dac3ee745bab2…
Author: Eliot Miranda <eliot.miranda(a)gmail.com>
Date: 2023-02-22 (Wed, 22 Feb 2023)
Changed paths:
M src/plugins/UnixOSProcessPlugin/UnixOSProcessPlugin.c
M src/spur32.cog.lowcode/cogit.h
M src/spur32.cog.lowcode/cogitARMv5.c
M src/spur32.cog.lowcode/cogitIA32.c
M src/spur32.cog.lowcode/cointerp.c
M src/spur32.cog.lowcode/cointerp.h
M src/spur32.cog.lowcode/gcc3x-cointerp.c
M src/spur32.cog/cogit.h
M src/spur32.cog/cogitARMv5.c
M src/spur32.cog/cogitIA32.c
M src/spur32.cog/cointerp.c
M src/spur32.cog/cointerp.h
M src/spur32.cog/cointerpmt.c
M src/spur32.cog/cointerpmt.h
M src/spur32.cog/gcc3x-cointerp.c
M src/spur32.cog/gcc3x-cointerpmt.c
M src/spur32.sista/cogit.h
M src/spur32.sista/cogitARMv5.c
M src/spur32.sista/cogitIA32.c
M src/spur32.sista/cointerp.c
M src/spur32.sista/cointerp.h
M src/spur32.sista/gcc3x-cointerp.c
M src/spur32.stack.lowcode/gcc3x-interp.c
M src/spur32.stack.lowcode/interp.c
M src/spur32.stack/gcc3x-interp.c
M src/spur32.stack/interp.c
M src/spur32.stack/validImage.c
M src/spur64.cog.lowcode/cogit.h
M src/spur64.cog.lowcode/cogitARMv8.c
M src/spur64.cog.lowcode/cogitX64SysV.c
M src/spur64.cog.lowcode/cogitX64WIN64.c
M src/spur64.cog.lowcode/cointerp.c
M src/spur64.cog.lowcode/cointerp.h
M src/spur64.cog.lowcode/gcc3x-cointerp.c
M src/spur64.cog/cogit.h
M src/spur64.cog/cogitARMv8.c
M src/spur64.cog/cogitX64SysV.c
M src/spur64.cog/cogitX64WIN64.c
M src/spur64.cog/cointerp.c
M src/spur64.cog/cointerp.h
M src/spur64.cog/cointerpmt.c
M src/spur64.cog/cointerpmt.h
M src/spur64.cog/gcc3x-cointerp.c
M src/spur64.cog/gcc3x-cointerpmt.c
M src/spur64.sista/cogit.h
M src/spur64.sista/cogitARMv8.c
M src/spur64.sista/cogitX64SysV.c
M src/spur64.sista/cogitX64WIN64.c
M src/spur64.sista/cointerp.c
M src/spur64.sista/cointerp.h
M src/spur64.sista/gcc3x-cointerp.c
M src/spur64.stack.lowcode/gcc3x-interp.c
M src/spur64.stack.lowcode/interp.c
M src/spur64.stack/gcc3x-interp.c
M src/spur64.stack/interp.c
M src/spur64.stack/validImage.c
M src/v3.cog/cogit.h
M src/v3.cog/cogitARMv5.c
M src/v3.cog/cogitIA32.c
M src/v3.cog/cointerp.c
M src/v3.cog/cointerp.h
M src/v3.cog/gcc3x-cointerp.c
M src/v3.stack/gcc3x-interp.c
M src/v3.stack/interp.c
Log Message:
-----------
CogVM source as per VMMaker.oscog-eem.3307/VMConstruction-Plugins-OSProcessPlugin.oscog-eem.76
Implement a machine code primitive for primitiveHighResClock on 64-bit platforms.
This is faster than the fast-call interpreter primitive by 15% on x86_64 and by
480% on ARMv8 (Apple M1).
Have compilePrimitive use methodOrBlockNumArgs rather than argumentCountOf: methodObj.
Fix the type of semaIndices. This should be int. unsigned char risks corruption
if there are more than 256 external semaphores, which could be the case in a
very complex application.
Fix a few sends of stackIntegerValue: that were not followed by the obligatory
interpreterProxy failed check. I lost patience/time, but this really should be
done. In all VMs, proceeding after a primitive has failed without checking for
primitive failure can have disastrous effects (arguments are popped off the
stack that shouldn't be).
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.3307.mcz
==================== Summary ====================
Name: VMMaker.oscog-eem.3307
Author: eem
Time: 22 February 2023, 6:19:12.024382 pm
UUID: bea33bb5-98d1-4d1a-8004-40be76e0b94c
Ancestors: VMMaker.oscog-eem.3306
Implement a machine code primitive for primitiveHighResClock on 64-bit platforms. This is faster than the fast-call interpreter primitive by 15% on x86_64 and by 480% on ARMv8 (Apple M1). Have compilePrimitive use methodOrBlockNumArgs rather than argumentCountOf: methodObj.
=============== Diff against VMMaker.oscog-eem.3306 ===============
Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveHighResClock32 (in category 'primitive generators') -----
+ genPrimitiveHighResClock32
+ <inline: true>
+ "This awaits a 32-bit implementation of genAlloc64BitPositiveIntegerValue:into:scratchReg:scratchReg:..."
+ ^UnimplementedPrimitive!
Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genPrimitiveHighResClock64 (in category 'primitive generators') -----
+ genPrimitiveHighResClock64
+ <inline: true>
+ | reg jumpFailAlloc jumpNotSmallInteger |
+ cogit backEnd has64BitPerformanceCounter ifFalse:
+ [^UnimplementedPrimitive].
+ reg := cogit backEnd preferredRegisterForMovePerfCnt64RL = NoReg
+ ifTrue: [Arg0Reg]
+ ifFalse: [cogit backEnd preferredRegisterForMovePerfCnt64RL].
+ self assert: (cogit register: reg isNotInMask: (cogit registerMaskFor: ReceiverResultReg and: Arg1Reg and: Extra0Reg and: Extra1Reg)).
+ cogit
+ MovePerfCnt64R: reg L: (cogit registerMaskFor: NoReg);
+ LogicalShiftRightCq: self numSmallIntegerBits - 1 R: reg R: Arg1Reg. "If in range this is now 0"
+ (cogit lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
+ [cogit CmpCq: 0 R: Arg1Reg]. "N.B. FLAGS := ClassReg - 0"
+ jumpNotSmallInteger := cogit JumpNonZero: 0.
+ self genConvertIntegerInReg: reg toSmallIntegerInReg: ReceiverResultReg.
+ cogit genPrimReturn.
+ jumpNotSmallInteger jmpTarget: cogit Label.
+ jumpFailAlloc := self genAlloc64BitPositiveIntegerValue: reg into: ReceiverResultReg scratchReg: Extra0Reg scratchReg: Extra1Reg.
+ cogit MoveR: SendNumArgsReg R: ReceiverResultReg.
+ cogit genPrimReturn.
+ jumpFailAlloc jmpTarget: cogit Label.
+ ^0!
Item was changed:
----- Method: CurrentImageCoInterpreterFacade>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'accessing') -----
functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr
primIndex = PrimNumberExternalCall ifTrue:
[flagsPtr
at: 0
put: (coInterpreter
primitivePropertyFlagsFor: (self primitiveMethodForMethodContainingExternalPrimitive: methodOop)
primitiveIndex: primIndex).
+ ^((self objectForOop: methodOop) literalAt: 1) second].
- ^self oopForObject: ((self objectForOop: methodOop) literalAt: 1) second].
^(coInterpreter functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr) ifNotNil:
[:symbol| self addressForLabel: symbol]!
Item was changed:
----- Method: InterpreterPrimitives>>primitiveHighResClock (in category 'system control primitives') -----
primitiveHighResClock
"Return the value of the high resolution clock if this system has any.
The exact frequency of the high res clock is undefined specifically so that we can use
processor dependent instructions (like RDTSC). The only use for the high res clock is for
profiling where we can allocate time based on sub-msec resolution of the high res clock.
If no high-resolution counter is available, the platform should return zero. ar 6/22/2007"
<export: true>
+ <api>
<primitiveMetadata: #FastCPrimitiveFlag>
self methodReturnValue: (self positive64BitIntegerFor: self ioHighResClock)!
Item was changed:
----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive:flags: (in category 'primitive generators') -----
compileInterpreterPrimitive: primitiveRoutine flags: flags
"Compile a call to an interpreter primitive. Call the C routine with the
usual stack-switching dance, test the primFailCode and then either
return on success or continue to the method body."
<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
| jmp continueAfterProfileSample jumpToTakeSample |
+ self cCode: '' inSmalltalk:
+ [primitiveRoutine isSymbol ifTrue:
+ [^self compileInterpreterPrimitive: (self simulatedAddressFor: primitiveRoutine) flags: flags]].
+
self deny: (backEnd hasVarBaseRegister
and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
self genExternalizePointersForPrimitiveCall.
"Switch to the C stack."
self genLoadCStackPointersForPrimCall.
"Old old full prim trace is in VMMaker-eem.550 and prior.
Old simpler full prim trace is in VMMaker-eem.2969 and prior."
(coInterpreter recordPrimTraceForMethod: methodObj) ifTrue:
[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
"Clear the primFailCode and set argumentCount"
self MoveCq: 0 R: TempReg.
self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
methodOrBlockNumArgs ~= 0 ifTrue:
[self AddCq: methodOrBlockNumArgs R: TempReg]. "As small or smaller than move on most archs"
self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
"If required, set newMethod"
(flags anyMask: PrimCallNeedsNewMethod) ifTrue:
[self genLoadNewMethod].
"Invoke the primitive. If the primitive (potentially) contains a call-back then its code
may disappear and consequently we cannot return here, since here may evaporate.
Instead sideways-call the routine, substituting cePrimReturnEnterCogCode[Profiling]
as the return address, so the call always returns there."
self PrefetchAw: coInterpreter primFailCodeAddress.
(flags anyMask: PrimCallMayEndureCodeCompaction) ifTrue:
["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
needsFrame := true.
backEnd
genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil;
genSubstituteReturnAddress:
((flags anyMask: PrimCallCollectsProfileSamples)
ifTrue: [cePrimReturnEnterCogCodeProfiling]
ifFalse: [cePrimReturnEnterCogCode]).
self JumpFullRT: primitiveRoutine asInteger.
^0].
"Call the C primitive routine."
backEnd genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil.
self CallFullRT: primitiveRoutine asInteger.
backEnd genRemoveNArgsFromStack: 0.
objectRepresentation maybeCompileRetryOf: primitiveRoutine onPrimitiveFail: primitiveIndex flags: flags.
"Switch back to the Smalltalk stack. Stack better be in either of these two states:
success: stackPointer -> result (was receiver)
arg1
...
argN
return pc
failure: receiver
arg1
...
stackPointer -> argN
return pc"
backEnd genLoadStackPointersForPrimCall: ClassReg.
"genLoadStackPointersForPrimCall: leaves the stack in these states:
NoLinkRegister LinkRegister
success: result (was receiver) stackPointer -> result (was receiver)
stackPointer -> arg1 arg1
... ...
argN argN
return pc
failure: receiver receiver
arg1 arg1
... ...
argN stackPointer -> argN
stackPointer -> return pc
which corresponds to the stack on entry after pushRegisterArgs.
In either case we can write the instructionPointer to top of stack or load it into the LinkRegister to reestablish the return pc."
backEnd hasLinkRegister
ifTrue:
[self MoveAw: coInterpreter instructionPointerAddress R: LinkReg]
ifFalse:
[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
self MoveR: ClassReg Mw: 0 r: SPReg].
"Test primitive failure"
self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
self flag: 'ask concrete code gen if move sets condition codes?'.
self CmpCq: 0 R: TempReg.
jmp := self JumpNonZero: 0.
"placing the test here attributes the tick to the primitive plus any checkForAndFollowForwardedPrimitiveState
scanning, but attributes all of a failing primitive to the current method (in ceStackOverflow: on frame build)."
(backEnd has64BitPerformanceCounter
and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
[jumpToTakeSample := self genCheckForProfileTimerTick: (self registerMaskFor: NoReg)].
"Fetch result from stack"
continueAfterProfileSample :=
self MoveMw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
r: SPReg
R: ReceiverResultReg.
self RetN: objectMemory wordSize. "return to caller, popping receiver"
(backEnd has64BitPerformanceCounter
and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
[jumpToTakeSample jmpTarget: self Label.
self genTakeProfileSample.
backEnd genLoadStackPointerForPrimCall: ClassReg.
backEnd hasLinkRegister
ifTrue:
[self MoveAw: coInterpreter instructionPointerAddress R: LinkReg]
ifFalse:
[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
self MoveR: ClassReg Mw: 0 r: SPReg].
self Jump: continueAfterProfileSample].
"Jump to restore of receiver reg and proceed to frame build for failure."
jmp jmpTarget: self Label.
"Restore receiver reg from stack. If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
self MoveMw: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
r: SPReg
R: ReceiverResultReg.
^0!
Item was changed:
----- Method: SimpleStackBasedCogit>>compileOnStackExternalPrimitive:flags: (in category 'primitive generators') -----
compileOnStackExternalPrimitive: primitiveRoutine flags: flags
"Compile a fast call of a C primitive using the current stack page, avoiding the stack switch except on failure.
This convention still uses stackPointer and argumentCount to access operands. Push all operands to the stack,
assign stackPointer, argumentCount, and zero primFailCode. Make the call (saving a LinkReg if required).
Test for failure and return. On failure on Spur, if there is an accessor depth, assign framePointer and newMethod,
do the stack switch, call checkForAndFollowForwardedPrimitiveState, and loop back if forwarders are found.
Fall through to frame build."
<option: #SpurObjectMemory>
<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
| calleeSavedRegisterMask linkRegSaveRegister spRegSaveRegister jmpFail retry continueAfterProfileSample jumpToTakeSample |
+ self cCode: '' inSmalltalk:
+ [primitiveRoutine isSymbol ifTrue:
+ [^self compileOnStackExternalPrimitive: (self simulatedAddressFor: primitiveRoutine) flags: flags]].
+
self assert: (objectRepresentation hasSpurMemoryManagerAPI and: [flags anyMask: PrimCallOnSmalltalkStack]).
self deny: (backEnd hasVarBaseRegister
and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
(coInterpreter recordFastCCallPrimTraceForMethod: methodObj) ifTrue:
[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
"Clear the primFailCode and set argumentCount"
self MoveCq: 0 R: TempReg.
self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
methodOrBlockNumArgs ~= 0 ifTrue:
[self AddCq: methodOrBlockNumArgs R: TempReg]. "As small or smaller than move on most archs"
self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
self genExternalizeStackPointerForFastPrimitiveCall.
"We may need to save LinkReg and/or SPReg, and given the stack machinations
it is much easier to save them in callee saved registers than on the stack itself."
calleeSavedRegisterMask := ABICalleeSavedRegisterMask bitClear: (self registerMaskFor: ClassReg).
backEnd hasLinkRegister ifTrue:
[linkRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
self deny: linkRegSaveRegister = NoReg.
self MoveR: LinkReg R: linkRegSaveRegister.
calleeSavedRegisterMask := calleeSavedRegisterMask bitClear: (self registerMaskFor: linkRegSaveRegister)].
spRegSaveRegister := NoReg.
(SPReg ~= NativeSPReg
and: [(self isCalleeSavedReg: SPReg) not]) ifTrue:
[spRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
self deny: spRegSaveRegister = NoReg.
self MoveR: SPReg R: spRegSaveRegister].
retry := self Label.
(flags anyMask: PrimCallOnSmalltalkStackAlign2x)
ifTrue: [self AndCq: (objectMemory wordSize * 2 - 1) bitInvert R: SPReg R: NativeSPReg]
ifFalse:
[SPReg ~= NativeSPReg ifTrue:
[backEnd genLoadNativeSPRegWithAlignedSPReg]].
backEnd genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil.
"If the primitive is in the interpreter then its address won't change relative to the code zone over time,
whereas if it is in a plugin its address could change if the module is un/re/over/loaded.
So if in the interpreter and in range use a normal call instruction."
((flags noMask: PrimCallIsExternalCall)
and: [backEnd isWithinCallRange: primitiveRoutine asInteger])
ifTrue: [self CallRT: primitiveRoutine asInteger]
ifFalse: [self CallFullRT: primitiveRoutine asInteger].
backEnd genRemoveNArgsFromStack: 0.
"test primFailCode and jump to failure sequence if non-zero"
self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
spRegSaveRegister ~= NoReg ifTrue:
[self MoveR: spRegSaveRegister R: SPReg].
self CmpCq: 0 R: TempReg.
jmpFail := self JumpNonZero: 0.
"Remember to restore the native stack pointer to point to the C stack,
otherwise the Smalltalk frames will get overwritten on an interrupt."
SPReg ~= NativeSPReg ifTrue:
[backEnd genLoadCStackPointer].
"placing the test here attributes the tick to the primitive plus any checkForAndFollowForwardedPrimitiveState
scanning, but attributes all of a failing primitive to the current method (in ceStackOverflow: on frame build)."
(backEnd has64BitPerformanceCounter
and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
[jumpToTakeSample := self genCheckForProfileTimerTick: (self registerMaskFor: NoReg)].
"At this point the primitive has cut back stackPointer to point to the result."
continueAfterProfileSample :=
self MoveAw: coInterpreter stackPointerAddress R: TempReg.
"get result and restore retpc"
backEnd hasLinkRegister
ifTrue:
[self MoveMw: 0 r: TempReg R: ReceiverResultReg;
AddCq: objectMemory wordSize R: TempReg R: SPReg;
MoveR: linkRegSaveRegister R: LinkReg]
ifFalse:
[| retpcOffset |
"The original retpc is (argumentCount + 1) words below stackPointer."
retpcOffset := (methodOrBlockNumArgs + 1 * objectMemory wordSize) negated.
self MoveMw: retpcOffset r: TempReg R: ClassReg; "get retpc"
MoveR: TempReg R: SPReg;
MoveMw: 0 r: TempReg R: ReceiverResultReg;
MoveR: ClassReg Mw: 0 r: TempReg "put it back on stack for the return..."].
self RetN: 0.
(backEnd has64BitPerformanceCounter
and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
[jumpToTakeSample jmpTarget: self Label.
self genTakeProfileSample.
self Jump: continueAfterProfileSample].
"primitive failure. if there is an accessor depth, scan and retry on failure (but what if faling for out of memory?)"
jmpFail jmpTarget: self Label.
(coInterpreter accessorDepthForPrimitiveMethod: methodObj) >= 0
ifTrue:
[| skip |
"Given that following primitive state to the accessor depth is recursive, we're asking for
trouble if we run the fixup on the Smalltalk stack page. Run it on the full C stack instead.
This won't be a performance issue since primitive failure should be very rare."
self MoveR: FPReg Aw: coInterpreter framePointerAddress.
self MoveCw: primitiveRoutine asInteger R: TempReg.
self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress.
self genLoadNewMethod.
self genLoadCStackPointersForPrimCall.
backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
(backEnd isWithinCallRange: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState]))
ifTrue:
[self CallRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState])]
ifFalse:
[self CallFullRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState])].
backEnd genLoadStackPointersForPrimCall: ClassReg.
self CmpCq: 0 R: ABIResultReg.
skip := self JumpZero: 0.
self MoveCq: 0 R: TempReg.
self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
self Jump: retry.
skip jmpTarget: self Label]
ifFalse: "must reload SPReg to undo any alignment change,"
[(flags anyMask: PrimCallOnSmalltalkStackAlign2x) ifTrue:
[backEnd hasLinkRegister
ifTrue:
[self MoveAw: coInterpreter stackPointerAddress R: SPReg]
ifFalse: "remember to include return address; use scratch to avoid an interrupt overwriting retpc"
[self MoveAw: coInterpreter stackPointerAddress R: TempReg.
self SubCq: objectRepresentation wordSize R: TempReg.
self MoveR: TempReg R: SPReg]]].
"Remember to restore the native stack pointer to point to the C stack,
otherwise the Smalltalk frames will get overwritten on an interrupt."
SPReg ~= NativeSPReg ifTrue:
[backEnd genLoadCStackPointer].
"The LinkRegister now contains the return address either of the primitive call or of checkForAndFollowForwardedPrimitiveState.
It must be restored to the return address of the send invoking this primtiive method."
backEnd hasLinkRegister ifTrue:
[self MoveR: linkRegSaveRegister R: LinkReg].
"Finally remember to reload ReceiverResultReg if required. Even if
arguments have been pushed, the prolog sequence assumes it is live."
(self register: ReceiverResultReg isInMask: ABICallerSavedRegisterMask) ifTrue:
[self MoveMw: (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1])) * objectMemory wordSize
r: SPReg
R: ReceiverResultReg].
"continue to frame build..."
^0!
Item was changed:
----- Method: SimpleStackBasedCogit>>compilePrimitive (in category 'primitive generators') -----
compilePrimitive
"Compile a primitive. If possible, performance-critical primitives will
be generated by their own routines (primitiveGenerator). Otherwise,
if there is a primitive at all, we call the C routine with the usual
stack-switching dance, test the primFailCode and then either return
on success or continue to the method body."
<inline: false>
+ | primitiveDescriptor primitiveRoutine code flags |
- | primitiveDescriptor primitiveRoutine flags |
<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
primitiveIndex = 0 ifTrue: [^0].
"If a descriptor specifies an argument count (by numArgs >= 0) then it must match
for the generated code to be correct. For example for speed many primitives use
ResultReceiverReg instead of accessing the stack, so the receiver better be at
numArgs down the stack. Use the interpreter version if not."
((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
and: [primitiveDescriptor primitiveGenerator notNil
and: [(primitiveDescriptor primNumArgs < 0 "means generator doesn't care"
+ or: [primitiveDescriptor primNumArgs = methodOrBlockNumArgs])]]) ifTrue:
+ [| opcodeIndexAtPrimitive |
- or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)])]]) ifTrue:
- [| opcodeIndexAtPrimitive code |
"Note opcodeIndex so that any arg load instructions
for unimplemented primitives can be discarded."
opcodeIndexAtPrimitive := opcodeIndex.
code := objectRepresentation perform: primitiveDescriptor primitiveGenerator.
(code < 0 and: [code ~= UnimplementedPrimitive]) ifTrue: "Generator failed, so no point continuing..."
[^code].
"If the primitive can never fail then there is nothing more that needs to be done."
code = UnfailingPrimitive ifTrue:
[^0].
"If the machine code version handles all cases the only reason to call the interpreter
primitive is to reap the primitive error code. Don't bother if it isn't used."
(code = CompletePrimitive
and: [(self methodUsesPrimitiveErrorCode: methodObj header: methodHeader) not]) ifTrue:
[^0].
"Discard any arg load code generated by the primitive generator."
code = UnimplementedPrimitive ifTrue:
[opcodeIndex := opcodeIndexAtPrimitive]].
primitiveRoutine := coInterpreter
functionPointerForCompiledMethod: methodObj
primitiveIndex: primitiveIndex
primitivePropertyFlagsInto: (self addressOf: flags put: [:val| flags := val]).
(primitiveRoutine = 0 "no primitive"
or: [primitiveRoutine = (self cCoerceSimple: #primitiveFail to: 'void (*)(void)')]) ifTrue:
[^self genFastPrimFail].
+ (backEnd has64BitPerformanceCounter
+ and: [primitiveRoutine = (self cCoerceSimple: #primitiveHighResClock to: 'void (*)(void)')
+ and: [methodOrBlockNumArgs = 0]]) ifTrue:
+ [objectRepresentation wordSize = 8
+ ifTrue: [code := objectRepresentation genPrimitiveHighResClock64]
+ ifFalse: [code := objectRepresentation genPrimitiveHighResClock32].
+ code ~= UnimplementedPrimitive ifTrue:
+ [^code]].
+
(objectRepresentation hasSpurMemoryManagerAPI
and: [flags anyMask: PrimCallOnSmalltalkStack]) ifTrue:
[^self compileOnStackExternalPrimitive: primitiveRoutine flags: flags].
^self compileInterpreterPrimitive: primitiveRoutine flags: flags!