• Welcome to Jose's Read Only Forum 2023.
 

Different techniques for calling methods in COM-like objects

Started by Charles Pegge, January 16, 2008, 04:55:22 PM

Previous topic - Next topic

0 Members and 1 Guest are viewing this topic.

Charles Pegge

The COM-like object contains a set of elements, the first of which is an address to its table of methods. There are numerable ways to access the methods, some more elegant than others. Below is an extremely simple example (no parameters) showing 4 ways of doing it in PB. The first does it with assembler very cleanly. It only takes 6 bytes! Unfortunately there is an omission in the PB inline assembler, so we have to do the indirect call in opcodes but that is no great burden. The x86 is in fact very good at handling indirection and makes most high level language techniques look very confusing.




#COMPILE EXE
#DIM ALL

' Different ways of Calling methods/procedures in COM-like objects


' some test procedures

    SUB proc1: MSGBOX "Proc1":END SUB
    SUB proc2: MSGBOX "Proc2":END SUB
    SUB proc3: MSGBOX "Proc3":END SUB
    SUB proc4: MSGBOX "Proc4":END SUB

FUNCTION PBMAIN () AS LONG
    #REGISTER NONE
    LOCAL p AS LONG PTR '

    'create virtual table of functions

        LOCAL tbl AS STRING*16
        tbl=MKL$(CODEPTR(proc1))+MKL$(CODEPTR(proc2))+MKL$(CODEPTR(proc3))+MKL$(CODEPTR(proc4))

    'create an object

        LOCAL obj AS STRING*12
        'first element contains a pointer to the table of procedures
        obj=MKL$(VARPTR(tbl))

    '-----------------------------------------
    ' Techniques for calling one of the SUBs
    '-----------------------------------------


    'call the third procedure using Assembler (6 bytes)

        ! mov eax,obj       ' get the first element of obj (containing table address
        ! db &hff,&h50,&h08 ' equivalent ! call [eax+08] ' calls the procedure indirectly from table

       
    'call the third procedure using an absolute array

        DIM t(3) AS LONG AT CVL(obj)
        CALL DWORD t(2)

    'call the third procedure using classical basic syntax

        p=CVL(obj)          ' get the table address
        p=PEEK(LONG,p+8)    ' get the 3rd proc address from the table
        CALL DWORD p        ' call the proc


    'call the third procedure using PB pointers

        p=VARPTR(obj)       ' get the address of the object
        p=@p+8              ' get the address of the proc table 3rd element
        CALL DWORD @p       ' call the proc address contained there
        ' CALL DWORD @@p[2]    ' does the same as the above two lines


END FUNCTION

MikeTrader

Very Interesting.
So a Call like this:

DECLARE FUNCTION Proto_IStorage_CreateStream (BYVAL pthis AS DWORD PTR, BYVAL pwcsName AS DWORD, BYVAL grfMode AS DWORD, BYVAL reserved1 AS DWORD, BYVAL reserved2 AS DWORD, BYREF ppstm AS DWORD) AS LONG

FUNCTION IStorage_CreateStream ALIAS "IStorage_CreateStream" (BYVAL pthis AS DWORD PTR, BYVAL strName AS STRING, BYVAL grfMode AS DWORD) EXPORT AS DWORD
    strName = UCODE$(strName)
    LOCAL ppstm AS DWORD
    IF ISFALSE pthis THEN STG_ERROR_HRESULT = %E_POINTER : EXIT FUNCTION
    CALL DWORD @@pthis[3] USING Proto_IStorage_CreateStream(pthis, STRPTR(strName), grfMode, %NULL, %NULL, ppstm) TO STG_ERROR_HRESULT
    FUNCTION = ppstm
END FUNCTION


you would replace:
CALL DWORD @@pthis[3]

with ASM Opcodes after pushing the arguments onto the stack?


Charles Pegge

#2
Well this is quite a handful. pthis has an additional level of indirection from the example above, because pthis is a pointer to the object. The parameters are stacked in reverse order as per STDCALL.

I don't have the supporting code to test it but I persuaded it to compile. The compiler will produce very similar output to this hand assembled code, but it is interesting to see what the expressions required to do the deed look like in comparison to each other.




