EuroAssembler Index Manual Download Source Macros


Sitemap Links Forum Tests Projects

sysvcall.htm
Macros
ClearLocalVar
EndProcedure
Invoke
LocalVar
Procedure
Uses

This file can be included to 64bit programs written in EuroAssembler. The library contains macroinstructions Procedure, EndProcedure, Invoke which extend generic (pseudo)instructions PROC, ENDPROC, CALL in calling convention defined by System V Application Binary Interface in AMD64 architecture [SystemV] , where the arguments are transferred to the function in registers. If there is no enough registers, the remaining arguments are pushed on stack, starting with the last, and the stack is restored by the caller after return.
Machine stack is OWORD aligned before the CALL is performed.
The first 6 arguments are provided in registers RDI,RSI,RDX,RCX,R8,R9 (or in XMM0..XMM7 when they are floating-point numbers). Callee-save registers are RBX,RBP,RSP,R12..R15. All other registers may be destroyed by the invoked function.
Such calling convention is used in Linux and Unix based operation systems.

This library implements simplified subset of System V convention, where the invoked procedure has not more than 6 integer and 8 floating-point arguments (no argument is transferred via machine stack), only one (scalar) FP value is transferred in the lower 32 or 64 bits of XMM.
Macros from this library cannot be used for functions which have more than 6 integer arguments, more than 8 floating-point arguments, which require transfer in YMM or ZMM register, which require stack alignment better than 16.

The block of code defined between macros Procedure .. EndProcedure can be called by macro Invoke or as a callback procedure from library functions.

Macro Invoke can be also used to call functions from third-party static or dynamically linked libraries. For invocation of Linux kernel functions it's necessary to use specialized macro LinABI because of differences in the register used for transfer of 4th argument and because LinABI uses SYSCALL instead of CALL.

Macro Invoke takes care of stack alignment to OWORD just before execution of instruction CALL Function.

Example
Definition of procedure MyProc with five parameters, where Par1, Par4, Par5 are integer|pointers, and Par2,Par3 are floats. MyProc uses two GP registers RBX and R12 an two local stack variables with sizes 8 and 16:
MyProc Procedure Par1,Par2,Par3,Par4,Par5 ; Parameters Par1..Par5 should be loaded in RDI,XMM0,XMM1,RSI,RDX, respectively, when MyProc is invoked. Uses RBX,R12 ; These callee-save registers should be enumerated here, if they are used. They will be restored in EndProcedure. LocV1 LocalVar ; Reserve local stack variable with default size 8. LocV2 LocalVar Size=16 ; Reserve another variable. ClearLocalVar ; This fills all local stack variables with 0. ; Local variables are available by formal name prefixed with %, e.g. MOV [%LocV1],RDI ; Copy Par1 to the local variable. ; Programmer should emit instructions of the MyProc body here ; and load the result of MyProc into return-register (RAX or XMM0). EndProcedure MyProc ; This macro discards local variables, pops used callee-save registers, ; pops RBP and returns below Invoke statement at run-time.

The following diagram shows the stack frame created by invoking MyProc defined in the example above.

Macros of sysvcall convention will create and update the following "global" %variables at asm-time:
%ArgC_MyProc %SETA 5 (number of arguments),
%Uses_MyProc %SET R12,RBX (list of used callee-saved registers),
%LvSize_MyProc %SETA 8+16 (total size of local stack-variables),
%LocV1 %SET RBP-24 (1st local stack variable),
%LocV2 %SET RBP-40 (2nd local stack variable),
RSP after the step #. │ Stack ┌ 0.>┌───────┐<15. ┐ │1.PUSH RSP │origRSP│ 15.POP RSP │ Invoke Invoke │ 1.>├───────┤ ├ epilogue prologue ┤2.PUSH RSP;ADD [RSP],8 │origRSP│ ┘ │ OWORD-aligned> 2.>├═══════┤<14. ┐ │3.CALL MyProc │return │ 14.RET │ └ 3.>├───────┤<13. │ Procedure┤4.PUSH RBP;MOV RBP,RSP │origRBP│ 13.POP RBP │ ┌ 4.>├───────┤<12. │ Uses ┤5.PUSH RBX │ RBX │ 12.POP RBX │ │ 5.>├───────┤<11. ├EndProcedure │6.PUSH R12 │ R12 │ 11.POP R12 │ ┌ 6.>├───────┤<10. │ │7.SUB RSP,8 │ LocV1 │ 10.ADD RSP,8+16 │ │ 7.>├───────┤ │ LocalVar ┤ │ │ │ │ │ LocV2 │ │ │8.SUB RSP,16 │ │ │ └ 8.>└───────┘<9. ┘ 9. MyProc body

