embedding assembler in Pharo method using NativeBoost

Hooray!

L


test code:

fr1 := GMPfrWrapper new.  "create new GNU mpfr floating point number"
fr1 prim_mpfr_prec_roundWithPrecision:4096 withRounding: 0. "set to 4096 digits of precision"
fr1 set_d: 1.           "set it to 1.0"



"perform 10,000,000 4096-digit  additions fr1 := fr1 + fr1 in a loop"
[fr1 test:10000000.] timeToRun    =>1971 ms




GMPfrWrapper>>test:cnt

"function prototype: mpfr_add (mpzf_t gmpf, mpf_t op1, mpf_t op2)"

    <primitive: #primitiveNativeCall module: #NativeBoostPlugin>

    ^ NBFFICallout cdecl: #( void (mpfr_t gmpfr, ulong cnt))
    emitCall: [:gen | | asm  proxy smpfr scnt|
        asm := gen asm.
        proxy := gen proxy.

        "reserve temps for parameters passed in from Smalltalk"
        smpfr := gen reserveTemp.
        scnt := gen reserveTemp.

        "move parameters into temps"

        asm
                   mov: asm ESP ptr to:  asm EAX;
                 mov: asm EAX to: smpfr;   "gmpfr -> smpfr"
                   mov: asm ESP ptr + 4 to: asm EAX;
            mov: asm EAX to: scnt.  "cnt -> scnt"


"setup loop compare and jmp or push ECX and pass through to function call"
        asm
            mov: scnt to: asm ECX;
            label: #top;
            cmp: asm ECX with: 0;
            jz: #bottom;
            push: asm ECX.

        "call function"

asm cdeclCall: [:call | | gmpfrAddFcnPtr | "handles stack alignment"

"push function arguments (note, cdecl push order is from right to left ) "
        asm
            push: smpfr;
            push: smpfr;
            push: smpfr.

        "get a function address"
gmpfrAddFcnPtr := self nbGetSymbolAddress: 'mpfr_add' module:self nbLibraryNameOrHandle.


        "put a function address into EAX, and call function "

           asm mov: gmpfrAddFcnPtr asUImm to: asm EAX.
           asm call: asm EAX.


    ] alignment: gen stackAlignment .

    "restore ECX and jump to top for test"

    asm
        pop: asm ECX;
        dec: asm ECX;
        jmp: #top.

    asm label: #bottom.

    ]

--
Squeak from the very start (introduction to Squeak and Pharo Smalltalk for the 
(almost) complete and compleate beginner).
https://www.youtube.com/playlist?list=PL6601A198DF14788D&feature=view_all


Reply via email to