DECLARE FUNCTION Proto_IStorage_CreateStream (BYVAL pthis AS DWORD PTR, BYVAL pwcsName AS DWORD, BYVAL grfMode AS DWORD, BYVAL reserved1 AS DWORD, BYVAL reserved2 AS DWORD, BYREF ppstm AS DWORD) AS LONG

' ANALYSIS of indirection:
' pthis contains the address of the object
' @pthis is the first element of the object and contains the address of the virtual function table
' @@pthis[3] is the value in the fourth element in the function table and is the address of the function to call


FUNCTION IStorage_CreateStream ALIAS "IStorage_CreateStream" (BYVAL pthis AS DWORD PTR, BYVAL strName AS STRING, BYVAL grfMode AS DWORD) EXPORT AS DWORD
    strName = UCODE$(strName)
    LOCAL ppstm AS DWORD
    IF ISFALSE pthis THEN STG_ERROR_HRESULT = %E_POINTER : EXIT FUNCTION
    ' CALL DWORD @@pthis[3]
    'USING Proto_IStorage_CreateStream
    '(pthis,
    'STRPTR(strName),
    'grfMode,
    '%NULL,
    '%NULL,
    'ppstm)
    'TO STG_ERROR_HRESULT
    ' The [arams are stacked in reverse order
    LOCAL v AS LONG             ' temp variable
    v=VARPTR(ppstm)             ' to pass ppstm address
    ! push eax                  ' varptr leaves result in eax so push it
    ! xor eax,eax               ' eax zeroed
    ! push eax                  ' push null for reserved2
    ! push eax                  ' push null for reserved1
    ! push grfMode              ' push value
    v=STRPTR(strName)           ' string point to eax
    ! push eax                  ' push string pointer
    ! mov ecx,pthis             ' get the object pointer
    ! push ecx
    ! mov eax,[ecx]             ' get the 1st element value containing the table address
    ! db &hff, &h50, &h0c       ' call [eax+12] ' call indirect usting the address in the 3rd table element
      '! mov eax,[eax+12]       ' Alternative way of doing this which PB ASM will accept
      '! call eax               '
    ! mov STG_ERROR_HRESULT,eax ' result returned in eax
    FUNCTION = ppstm
END FUNCTION


MikeTrader

Very interesting Charles.
I assume this would be a lot faster if the function was called many times?


         
' ****************************************************************************************
' Mike Trader Jan 2008
' Calling COM object with ASM example
' ****************************************************************************************

#COMPILE EXE
#DIM ALL
#INCLUDE "Win32Api.inc"
#INCLUDE "Stream.inc"   
             
GLOBAL hDbg AS LONG 
                     


' ****************************************************************************************
' ANALYSIS of indirection:
' pthis contains the address of the object
' @pthis is the first element of the object and contains the address of the virtual function table
' @@pthis[3] is the value in the fourth element in the function table and is the address of the function to call


FUNCTION IStorage_CreateStreamASM ALIAS "IStorage_CreateStreamASM" (BYVAL pthis AS DWORD PTR, BYVAL strName AS STRING, BYVAL grfMode AS DWORD) EXPORT AS DWORD
             
    LOCAL ppstm AS DWORD

    strName = UCODE$(strName)
 
    IF ISFALSE pthis THEN STG_ERROR_HRESULT = %E_POINTER : EXIT FUNCTION

    ' CALL DWORD @@pthis[3]
    'USING Proto_IStorage_CreateStream
    '(pthis,
    'STRPTR(strName),
    'grfMode,
    '%NULL,
    '%NULL,
    'ppstm)
    'TO STG_ERROR_HRESULT
    ' The params are stacked in reverse order 

    LOCAL v AS LONG             ' temp variable

    v=VARPTR(ppstm)             ' to pass ppstm address
    ! push eax                  ' varptr leaves result in eax so push it
    ! XOR eax,eax               ' eax zeroed
    ! push eax                  ' push null for reserved2
    ! push eax                  ' push null for reserved1
    ! push grfMode              ' push value
    v=STRPTR(strName)           ' string point to eax
    ! push eax                  ' push string pointer
    ! mov ecx,pthis             ' get the object pointer
    ! push ecx
    ! mov eax,[ecx]             ' get the 1st element value containing the table address
    ! db &hff, &h50, &h0c       ' call [eax+12] ' call indirect using the address in the 3rd table element 