sysvcall HEAD
↑ Procedure Operand1, Operand2,,,

This macro Procedure declares simplified 64bit System V procedure prologue.
Using of the macro Procedure requires the corresponding EndProcedure be used in the same program.

Input
Label of Procedure statement is mandatory, it gives the procedure a callable name.
Operand* is the list of formal names for arguments passed to the procedure. Those formal names are not used, arguments are expected in registers only.
Output
Macroinstruction will define public symbol with procedure name.
It does not push registers (except for RBP). Programmer is responsible for saving and restoring callee-save registers RBX, R12..R15 if they are used in procedure body. This can be done either manually, or with macro Uses.
RBP must not be changed while the procedure body uses preprocessing %variables referring the temporary stack local variables defined with LocalVar.
Example
Move Procedure Source,Destination,Size ; Declaration of procedure Move and its formal arguments. ; Argument are in RDI, RSI, RDX. XCHG RSI,RDI ; Source to RSI, Destination to RDI. MOV RCX,RDX ; Size. REP MOVSB ; Perform the actual copy. EndProcedure Move ; Return from the procedure Move. Macro Move Procedure in the previous example will assign %ArgC_Move %SET 3 ; This %variable propagates to the corresponding macro EndProcedure Move. %Uses_Move %SET ; This %variable propagates to the macro Uses and EndProcedure. %LvSize_Move %SETA 0 ; This %variable propagates to the macro LocalVar and EndProcedure. Invoke Move, RSI, OutBuffer, SIZE# OutBuffer ; Example of procedure invocation.
Procedure %MACRO FormalName1, FormalName2,,,,
LblCheck    %IF "%:" === ""
              %ERROR ID=5921, 'Macro "Procedure" requires a label.'
              %EXITMACRO Procedure
            %ENDIF LblCheck
%%ArgC_%:   %SETX %#                   ; Initialize with number of arguments.
%%Uses_%:   %SETX                      ; Initialize as empty list.
%%LvSize_%: %SETX 0                    ; Initialize as zero.
%:::        PROC %=*, NESTINGCHECK=OFF ; Open the namespace and define entry symbol from macro label %: as GLOBAL.
            PUSH RBP
            MOV RBP,RSP                ; Initialize the frame pointer.
          %ENDMACRO Procedure
↑ Uses Register1, Register2,,,,

Macro Uses specifies which callee-save registers does the Procedure use, so they are pushed on stack here (and they will be restored in EndProcedure epilogue).

Calling convention macros in 16bit and 32bit mode could save/restore all eight GPR with a single PUSHA/POPA. This instruction is not available in 64bit mode, so we will use this macro instead.

Macro Uses can be used in 64bit mode only, right after the statement Procedure and before local stack variables are defined with LocalVar.

Callee-save registers RBX,,R12..R15 should be enumerated here if they are actually used in Procedure..EndProcedure block.
Callee-save registers RBP,RSP should not be mentioned here, they are always saved automatically in Procedure prologue.
It is useless to enumerate all other registers here, because the caller of our Procedure cannot expect them to be preserved.
Registers which return the result may not be enumerated here, because they wouldn't return the expected value after their restoration.

Input
Register* is GPR register.
Output
Macro will push all enumerated registers on stack and assign their list to a unique %variable named %Uses_ProcedureName in reversed order. This %variable will be used by EndProcedure for restoration of callee-save registers.
Uses %MACRO Register1,Register2,...
InProcCheck   %IF "%^PROC" === ""
                %ERROR ID=5926,'Macro "%0" is unexpected here.'
              %ENDIF InProcCheck
%Uses         %SET2 %%Uses_%^PROC
reg           %FOR %*
                %IF REGTYPE#(%reg) = 'Q' ; General-purpose 64bit register.
                  PUSHQ %reg