'   ! mov eax,[eax+12]          ' Alternative way of doing this which PB ASM will accept
'   ! CALL eax 
             '
    ! mov STG_ERROR_HRESULT,eax ' result returned in eax 

  FUNCTION = ppstm   

END FUNCTION
   


' ****************************************************************************************
FUNCTION PBMAIN () AS LONG                     
                 
  LOCAL i, hFile, nFiles, RetVal AS LONG   
  LOCAL ppStorage, ppStream, pStg AS DWORD
  LOCAL t, sBuff AS STRING


    sBuff  = STRING$( 22, "*" ) '
                                                     
    '- Structured storage                           %STGM_SIMPLE ?
    ppStorage = Storage_CreateStorageEx("Test.stg", %STGM_CREATE OR %STGM_READWRITE OR %STGM_SHARE_EXCLUSIVE, %STGFMT_STORAGE, 0, 0) ' %STGM_CREATE OR %STGM_DIRECT OR %STGM_SHARE_EXCLUSIVE OR %STGM_READWRITE )
    '================

    IF ISFALSE ppStorage THEN
      IF StgResult = &h800300FF THEN
        MSGBOX "Storage_CreateDocFile failure: STG_E_INVALIDFLAG Indicates a non-valid flag combination in the grfMode parameter: " + HEX$(StgResult)
      ELSE
        MSGBOX "Storage_CreateDocFile failure: " + HEX$(StgResult)
      END IF
      EXIT FUNCTION
    END IF       

    ppStream = IStorage_CreateStreamASM( ppStorage, "MyStream",  %STGM_DIRECT OR %STGM_CREATE OR %STGM_WRITE OR %STGM_SHARE_EXCLUSIVE )
    IF ISFALSE ppStream THEN
      MSGBOX "IStorage_CreateStream failure " + HEX$(StgResult)
    EXIT FUNCTION
    END IF
           
    IF ISequentialStream_Write( ppStream, STRPTR(sBuff), LEN(sBuff) ) = 0 THEN ' Save a DWORD variable
      MSGBOX "SequentialStream_Write Failed",48,"ERROR" 
      EXIT FUNCTION
    END IF 
    IF ppStream THEN StgRelease ppStream : ppStream = 0
    '================       

                 
    ppStream = IStorage_OpenStream(ppStorage, "MyStream", %STGM_READ OR %STGM_SHARE_EXCLUSIVE ) ' %STGM_DIRECT OR %STGM_READWRITE OR %STGM_SHARE_EXCLUSIVE)
    IF ISFALSE ppStream THEN
      MSGBOX "IStorage_OpenStream failure: " & HEX$(StgResult)
      EXIT FUNCTION
    END IF
    t = t + IStream_ReadText(ppStream) + $CRLF '
    IF ppStream THEN StgRelease ppStream : ppStream = 0
    '================   

    IF ppStorage THEN StgRelease ppStorage : ppStorage = 0 ' Don't Call twice! 
    '================

  MSGBOX t,64,"All Done"   

END FUNCTION 

' ****************************************************************************************

stream.inc here;
http://www.jose.it-berater.org/smfforum/index.php?topic=1537.msg5025#msg5025


    ! mov STG_ERROR_HRESULT,eax ' result returned in eax
How do you know this?

Charles Pegge

An HRESULT is an Integer.

Returning integer results in EAX is part of the STDCALL convention. Its a universal standard for other calling conventions as well.

( Floats are returned in the FPU register ST(0) )

In this example, I would not expect the Assembler version of the call to be significantly faster than the PB-compiled version.  I dont think there is any additional overhead. But I made a small economy by doing this:

! xor eax,eax
! push eax
! push eax

(4 bytes)

instead of:
! push dword 0
! push dword 0

(12 bytes)

but I dont know whether this improves the processing speed. In any case the time required to make the call will often be very small compared to the time required to execute the function itself. You can count each line of CPU assembler as taking 1 clock cycle as a very rough measure. (FPU instructions vary a lot, some more than 100 clocks)


Charles Pegge

#5
Mike, you  could increase the code performance by using macros instead of Functions in your streams.inc library. This will eliminate most of the overhead in using wrapper functions (say on average 20 clocks per call).

Of course macros are not quite the same as called procedures since the parameters are not really parameters and behave more like BYREF than BYVAL, so each procedure has to be considered individually - it would not be safe to do a mechanical translation.

Taking your example:


DECLARE FUNCTION Proto_IStorage_CreateStream (BYVAL pthis AS DWORD PTR, BYVAL pwcsName AS DWORD, BYVAL grfMode AS DWORD, BYVAL reserved1 AS DWORD, BYVAL reserved2 AS DWORD, BYREF ppstm AS DWORD) AS LONG

FUNCTION IStorage_CreateStream ALIAS "IStorage_CreateStream" (BYVAL pthis AS DWORD PTR, BYVAL strName AS STRING, BYVAL grfMode AS DWORD) EXPORT AS DWORD
    strName = UCODE$(strName)
    LOCAL ppstm AS DWORD
    IF ISFALSE pthis THEN STG_ERROR_HRESULT = %E_POINTER : EXIT FUNCTION
    CALL DWORD @@pthis[3] USING Proto_IStorage_CreateStream(pthis, STRPTR(strName), grfMode, %NULL, %NULL, ppstm) TO STG_ERROR_HRESULT
    FUNCTION = ppstm
END FUNCTION


The macro version might look like this:


DECLARE FUNCTION Proto_IStorage_CreateStream (BYVAL pthis AS DWORD PTR, BYVAL pwcsName AS DWORD, BYVAL grfMode AS DWORD, BYVAL reserved1 AS DWORD, BYVAL reserved2 AS DWORD, BYREF ppstm AS DWORD) AS LONG

MACRO mIStorage_CreateStream (pthis, sName, grfMode, ppstm)
    MACROTEMP strName
    LOCAL strName AS STRING
    strName = UCODE$(sName)
    IF ISFALSE pthis THEN STG_ERROR_HRESULT = %E_POINTER : EXIT MACRO
    CALL DWORD @@pthis[3] USING Proto_IStorage_CreateStream(pthis, STRPTR(strName), grfMode, %NULL, %NULL, ppstm) TO STG_ERROR_HRESULT
END MACRO

    ' invoked like this
    'mIStorage_CreateStream (pthis,"abc",1,ppstm)


   


PS:
The PB help file shows an example of a macro that returns a value (or expression) like a function but this does not appear to work. (using the PBwin v8.04).

José Roca

 
Instead of


LOCAL strName AS STRING


you need to use:


MACROTEMP strName
DIM strName AS STRING


Otherwise you will get a duplicate name definition if you call the macro more than once.

And macrotemp variables are inviable if you plan to call the macro more than 9999 times, e.g. in a tight loop.

If you are so worried about execution speed, then use CALL DWORD directly, without the help of wrapper functions or macros.


Charles Pegge

Thanks for spotting that José, I have added the MACROTEMP to the example above. And running up a stackful of temporary variables is one of the hidden hazards of using macros in this way.

I would say that macros are best suited to occasionally called procedures where there is a desire to hide complexity or to provide a large sourcecode library that does not compile its unused procedures into the program.


Charles Pegge

#8
Quote
macrotemp variables are inviable if you plan to call the macro more than 9999 times, e.g. in a tight loop.

After this afternoon's siesta, I devised a little test to see if macrotemps would proliferate or behave as  conventional locals within the procedure in which they are invoked,


#COMPILE EXE
#DIM ALL

MACRO persistant_macrotemp(a)
    MACROTEMP b
    LOCAL b AS LONG
    b=b+1
    a=b
END MACRO

FUNCTION PBMAIN () AS LONG
    LOCAL i,c AS LONG
    FOR i=1 TO 10001
        persistant_macrotemp(c)
    NEXT
    MSGBOX STR$(c)
END FUNCTION


I am pleased to say this macro behaved as all good macros should and delivered an answer of 10001  ;D

Has this been fixed in PB v8.04 or prior versions?

PS: I found the macrotemp for b translates to b0001


José Roca

 
If I remember well, using macros in a loop was a problem when they were implemented in PBWin 7.0 and PBCC 3.0. If this has changed, or if I was wrong, it is good news.

Patrice Terrier

As i can find a relative interest of macro for text substitution, i never use them to replace standard sub or function, especialy when there are many places within my code where such sub of function are being used.

...
Patrice Terrier
GDImage (advanced graphic addon)
http://www.zapsolution.com