%Uses             %SET %reg,%Uses        ; Accumulate register names in reversed order.
                %ELSE
                  %ERROR ID=5927,'Macro "Uses" does not support operand "%reg".'
                %ENDIF
              %ENDFOR reg
%%Uses_%^PROC %SETX %Uses
            %ENDMACRO Uses
↑ LocalVar Size=8
Macro LocalVar reserves and declares local memory variable with the given Size allocated on machine stack and assigns its name to a preprocessing %variable which has its name derived from the label of macro LocalVar.
It can only be used inside Procedure..EndProcedure block.
Input
Plain identifier must be defined as a label of LocalVar statement. It does not need to be unique in the program because it does not declare assembly symbol. The name will be prefixed with % and used as preprocessing %variable for addressing the memory variable withing the procedure body.
Size=8 specifies how many bytes should be reserved for the local stack variable. The Size is automatically rounded up to the nearest multiple of 8.
Output
Macro will define a preprocessing %variable with the name which was defined as the label but it is now prefixed with percent sign. Then it will emit machine instruction SUB RSP,%Size to reserve room on the machine stack.
Macro LocalVar also maintains the "global" preprocessing %variable %LvSize_ProcedureName which was initialized in macro Procedure and which will be used for zeroing local variables in ClearLocalVar and for discarding local variables in EndProcedure.
Example
ProcName: Procedure Param1 ; This example uses two local stack variables with sizes 8 and 1K. Uses RBX ; Saved callee-save register is now available at RBP-8. BlockSize LocalVar ; %BlockSize is now assigned with RBP-16 (8+8). Block LocalVar Size=1024 ; %Block is now assigned with RBP-1040 (8+8+1024). ClearLocalVar ; Fill %Block and %BlockSize with 0. MOV [%BlockSize],1K, DATA=QWORD LEA RBX,[%Block] ; more instructions... EndProcedure ProcName
LocalVar      %MACRO Size=8
InProcCheck     %IF "%^PROC" === ""
                  %ERROR ID=5926,'Macro "%0" is unexpected here.'
                  %EXITMACRO LocalVar
                %ENDIF InProcCheck
LblCheck        %IF "%:" === ""
                  %ERROR ID=5922, 'Macro "%0" requires a label.'
                  %EXITMACRO LocalVar
                %ENDIF
OrdCheck        %IF %#
                  %ERROR ID=5923, 'Macro "%0" does not expect ordinal parameters.'
                %ENDIF
%:              %COMMENT                          ; This empty comment block makes the label of macro void,
                %ENDCOMMENT %:                    ;   so it does not declare a symbol.
%ThisLvSize     %SETA (%Size + 7) & ~7            ; Round up to the nearest multiple of 8.
%GlbLvSize      %SET2 %%LvSize_%^PROC+%ThisLvSize ; Increase the total size of previously defined local variables.
%%LvSize_%^PROC %SETX %GlbLvSize                  ; Update the "global" %variable.
                SUB RSP, %ThisLvSize              ; Stack memory allocation.
%ThisUses       %SET2 %%Uses_%^PROC               ; Retrieve the list of used registers.
%ThisLen        %SETL %ThisUses                   ; Number of registers pushed by macro Uses.
%%%:            %SETX RBP-8*%ThisLen-(%GlbLvSize) ; Assign formal %name to the id %: specified as LocalVar label.
   %ENDMACRO LocalVar
↑ ClearLocalVar
This macro zeroes all variables on stack previously declared with LocalVar. ClearLocalVar should be expanded right after the last LocalVar declarations, before any stack operations are made.
We could as well decide to initialize each local variable individually, e.g. MOVQ [%MyLocalVar],0, and in this case the macro ClearLocalVar will not be used in the Procedure body at all.
Input
Macro does not use explicit parameters. The cleared memory is pointed to with RSP, its size is specified with "global" variable %LvSize_ProcedureName.
Output
RAX=0
ClearLocalVar %MACRO
InProcCheck %IF "%^PROC" === ""
              %ERROR ID=5926,'Macro "%0" is unexpected here.'
              %EXITMACRO ClearLocalVar
            %ENDIF
%GlbLvSize  %SET2 %%LvSize_%^PROC
            %IF %GlbLvSize  ; Do nothing if no LocalVar was used in this Procedure (%GlbLvSize=0).
              PUSH RCX,RDI
               LEA RDI,[RSP+2*8] ; Skip pushed RCX,RDI.
               MOV ECX,%GlbLvSize / 8
               XOR EAX,EAX
               REP STOSQ
              POP RDI,RCX
            %ENDIF
          %ENDMACRO ClearLocalVar
↑ EndProcedure ProcName

Macro EndProcedure terminates context of the previously opened Procedure . This epilogue of System V convention will

Programmer should never use explicit machine instruction RET to return from the block defined with Procedure .. EndProcedure.
If premature return is required, jump to the label of EndProcedure statement instead.
Input
ProcName This macroinstruction requires exactly one operand which is identical with the label of previous corresponding Procedure statement.
Output
Stack frame is released, current process returns below Invoke statement.
EndProcedure %MACRO ProcName
OpCheck    %IF %# <> 1
             %ERROR ID=5924, 'Macro "EndProcedure" requires one operand.'
             %EXITMACRO EndProcedure
           %ENDIF
%NameStrip %SET %ProcName
Decolonize %WHILE "%NameStrip[%&]" === ":" ; Get rid of trailing colon(s), if used.
%NameStrip   %SET %NameStrip[1..%&-1]
           %ENDWHILE Decolonize
NestCheck  %IF "%NameStrip" !=== "%^PROC"
             %ERROR ID=5925, 'Nesting mismatch, "%ProcName Procedure" missing.'
             %EXITMACRO EndProcedure
           %ENDIF NestCheck
%GlbLvSize %SET2 %%LvSize_%^PROC
           %IF %GlbLvSize
             ADD RSP,%GlbLvSize            ; Discard local variables.
           %ENDIF
%ThisUses  %SET2 %%Uses_%^PROC
           %IF "%ThisUses" <> ""
             POP %ThisUses                 ; Callee-save registers saved by macro Uses.
           %ENDIF
           POP RBP                         ; Restore caller's frame pointer.
           RET                             ; Return below Invoke which called %ProcName.
           ENDP %ProcName, NESTINGCHECK=OFF
         %ENDMACRO EndProcedure
↑ Invoke ProcName, Arg1, Arg2,,,

Macro Invoke is a replacement of standard CALL instruction which can pass parameters to the Procedure in simplified System V convention .

Invoke walks through the list of arguments, starting with the first, and loads them either to RDI,RSI,RDX,RCX,R8,R9 when they are integer, or to XMM0..XMM7 when they are floating-point.
Argument is treated as floating point when it is SIMD register or when it ends with suffix #SS or #SD.

Stack pointer will be OWORD aligned before the CALL instruction is performed.
Epilogue of macro Invoke restores RSP to its original value.

Input
ProcName is the name of invoked procedure. This can be a function from statically linked library or it can be a block defined with Procedure, EndProcedure from this FastCall macrolibrary.
Arg* can be a SIMD register or anything what can be copied to 64bit GPR:It is programmer's responsibility to provide exactly that many arguments as is specified in Function documentation.
Any argument may be suffixed with type specificator #SS or #SD (case insensitive), which signalizes that it represents floating-point value in Scalar Single or Scalar Double precision format, and that it should be therefore passed to the Function in XMM register instead of GPR.
Suffix is not necessary with XMM register (argument passed in XMM is always assumed to contain floating-point number).
Fastmode=Yes This keyword is tolerated for compatibility with other macroinstructions, but it is ignored. Robust expansion mode is not supported by this macro.
Output
Registers are set as returned from the invoked Function.
RBX,RBP,RSP,R12..R15 are preserved (callee-save registers).
Other SIMD and GPR are undefined.
Invoke %MACRO Function, Arg1, Arg2,,, Fastmode=Yes
       PUSH RSP                            ; Store original stack pointer value (equilibrum).
       TEST SPL,1000b                      ; Test stack OWORD alignment at run-time.
FaEv   %IF %# & 1b                         ; If the number of Function arguments is 0,2,4,6,8,10,,(even),
         JZ .Invoke%.:                     ;   store 2nd copy of equilibrum when RSP is OWORD-unaligned.
       %ELSE FaEv                          ; If the number of arguments is 1,3,5,7,9,11,,, (odd),
         JNZ .Invoke%.:                    ;   store 2nd copy of equilibrum when RSP is OWORD-aligned.
       %ENDIF FaEv
       PUSH RSP                            ; Store and update 2nd copy of original RSP (equilibrum).
       ADDQ [RSP],8                        ; Those two instructions aren't executed if RSP was properly aligned.
.Invoke%.:
%GPR   %SET RDI,RSI,RDX,RCX,R8,R9          ; Enumerate registers for transfer of integer|pointer values.
%SIMD  %SET  XMM0,XMM1,XMM2,XMM3, \        ; Enumerate registers for transfer of floating-point values.
             XMM4,XMM5,XMM6,XMM7
%ArgNr %SETA 2                             ; Start with the 2nd operand, i.e. the 1st Function argument.
Arg     %WHILE %ArgNr <= %#
%Arg      %SET %*{%ArgNr}                  ; Transfer all Function arguments, start with the first one.
%suffix   %SET Q                           ; %suffix of MOV will be Q, SS or SD (MOVQ, MOVSS or MOVSD).
          %IF '%Arg[%&-2..%&-1]'=='#S'     ; If suffix #SS or #SD is present in argument notation,
%suffix     %SET %Arg[%&-1..%&]            ;  let %suffix be SS or SD
%Arg        %SET %Arg[1..%&-3]             ;  and remove it from the argument.
          %ENDIF                           ; %Arg may be GPR,SIMD,imm@abs,ptr@rel,[mem@abs],[mem@rel].
FaSc      %IF TYPE#(SEGMENT#(%Arg)) = 'N'  ; %Arg is not relocatable (scalar). It can be GPR,SIMD,imm@abs,[mem@abs].
FaScRg      %IF TYPE#(%Arg) = 'R'          ; %Arg is a GP or SIMD register.
FaScRgXm      %IF REGTYPE#(%Arg) = 'X'
                %IF "%SIMD{1}" !== "%Arg"  ; %Arg is XMM. Skip when it's already there.
                  MOV%suffix %SIMD{1},%Arg ; Copy SIMD %Arg to the first available SIMD (XMM0..XMM7).
%SIMD             %SET %SIMD{2..}          ; Remove the used register from the list.
                %ENDIF
              %ELSE FaScRgXm               ; %Arg is GPR.
                %IF "%GPR{1}" !== "%Arg"   ; Skip when it's already there.
                  MOV %GPR{1},%Arg         ; Copy GPR to the first available GPR from the list RDI,RSI,RDX,RCX,R8,R9.
%GPR              %SET %GPR{2..}           ; Remove the used register from the list.
                %ENDIF
              %ENDIF FaScRgXm
            %ELSE FaScRg                   ; %Arg is scalar immediate or [mem], e.g. 1 or [RBP+16].
FaScIm        %IF '%suffix' === 'Q'
                MOV %GPR{1},%Arg           ; %Arg is integer value.
%GPR            %SET %GPR{2..}             ; Remove the used register from the list.
              %ELSE FaScIm
                MOV%suffix %SIMD{1},%Arg   ; %Arg is FP value, e g. [RSI].
%SIMD             %SET %SIMD{2..}          ; Remove the used register from the list.
              %ENDIF FaScIm
            %ENDIF FaScRg
          %ELSE FaSc                       ; %Arg is relocatable (vector), e.g. Symbol or [Symbol+RSI].
FaVeM       %IF '%Arg[1]' === '['          ; Argument is passed by value, via this GPR.
              LEA %GPR{1},%Arg
              MOV %GPR{1},[%GPR{1}]        ; Dereference the argument value, transfer the value.
%GPR          %SET %GPR{2..}               ; Remove the used register from the list.
            %ELSE FaVeM                    ; Argument is passed by reference, e.g. Symbol.
              LEA %GPR{1},[%Arg]           ; Transfer the pointer.
%GPR          %SET %GPR{2..}               ; Remove the used register from the list.
            %ENDIF FaVeM
          %ENDIF FaSc
%ArgNr    %SETA %ArgNr + 1                 ; The next argument.
        %ENDWHILE Arg
        CALL %Function                     ; Call the function.
        POP RSP                            ; Restore RSP to equilibrum from 1st or 2nd copy.
      %ENDMACRO Invoke
  ENDHEAD sysvcall

▲Back to the top▲