Microsoft KB Archive/71275

From BetaArchive Wiki

Article ID: 71275

Article Last Modified on 11/21/2006

This article was previously published under Q71275

SUMMARY

The article below contains Part 2 of 2 of a complete tutorial and examples for passing all types of parameters between compiled Basic and Assembly Language.

The examples in BAS2MASM (but not the tutorial section) are also available in this database as multiple separate ENDUSER articles, which can be found as a group by querying on the word BAS2MASM.

MORE INFORMATION

See article 51501 for the text of Part 1 of "How to Pass Parameters Between Basic and Assembly Language." Part 2 is below.

CHAIN AND REFERENCES TO DGROUP

For mixed-language programs that use the CHAIN command, you should make sure that any code built into an extended (or custom) run-time module does not contain any references to DGROUP. (The CHAIN command causes DGROUP to move, but does not update references to DGROUP.) This rule applies only to mixed-language programs; because Basic routines never refer to DGROUP, you can ignore this caution for programs written entirely in Basic.

To avoid this problem, you can use the value of SS or DS, since Basic always assumes that SS and DS coincide with DGROUP.

CALLING DOS I/O ROUTINES DOES NOT AFFECT QUICKBasic CURSOR POSITION

MASM routines linked with a QuickBasic program that do screen output (by DOS interrupts) do not update the cursor position after returning to the calling QuickBasic program. (Note: This also applies to using CALL INTERRUPT statements in QuickBasic.)

For example, after the following three steps, the next PRINT statement goes directly after the last QuickBasic PRINT statement, ignoring the new line position from calling the MASM routine:

  1. Do a PRINT from QuickBasic.
  2. CALL a MASM routine that does some DOS display string functions (INT 21h, function 09H).
  3. Return to QuickBasic.

This is expected behavior. Assembly-language routines should not change the Basic cursor position.

SOME COPROCESSOR ASSEMBLER INSTRUCTIONS ARE NOT EMULATED

The Microsoft Macro Assembler version 5.10 does not come with routines to emulate a math coprocessor.

Page 382 of the "Microsoft Macro Assembler 5.10: Programmer's Guide" states that to emulate math-coprocessor instructions, you must link with a Microsoft higher-level language that supports floating-point emulation of the coprocessor. You would write the assembler procedure using coprocessor instructions, then assemble with the /E option, and finally link it with the high-level-language modules. (Note: This is valid only under DOS; under OS/2, this causes a GP fault.)

However, only a subset of coprocessor instructions is emulated by the Microsoft high-level languages.

If you link your Microsoft higher-level language to an assembler routine that invokes an instruction that is NOT emulated by the higher-level language, then the program gives a run-time error (or possibly hangs or gives incorrect results) when run on a machine that has no coprocessor.

Below is a list of the coprocessor (8087 or 80287) instructions that are not emulated by Microsoft higher-level languages:

   Coprocessor
   Instruction   Definition
   -----------   ----------

   FBLD          packed decimal load

   FBSTP         packed decimal store and pop

   FCOS          cosine function

   FDECSTP       decrement stack pointer

   FINCSTP       increment stack pointer

   FINIT         initialize processor

   FLDENV        load environment

   FNOP          no operation

   FPREM1        partial remainder

   FRSTOR        restore saved state

   FSAVE         save state

   FSETPM        set protected mode

   FSIN          only sine function

   FSINCOS       sine and cosine function

   FSTENV        store environment

   FUCOM         unordered comparison

   FUCOMP        unordered comparison and pop

   FUCOMPP       unordered comparison and double pop

   FXTRACT       extract exponent and significant
                

Also, some of the no-wait forms of instructions are not emulated, such as FNSTENV and FNINIT.

APPENDIX B: COMMON PITFALLS

===============

The following common pitfalls are all explained in more detail in the main text. This list supplies a simple checklist to go over when you encounter problems doing mixed-language programming.

  1. Make certain all registers that need to be saved are preserved. There are several registers that need to be preserved in a mixed- language program. These registers are as follows:

    CX, BX
    BP, SI, DI, SP
    CS, DS, SS, ES

    The direction flag should also be preserved.
  2. When passing strings to assembly language, watch for two things:

    1. SADD should be used instead of VARPTR when passing variable- length strings to assembly language. VARPTR will return the offset to the string descriptor, not to the string itself.
    2. The assembly-language routine must not, under any circumstances, alter the string descriptor in any way.
  3. When using VARSEG, VARPTR, or SADD to pass addresses to assembly language, it is important to check the function definition. Since Basic normally passes all parameters by reference, any parameter that is an address should be declared using BYVAL. If BYVAL is not used, Basic will create a temporary variable to hold the address, then pass a pointer to this variable (in effect, pass a pointer to a pointer).
  4. Make certain there is not a label on the END directive in the assembly-language routine.
  5. If the routine works outside the environment but doesn't work in a Quick library, then check to make certain that ES is not assumed to be equal to DS.

    Note: ES and DS should never be assumed to be equal unless the assembly language routine explicitly sets them equal.
  6. If updating from QuickBasic version 3.00 or earlier to 4.00 or later, there are several things to watch for:

    1. The string descriptor changed between version 3.00 and 4.00 of QuickBasic. Any assembly-language routines that deal with the string descriptor should be updated to use the new string descriptor.
    2. In QuickBasic versions 3.00 and earlier, it doesn't matter if some registers are not preserved (such as SI and DI); therefore, routines that don't preserve these registers will still run. These registers must be preserved to be used with QuickBasic versions 4.00 and later.

PASSING NUMERIC VARIABLES FROM
Basic TO ASSEMBLY BY NEAR REFERENCE

=======================

Basic

DECLARE SUB Numint(i%)
DECLARE SUB Numlong(lng&)
DECLARE SUB Numsng(s!)
DECLARE SUB Numdbl(d#)

i% = 2
lng& = 4
s! = 3.4
d# = 5.6

CLS
PRINT "         BEFORE","AFTER"
PRINT "Integer: ";i%,,
CALL Numint(i%)
PRINT i%

PRINT "Long   : ";HEX$(lng&),,
CALL Numlong(lng&)
PRINT HEX$(lng&)

PRINT "Single : ";s!,
CALL Numsng(s!)
PRINT s!

PRINT USING "Double : ##.####            ";d#,
CALL Numdbl(d#)
PRINT USING "##.####"; d#

END
                

Assembly

.MODEL MEDIUM, Basic
.CODE
        PUBLIC Numint, Numlong, Numsng, Numdbl
Numint  PROC
        push bp
        mov bp, sp        ; set stack frame
        mov bx, [bp+6]
        mov ax, [bx]   ; get integer
        shl ax, 1         ; multiply by 2
        mov [bx], ax   ; put new value back
        pop bp
        ret 2
Numint  ENDP
Numlong PROC
        push bp
        mov bp, sp        ; set stack frame
        mov bx, [bp+6]
        mov cx, [bx]      ; get long
        mov ax, [bx+2]    ; switch high and low words
        mov [bx+2], cx    ; put new value back
        mov [bx], ax
        pop bp
        ret 2
Numlong ENDP

Numsng  PROC
        push bp
        mov bp, sp               ; set stack frame
        mov bx, [bp+6]
        or BYTE PTR [bx+2], 80h  ; set sign bit
        pop bp
        ret 2
Numsng  ENDP

Numdbl  PROC
        push bp
        mov bp, sp         ; set stack frame
        mov bx, [bp+6]
        or BYTE PTR [bx+6], 80h  ;set sign bit
        pop bp
        ret 2
Numdbl  ENDP
        END
                

Output

          BEFORE    AFTER
Integer:   2         4
Long   :  4         40000
Single :   3.4      -3.4
Double :   5.6000   -5.6000
                

PASSING NUMERIC VARIABLES FROM
Basic TO ASSEMBLY BY FAR REFERENCE

======================

Basic

DECLARE SUB Numint(SEG i%)
DECLARE SUB Numlong(SEG lng&)
DECLARE SUB Numsng(SEG s!)
DECLARE SUB Numdbl(SEG d#)

i% = 2
lng& = 4
s! = 3.4
d# = 5.6

CLS
PRINT "         BEFORE","AFTER"
PRINT "Integer: ";i%,,
CALL Numint(i%)
PRINT i%

PRINT "Long   : ";HEX$(lng&),,
CALL Numlong(lng&)
PRINT HEX$(lng&)

PRINT "Single : ";s!,
CALL Numsng(s!)
PRINT s!

PRINT USING "Double : ##.####            ";d#,
CALL Numdbl(d#)
PRINT USING "##.####"; d#
END
                

Assembly

.MODEL MEDIUM, Basic
.CODE
        PUBLIC Numint, Numlong, Numsng, Numdbl
Numint  PROC
        push bp
        mov bp, sp        ; set stack frame
        push es
        mov es, [bp+8]    ; get seg
        mov bx, [bp+6]    ; get offset
        mov ax, es:[bx]   ; get actual integer
        shl ax, 1         ; multiply by 2
        mov es:[bx], ax   ; put back new value
        pop es
        pop bp
        ret 4
Numint  ENDP
Numlong PROC
        push bp
        mov bp, sp        ; set stack frame
        push es
        mov es, [bp+8]    ; get seg
        mov bx, [bp+6]    ; get offset
        mov cx, es:[bx]   ; get actual long
        mov ax, es:[bx+2] ; switch high and low words
        mov es:[bx+2], cx ; put back new value
        mov es:[bx], ax
        pop es
        pop bp
        ret 4
Numlong ENDP

Numsng  PROC
        push bp
        mov bp, sp        ; set stack frame
        push es
        mov es, [bp+8]    ; get seg
        mov bx, [bp+6]    ; get offset
        mov ax, es:[bx+2] ; get actual single
        or ah, 80h        ; set sign bit
        mov es:[bx+2], ax ; put back new value
        pop es
        pop bp
        ret 4
Numsng  ENDP

Numdbl  PROC
        push bp
        mov bp, sp         ; set stack frame
        push es
        mov es, [bp+8]     ; get seg
        mov bx, [bp+6]     ; get offset
        mov ax, es:[bx+6]  ; get actual double
        or ah, 80h         ; set sign bit
        mov es:[bx+6], ax  ; put back new value
        pop es
        pop bp
        ret 4
Numdbl  ENDP
        END
                

Output

          BEFORE    AFTER
Integer:   2         4
Long   :  4         40000
Single :   3.4      -3.4
Double :   5.6000   -5.6000
                
      PASSING NUMERIC VARIABLES FROM Basic TO ASSEMBLY BY VALUE
      =========================================================

Basic
-----

DECLARE SUB ValInt(BYVAL i%)
DECLARE SUB ValLong(BYVAL lng&)

i% = ASC("A")
lng& = ASC("B") * 65536 + ASC("C")

CLS
CALL ValInt(i%)
CALL ValLong(lng&)

END


Assembly
--------

.MODEL MEDIUM, Basic
.CODE
        PUBLIC ValInt, ValLong
ValInt  PROC
        push bp
        mov bp, sp      ; set stack frame
        mov dx, [bp+6]  ; get integer
        mov ah, 02      ; DOS interrupt to print character
        int 21h
        pop bp
        ret 2
ValInt  ENDP

ValLong PROC
        push bp
        mov bp, sp      ; set stack frame
        mov dx, [bp+6]  ; get first part of long
        mov ah, 02      ; DOS interrupt to print character
        int 21h
        mov dx, [bp+8]  ; get second part of long
        int 21h         ; print it
        pop bp
        ret 4
ValLong ENDP
        END


Output
------

ABC


           PASSING NUMERIC VARIABLES FROM ASSEMBLY TO Basic
           ================================================

Basic
-----

DECLARE SUB AssemSub(dummy AS INTEGER)

CALL AssemSub(dummy%)
END

SUB NumInt(i AS INTEGER)
   PRINT "Integer : "; i
END SUB

SUB NumLong(lng AS LONG)
   PRINT "Long    : "; lng
END SUB

SUB NumSingle(s AS SINGLE)
   PRINT "Single  : "; s
END SUB

SUB NumDouble(d AS DOUBLE)
   PRINT "Double  : "; d
END SUB


Assembly
--------

.MODEL MEDIUM, Basic
         EXTRN NumInt:PROC         ; declare Basic procedures
         EXTRN NumLong:PROC
         EXTRN NumSingle:PROC
         EXTRN NumDouble:PROC
.DATA
         intnum dw 32767           ; initialize data
         Longnum dd 37999
         Singlenum dd 123.45
         Doublenum dq 1234.14159

.CODE

         PUBLIC AssemSub
AssemSub PROC
         push bp
         mov bp, sp

         mov ax, OFFSET intnum     ; get address of integer
         push ax
         call NumInt

         mov ax, OFFSET Longnum    ; get address of long
         push ax
         call NumLong

         mov ax, OFFSET Singlenum  ; get address of single
         push ax
         call NumSingle

         mov ax, OFFSET Doublenum  ; get address of double
         push ax
         call NumDouble

         pop bp
         ret 2
AssemSub ENDP

         END


Output
------

Integer : 32767
Long    : 37999
Single  : 123.45
Double  : 1234.14159


                      PASSING A VARIABLE-LENGTH
                STRING TO ASSEMBLY BY NEAR REFERENCEP
                =====================================

Basic
-----

DECLARE SUB RString(BYVAL soff AS INTEGER)

A$ = "This is the string" + "$"  ' "$" terminates string for INT call

CALL RString(SADD(A$))

END


Assembly
--------

.MODEL MEDIUM
.CODE
        PUBLIC RString
RString PROC
        push bp
        mov bp, sp      ; set stack frame
        mov dx, [bp+6]  ; get offset to string
        mov ah, 9       ; DOS interrupt to print string
        int 21h
        pop bp
        ret 2
RString ENDP
        END


Output
------

This is the string


                      PASSING A VARIABLE-LENGTH
                 STRING TO ASSEMBLY BY FAR REFERENCE
                 ===================================

Basic
-----

DECLARE SUB PSTRING(BYVAL STRSEG AS INTEGER, BYVAL STROFF AS INTEGER)

A$ = "Hello World"
PRINT "Before call: ";
PRINT A$
CALL PSTRING(VARSEG(A$), SADD(A$))
PRINT "After call : ";
PRINT A$


Assembly
--------

; Note: This routine uses the MASM 5.10 update PROC extensions

.MODEL MEDIUM, Basic
.CODE

pstring PROC sseg:WORD, soff:WORD
        push bx                  ; save bx register and dx
        push dx
        push es

        mov ax, sseg             ; get segment of string
        mov es, ax               ; put into segment register
                                 ; get offset of string
        mov bx, soff
                                 ; 65 = ASCII 'A'
        mov BYTE PTR es:[bx], 65 ; move the 'A' to the first character
                                 ;   in the string
        pop es
        pop dx
        pop bx                   ; restore dx and bx
        ret
pstring ENDP
        END


Output
------

Before call: Hello World
After call : Aello World


                        PASSING A Basic STRING
               DESCRIPTOR TO ASSEMBLY BY NEAR REFERENCE
               ========================================

Basic
-----

DECLARE SUB RString(A AS STRING)

A$ = "This is the String" + "$"  ' "$" terminates the string for INT
call
CALL RString(A$)

END


Assembly
--------

.MODEL MEDIUM, Basic
.CODE
        PUBLIC RString
RString PROC
        push bp
        mov bp, sp     ; set stack frame
        mov bx, [bp+6] ; get offset of string descriptor
        mov dx, [bx+2] ; get address of string
        mov ah, 9      ; int call to print string
        int 21h
        pop bp

        ret 2
RString ENDP

        END


Output
------

This is the String


                        PASSING A Basic STRING
               DESCRIPTOR TO ASSEMBLY BY FAR REFERENCE
               =======================================

Basic
-----

A$ = "This is the String" + "$"  ' "$" terminates the string for INT
call
CALLS RString(A$)   ' Note: CALLS makes this pass seg and offset

END


Assembly
--------

.MODEL MEDIUM, Basic
.CODE
        PUBLIC RString
RString PROC
        push bp
        mov bp, sp     ; set stack frame
        push ds
        mov ds, [bp+8] ; segment of descriptor
        mov bx, [bp+6] ; offset of descriptor
        mov dx, [bx+2] ; address of actual string
        mov ah, 9      ; DOS interrupt to print string
        int 21h
        pop ds
        pop bp

        ret 4
RString ENDP

        END


Output
------

This is the String


                        PASSING A Basic STRING
                  DESCRIPTOR TO Basic FROM ASSEMBLY
                  =================================

Basic
-----

DECLARE SUB MkString

CALL MkString

END

SUB BasicSub(TheString AS STRING)
   PRINT LEN(TheString)
   PRINT TheString
END SUB


Assembly
--------

.MODEL MEDIUM
         SType STRUC    ; this structure defines a string descriptor
               SLength DW 18
               Soff    DW ?
         SType ENDS
.DATA
         StringDesc SType <>
         TheString  DB 'This is the string'

.CODE
         EXTRN BasicSub:PROC

         PUBLIC MkString
MkString PROC
         mov ax, OFFSET TheString        ; set up string descriptor
         mov bx, OFFSET StringDesc.Soff
         mov [bx], ax
         mov ax, OFFSET StringDesc.SLength
         push ax        ; pass address of descriptor to Basic
         CALL BasicSub
         ret
MkString ENDP
         END


Output
------

 18
This is the string


                     PASSING A Basic FIXED-LENGTH
            STRING TO AND FROM ASSEMBLY BY NEAR REFERENCE
            =============================================

Basic
-----

DECLARE SUB RString(BYVAL offs AS INTEGER)

TYPE fixstring
   s AS STRING * 20
END TYPE

DIM a AS STRING * 20

CLS
a = "Basic String$" ' "$" terminates string for assembly

CALL RString(VARPTR(a))
END

SUB BasicSub(a AS fixstring)
   LOCATE 2, 1        ' because print in assembly won't move Basic's
   PRINT a.s          '   screen position
END SUB


Assembly
--------

.MODEL MEDIUM, Basic
        EXTRN BasicSub:PROC
.DATA
  astr  DB 'Assembly String      '

.CODE

        PUBLIC RString
RString PROC
        push bp
        mov bp, sp           ; set stack frame
        mov dx, [bp+6]       ; address of string
        mov ah, 9            ; DOS interrupt to print string
        int 21h

        mov ax, OFFSET astr  ; address of assembly string
        push ax              ; pass it to Basic
        call BasicSub

        pop bp
        ret 2
RString ENDP
        END


Output
------

Basic String
Assembly String


                     PASSING A Basic FIXED-LENGTH
                 STRING TO ASSEMBLY BY FAR REFERENCE
                 ===================================

Basic
-----

DECLARE SUB RString(BYVAL sseg AS INTEGER, BYVAL soff AS INTEGER)

DIM a AS STRING * 20

CLS
a = "Basic String$" ' "$" terminates string for assembly

CALL RString(VARSEG(a), VARPTR(a))

END


Assembly
--------

.MODEL MEDIUM, Basic
.CODE
        PUBLIC RString
RString PROC
        push bp
        mov bp, sp      ; set stack frame
        push ds
        mov ds, [bp+8]  ; segment of string
        mov dx, [bp+6]  ; offset of string
        mov ah, 9       ; DOS interrupt to print string
        int 21h
        pop ds
        pop bp
        ret 4
RString ENDP
        END


Output
------

Basic String


                   PASSING A USER-DEFINED TYPE FROM
                 Basic TO ASSEMBLY BY NEAR REFERENCE
                 ===================================

Basic
-----

DEFINT A-Z

TYPE mixed
   i AS INTEGER
   l AS LONG
   s AS SINGLE
   d AS DOUBLE
   fx AS STRING * 19
END TYPE

DECLARE SUB MasmSub (dummy AS mixed)

DIM dummy AS mixed

CLS
PRINT "Calling assembly routine to fill the user-defined
type."
CALL MasmSub(dummy)
PRINT "Values in user-defined type:"

PRINT "Integer: ", dummy.i
PRINT "Long: ", dummy.l
PRINT "Single: ", dummy.s
PRINT "Double: ", dummy.d
PRINT "fixed-length String: ", dummy.fx

END


Assembly
--------

.MODEL MEDIUM
        usrdefType STRUC
                   iAsm  DW 10
                   lAsm  DD 43210
                   sAsm  DD 32.10
                   dAsm  DQ 12345.67
                   fxAsm DB 'Fixed-length string'
        usrdefType ENDS
.DATA
        AsmRec usrdefType <>

        PUBLIC MasmSub
MasmSub PROC
        push bp
        mov  bp,sp            ; set stack frame
        push es
        push di
        push si
        push cx
        push ds
        pop  es

        mov di,[bp+6]         ; get offset of user-defined type
        mov si,OFFSET AsmRec  ; set up for copy
        mov cx,37             ; size of structure
        rep movsb             ; copy values to Basic variable

        pop cx
        pop si
        pop di
        pop es
        pop bp
        ret 2
MasmSub ENDP
        END


Output
------

     Integer:   10
     Long:      43210
     Single:    32.10
     Double:    12345.67
     fixed-length String:  Fixed-length string


                   PASSING A USER-DEFINED TYPE FROM
                  Basic TO ASSEMBLY BY FAR REFERENCE
                  ==================================

Basic
-----

DEFINT A-Z
DECLARE SUB MasmSub (BYVAL segment, BYVAL offset)

TYPE mixed
   i AS INTEGER
   lng AS LONG
   s AS SINGLE
   d AS DOUBLE
   fx AS STRING * 19
END TYPE

DIM dummy AS mixed

CLS
PRINT "Calling assembly routine to fill the user-defined type."
CALL MasmSub(VARSEG(dummy), VARPTR(dummy))
PRINT "Values in user-defined type:"

PRINT "Integer: ", dummy.i
PRINT "Long: ", dummy.lng
PRINT "Single: ", dummy.s
PRINT "Double: ", dummy.d
PRINT "fixed-length String: ", dummy.fx

END


Assembly
--------

.MODEL MEDIUM
        usrdefType STRUC
                   iAsm  DW 10
                   lAsm  DD 43210
                   sAsm  DD 32.10
                   dAsm  DQ 12345.67
                   fxAsm DB 'Fixed-length string'
        usrdefType ENDS
.DATA
        AsmRec usrdefType <>

        PUBLIC MasmSub
MasmSub PROC FAR
        push bp
        mov  bp,sp
        push es
        push di
        push si
        push cx

        mov es,[bp+8]         ; get segment of user-defined type
        mov di,[bp+6]         ; get offset of user-defined type
        mov si,OFFSET AsmRec
        mov cx,37             ; size of structure
        rep movsb             ; copy values to Basic variable

        pop cx
        pop si
        pop di
        pop es
        pop bp
        ret 4
MasmSub ENDP
        END


Output
------

     Integer:   10
     Long:      43210
     Single:    32.10
     Double     12345.67
     fixed-length String:  Fixed-length string


                        PASSING A USER-DEFINED
                     TYPE FROM ASSEMBLY TO Basic
                     ===========================

Basic
-----

DEFINT A-Z
DECLARE SUB MasmSub

TYPE mixed
   i AS INTEGER
   lng AS LONG
   s AS SINGLE
   d AS DOUBLE
   fx AS STRING * 19
END TYPE

DIM dummy AS mixed

CLS
PRINT "Calling assembly routine which will fill the";
PRINT " user-defined type."
CALL MasmSub
END

SUB BasicSub (dummy AS mixed)

   PRINT "Values in user-defined type:"
   PRINT
   PRINT "Integer: ", dummy.i
   PRINT "Long: ", dummy.lng
   PRINT "Single: ", dummy.s
   PRINT "Double: ", dummy.d
   PRINT "fixed-length String: ", dummy.fx

END SUB


Assembly
--------

.MODEL MEDIUM
        usrdefType STRUC
                   iAsm  DW 10
                   lAsm  DD 43210
                   sAsm  DD 32.10
                   dAsm  DQ 12345.67
                   fxAsm DB 'Fixed-length string'
        usrdefType ENDS
        EXTRN BasicSub:PROC
.DATA
        BasicRec usrdefType <>
.CODE

        PUBLIC MasmSub
MasmSub PROC                     ; no stack frame is needed
                                 ;   because no arguments are
                                 ;   passed to assembly
        mov ax, OFFSET BasicRec  ; get address of structure
        push ax                  ; pass it as argument to Basic
        CALL BasicSUb
        ret
MasmSub ENDP
        END


Output
------

     Integer:   10
     Long:      43210
     Single:    32.10
     Double:    12345.67
     fixed-length String:  Fixed-length string


                         PASSING AN ARRAY OF
                   INTEGERS FROM Basic TO ASSEMBLY
                   ===============================

Basic
-----

DEFINT A-Z
DECLARE SUB MasmSub (BYVAL segment, BYVAL offset, BYVAL number)

'REM $DYNAMIC     'Can be either STATIC (the default) or DYNAMIC
DIM x%(1 TO 10)   'Remove comment to define array DYNAMICally

CLS
PRINT "Calling assembly routine to fill array elements..."
CALL MasmSub(VARSEG(x%(1)), VARPTR(x%(1)), 10)
PRINT "Values in array:"

FOR i = 1 TO 10
    PRINT x%(i);
NEXT

END


Assembly
--------

.MODEL MEDIUM
.CODE
        PUBLIC MasmSub
MasmSub PROC            ; can use proc far here too
        push bp         ; save registers for Basic
        mov  bp,sp      ; get the stack pointer

        mov  es,[bp+10] ; get segment of array
        mov  bx,[bp+8]  ; get offset of array

        mov  cx,[bp+6]  ; get length of array
        mov  al,1       ; fill array elements with 1's

next:   mov  es:[bx],al ; put one in the array element
        add  bx,2       ; increment counter to next array element
                        ; -- add two bytes for integers, four bytes
                        ; -- for single precision and long integers,
                        ; -- and 8 bytes for double precision numbers
        loop next       ; loop to assign next array element
        pop  bp         ; restore bp for Basic
        ret  6          ; restore stack
MasmSub ENDP
        END


Output
------

  1 1 1 1 1 1 1 1 1 1


                       PASSING AN ARRAY OF LONG
                   INTEGERS FROM Basic TO ASSEMBLY
                   ===============================

Basic
-----

REM Program that calls an assembly routine that fills each
REM element with a 1.

DEFINT A-Z
DECLARE SUB MasmSub (BYVAL segment, BYVAL offset, BYVAL number)

'REM $DYNAMIC       'Can be either STATIC (the default) or DYNAMIC
DIM lng&(1 TO 10)   'Remove comment to define array DYNAMICally

CLS
PRINT "Calling assembly routine to fill array elements..."
CALL MasmSub(VARSEG(lng&(1)), VARPTR(lng&(1)), 10)
PRINT "Values in array:"

FOR i% = 1 TO 10
    PRINT lng&(i);
NEXT
END


Assembly
--------

.MODEL MEDIUM
.CODE
        PUBLIC MasmSub
MasmSub PROC             ; can use proc far here too
        push bp          ; save registers for Basic
        mov bp, sp

        mov es, [bp+10]  ; get segment of array
        mov bx, [bp+8]   ; get offset of array

        mov cx, [bp+6]   ; get length of array
        mov al, 1

next:   mov es:[bx], al  ; put one in the array element
        add bx, 4        ; increment counter to next array element
        loop next        ; loop to assign next array element
        pop bp           ; restore bp for Basic
        ret 6
MasmSub ENDP
        END


Output
------

 1 1 1 1 1 1 1 1 1 1


                         PASSING AN ARRAY OF
          SINGLE-PRECISION VARIABLES FROM Basic TO ASSEMBLY
          =================================================

Basic
-----

REM Program that calls an assembly routine that changes the
REM sign of an array of numbers
DEFINT A-Z
DECLARE SUB MasmSub (BYVAL segment, BYVAL offset, BYVAL number)
'REM $DYNAMIC     'Can be either STATIC (the default) or DYNAMIC
DIM s!(1 TO 10)   'Remove comment to define array DYNAMICally
FOR i% = 1 to 10
   s!(i%) = i%
NEXT
CLS
PRINT "Calling assembly routine to fill array elements..."
CALL MasmSub(VARSEG(s!(1)), VARPTR(s!(1)), 10)
PRINT "Values in array:"
FOR i% = 1 TO 10
    PRINT s!(i);
NEXT
END


Assembly
--------

.MODEL MEDIUM
.CODE
        PUBLIC MasmSub
MasmSub PROC             ; can use proc far here too
        push bp          ; save registers for Basic
        mov bp, sp

        mov es, [bp+10]  ; get segment of array
        mov bx, [bp+8]   ; get offset of array
        add bx, 3        ; offset to byte holding sign bit
        mov cx, [bp+6]   ; get length of array
        mov al, 1

next:   or BYTE PTR es:[bx], 80h   ; set sign bit
        add bx, 4        ; increment counter to next array element
        loop next        ; loop to assign next array element
        pop bp           ; restore bp for Basic
        ret 6
MasmSub ENDP
        END


Output
------

-1 -2 -3 -4 -5 -6 -7 -8 -9 -10


                         PASSING AN ARRAY OF
          DOUBLE-PRECISION VARIABLES FROM Basic TO ASSEMBLY
          =================================================

Basic
-----

DECLARE SUB FillDbl(BYVAL ASeg AS INTEGER, BYVAL AOff AS INTEGER)

DIM DblArray(1 TO 5) AS DOUBLE

CALL FillDbl(VARSEG(DblArray(1)), VARPTR(DblArray(1)))
FOR i% = 1 TO 5
   PRINT DblArray(i%)
NEXT
END


Assembly
--------

.MODEL MEDIUM, Basic
.DATA
        Dbl1 DQ 123.45       ; initialize data table
        Dbl2 DQ 456.78
        Dbl3 DQ 98765.432
        Dbl4 DQ 12345.678
        Dbl5 DQ 777.888
.CODE
        PUBLIC FillDbl
FillDbl PROC
        push bp
        mov bp, sp           ; set stack frame
        push es
        push di
        push si
        mov es, [bp+8]       ; segment of array
        mov di, [bp+6]       ; offset of array
        mov si, OFFSET Dbl1  ; get offset of data table
        mov cx, 40           ; length of data in table
        rep movsb            ; copy data table to array
        pop si
        pop di
        pop es
        pop bp
        ret 4
FillDbl ENDP
        END


Output
------

123.45
456.78
98765.432
12345.678
777.888


       PASSING AN ARRAY OF Basic STRING DESCRIPTORS TO ASSEMBLY
       ========================================================

Basic
-----

' This program demonstrates passing an array of strings
' to an assembly language routine.  The assembly language
' routine then receives the address of the array, and
' interprets the array as an array of string descriptors.
' It then uses the descriptors to get the length and address
' of the strings.  It uses these two values to uppercase all of
' the lowercase alphabetic characters in any of the
' strings, and to skip all others.
' It is very important to pass the assembly routine the number
' of elements in the array.

OPTION BASE 0
DECLARE SUB UpCaseArray (BYVAL ArrayAddress%, arraylen%)
' BYVAL is necessary because we want to pass the VALUE of
' the address, not a pointer to the address.
DIM Num%, Array1$(20)
CLS

WHILE NOT a$ = "quit"
   INPUT "Enter a string ('quit' to end): ", a$
   Array1$(Num%) = a$
   Num% = Num% + 1
WEND

CALL UpCaseArray(VARPTR(Array1$(0)), Num%)
CLS
FOR i% = 0 TO (Num% - 1)
   PRINT Array1$(i%)
NEXT
END


Assembly
--------

.MODEL MEDIUM,Basic
.CODE
        PUBLIC UpCaseArray
UpCaseArray PROC FAR
        push bp
        mov  bp,sp
        push di
        mov bx,[bp+6]    ; Argument #2: Number of array elements.
        mov cx,[bx]      ; Get the actual number of array elements.
        jcxz EndOutLoop  ; If the array has 0 elements then quit.
        mov bx,[bp+8]    ; Argument #1: Pointer to an array of
                         ; descriptors.
OutLoop:                 ; CX is the outer-OutLoop counter.
        push cx          ; Save the outer loop counter.
        mov cx,[bx]      ; Get the first two bytes of the current
                         ; descriptor, which is the string length.
        jcxz EndInLoop   ; If zero length, end the inner loop.
        mov di,[bx+2]    ; The second 2 bytes is the address.
                         ; DI = pointer to current string.
InLoop:                  ; Check if the char needs to be uppercased.
        cmp byte ptr [di],'a'  ; Is it < a ?
        jb I1                  ; If so, then move to the next char.
        cmp byte ptr [di],'z'  ; Is is > z ?
        ja I1                  ; If so, then move on to the next char.
        and byte ptr [di],05Fh ; Make upper case. Mask -> (0101 1111).
I1:     inc di                 ; Move on to next character in the
                               ;    string.
        loop InLoop            ; Do it for all characters
                               ;    (until CX = 0).
                               ; Note: 'loop' decrements CX.
EndInLoop:
        add bx,4               ; Move on to next descriptor.
        pop cx                 ; Restore the outer loop counter.
        loop OutLoop           ; Do for all descriptors
                               ;    (until CX = 0).
EndOutLoop:
        pop di
        pop bp
        ret 4
UpCaseArray ENDP
        END


Output
------

     Enter a string ('quit' to end): First String
     Enter a string ('quit' to end): Second String
     Enter a string ('quit' to end): quit

     FIRST STRING
     SECOND STRING


      PASSING DYNAMIC ARRAYS OF FIXED-LENGTH STRINGS TO ASSEMBLY
      ==========================================================

Basic
-----

REM $DYNAMIC
DECLARE SUB Masm (
       BYVAL StrLength AS INTEGER,_
       BYVAL Length AS INTEGER,_
       BYVAL SegAddr1 AS INTEGER,_
       BYVAL Addr1 AS INTEGER,_
       BYVAL SegAddr2 AS INTEGER,_
       BYVAL Addr2 AS INTEGER)
CONST Size% = 3%     'Size of the array (# of elements)
CONST StrSize% = 11%  'Size of strings stored in array
CLS
DIM inArray(1 TO Size%) AS STRING * StrSize%
DIM outArray(1 TO Size%) AS STRING * StrSize%

'Load inArray with a 11 character string " *inArray* ":
FOR i = 1 TO Size%
  inArray(i) = " *inArray* "
NEXT i

' Masm will copy the contents of inArray to outArray:
CALL Masm(StrSize%,_
          Size%,_
          VARSEG(inArray(1)),_
          VARPTR(inArray(1)),_
          VARSEG(outArray(1)),_
          VARPTR(outArray(1)))

' Print the inArray:
PRINT
PRINT
PRINT "inArray: "

FOR i = 1 TO Size%
   PRINT inArray(i);
NEXT i

' Print the outArray to see that the contents of inArray
' were copied to it:

PRINT
PRINT "outArray: "

FOR i = 1 TO Size%
  PRINT outArray(i);
NEXT i
END


Assembly
--------

;***********************************************************
; The routine 'Masm' copies a dynamic string array of any
;   length to another string array.
; Warnings:
;   -- Arrays must be adequately dimensioned.
; Masm takes six parameters from the Basic routine:
;   1 - Size of strings in array to be copied (BX)
;   2 - # of elements in array
;   3 - Segment of source array
;   4 - Offset of first element of source array
;   5 - Segment of destination array
;   6 - Offset of first element of destination array
;***********************************************************
.MODEL MEDIUM
.CODE
PUBLIC Masm

Masm    PROC
        push bp
        mov bp, sp
        push si

        mov bx, [bp+16]   ; Size of strings in array -> bx
        mov ax, [bp+14]   ; Elements in array -> ax
        mul bx            ; multiply ax by bx and put answer in ax
        mov cx, ax        ; Number of bytes in array -> cx

        mov es, [bp+12]   ; Segment of first array (inArray)
        mov bx, [bp+10]   ; Offset of first element in first
                          ; array
; body
        mov si, 0         ; initialize first array index (inArray)
again:
        mov al, es:[bx]   ; Load byte to copy to second array
                          ;  in al
        push bx           ; save bx
        push es           ; save es
        mov es, [bp+8]    ; Segment of second array (outArray)
        mov bx, [bp+6]    ; Offset of second arrays first
                          ; element
        add bx, si        ; Get correct offset into 2nd array from
                          ; index
        mov es:[bx], al   ; Move the byte into the second array
        pop es            ; restore es
        pop bx            ; restore bx
        add bx, 1         ; point to next element in first array
                          ; (inArray)
        add si, 1         ; increment second array (outArray) index
        loop again        ; Loop until cx is 0
        pop si
        pop bp
        ret
Masm    ENDP
        END


Output
------

 *InArray*
 *InArray*
 *InArray*


                      PASSING A TWO-DIMENSIONAL
                 INTEGER ARRAY FROM Basic TO ASSEMBLY
                 ====================================

Basic
-----

DECLARE SUB TwoInt(BYVAL ASeg AS INTEGER, BYVAL AOff AS INTEGER)

DIM IntArray(1 TO 2, 1 TO 3) AS INTEGER

CALL TwoInt(VARSEG(IntArray(1, 1)), VARPTR(IntArray(1, 1)))
FOR row% = 1 TO 2
   FOR col% = 1 TO 3
      PRINT IntArray(row%, col%)
   NEXT
NEXT
END


Assembly
--------

.MODEL MEDIUM, Basic
.DATA
        i11 DW 11           ; initialize data table
        i21 DW 21
        i12 DW 12
        i22 DW 22
        i13 DW 13
        i23 DW 23
.CODE
        PUBLIC TwoInt
TwoInt  PROC
        push bp
        mov bp, sp          ; set stack frame
        push es
        push si
        push di

        mov es, [bp+8]      ; segment of array
        mov di, [bp+6]      ; offset of array
        mov si, OFFSET i11
        mov cx, 6           ; number of items to copy
        rep movsw           ; copy data to array
        pop di
        pop si
        pop es
        pop bp
        ret 4
TwoInt  ENDP
        END


Output
------

11
12
13
21
22
23


                      PASSING A TWO-DIMENSIONAL
           FIXED-LENGTH STRING ARRAY FROM Basic TO ASSEMBLY
           ================================================

Basic
-----

DECLARE SUB TwoFix(BYVAL ASeg AS INTEGER, BYVAL AOff AS INTEGER)

DIM FixArray(1 TO 2, 1 TO 3) AS STRING * 9

CALL TwoFix(VARSEG(FixArray(1, 1)), VARPTR(FixArray(1, 1)))
FOR row% = 1 TO 2
   FOR col% = 1 TO 3
      PRINT FixArray(row%, col%)
   NEXT
NEXT
END


Assembly
--------

.MODEL MEDIUM, Basic
.DATA
        Fix11 DB 'String 11'  ; allocate string data
        Fix21 DB 'String 21'
        Fix12 DB 'String 12'
        Fix22 DB 'String 22'
        Fix13 DB 'String 13'
        Fix23 DB 'String 23'
.CODE
        PUBLIC TwoFix
TwoFix  PROC
        push bp
        mov bp, sp            ; set stack frame
        push es
        push si
        push di
        mov es, [bp+8]        ; segment of string array
        mov di, [bp+6]        ; offset of string array
        mov si, OFFSET Fix11  ; get offset to string data
        mov cx, 54            ; length of all string data
        rep movsw             ; copy string data to array
        pop di
        pop si
        pop es
        pop bp
        ret 4
TwoFix  ENDP
        END


Output
------

String 11
String 12
String 13
String 21
String 22
String 23


            PASSING A COMMON BLOCK FROM Basic TO ASSEMBLY
            =============================================

Basic
-----

DECLARE SUB PutInfo ()
DIM b%(100)
COMMON /BNAME/ a%, b%(), c%

CALL PutInfo
CLS
PRINT a%, c%
FOR i = 0 TO 100
   PRINT b%(i);
NEXT i
END


Assembly
--------

.MODEL MEDIUM

BNAME segment COMMON 'BC_VARS'
   a  dw 1 dup (?)
   b  db 202 dup (?)      ;Note that all the space for the
                          ;array is set up
   c  dw 1 dup (?)
BNAME ends

DGROUP group BNAME

.CODE

        PUBLIC PutInfo
PutInfo PROC FAR
        push bp
        mov bp, sp               ; set stack frame
        push di
        inc word ptr dgroup:a    ; add 1 to a
        inc word ptr dgroup:c    ; add 1 to b

        mov cx, 101              ; value to initialize b% array
        mov di, offset dgroup:b

repeat:
        mov [di], cx             ; store value to b% array
        add di, 2                ; go to next integer variable
        loop repeat              ; note value in cx decremented
        pop di
        pop bp
        ret
PutInfo ENDP
        END


Output
------

 1     2
101 100 99 98 97 96 95 94 93 92 91 90 89 88 87 86 85 84 83 82 81
80 79 78 77 76 75 74 73 72 71 70 69 68 67 66 65 64 63 62 61 60 59
58 57 56 55 54 53 52 51 50 49 48 47 46 45 44 43 42 41 40 39 38 37
36 35 34 33 32 31 30 29 28 27 26 25 24 23 22 21 20 19 18 17 16 15
14 13 12 11 10 9 8 7 6 5 4 3 2 1

   Note: When dynamic arrays are used, the array is not placed in
   the COMMON block. Instead, a multibyte array descriptor is
   placed in the COMMON block. The dynamic array descriptor changes
   from version to version, and is not released by Microsoft -- it
   is considered Microsoft proprietary information.


          AN ASSEMBLY FUNCTION RETURNING AN INTEGER TO Basic
          ==================================================

Basic
-----

DECLARE FUNCTION qprint%

FOR i = 1 TO 10
   x% = qprint%
   PRINT x%
NEXT i


Assembly
--------

.MODEL MEDIUM
.DATA
        shortnum dw 12345

.CODE
        PUBLIC QPrint
QPrint  PROC FAR
        push BP
        mov ax, shortnum                 ; value is stored in AX

        pop BP
        ret

QPrint  ENDP
        END


Output
------

 12345
 12345
 12345
 12345
 12345
 12345
 12345
 12345
 12345
 12345


        AN ASSEMBLY FUNCTION RETURNING A LONG INTEGER TO Basic
        ======================================================

Basic
-----

DECLARE FUNCTION qprint&

FOR i = 1 TO 10
   x& = qprint&
   PRINT x&
NEXT i


Assembly
--------

.MODEL MEDIUM
.DATA
        longnum dd 12345

.CODE
        PUBLIC  QPrint
QPrint  PROC FAR
        push bp
        mov ax, WORD PTR longnum         ; high order portion in AX
        mov dx, WORD PTR longnum+2       ; low order portion in DX

        pop bp
        ret

QPrint  ENDP
        END


Output
------

 12345
 12345
 12345
 12345
 12345
 12345
 12345
 12345
 12345
 12345


                    AN ASSEMBLY FUNCTION RETURNING
                 A SINGLE-PRECISION VARIABLE TO Basic
                 ====================================

Basic
-----

DECLARE FUNCTION qprint!

FOR i = 1 TO 2
   x! = qprint!
   PRINT x!
NEXT i


Assembly
--------

.MODEL MEDIUM
.DATA
        singlenum DD 98.6

.CODE
        PUBLIC QPrint
QPrint  PROC FAR
        push bp
        mov bp, sp
        push es
        push si
        push di

        push ds   ; set es = ds
        pop es

        mov si, offset dgroup:singlenum
        mov di, [bp+6]  ;LOAD VALUE INTO ADDRESS AT BP+6
        mov cx, 4
        rep movsb

        mov ax, [bp+6]  ;LOAD OFFSET OF TEMP VALUE IN AX and
        mov dx, ss      ;SS into DX
        pop di
        pop si
        pop es
        pop bp
        ret 2

QPrint  ENDP
        END


Output
------

98.6
98.6


                    AN ASSEMBLY FUNCTION RETURNING
                 A DOUBLE-PRECISION VARIABLE TO Basic
                 ====================================

Basic
-----

DECLARE FUNCTION qprint#
FOR i = 1 TO 2
   x# = qprint#
   PRINT x#
NEXT i


Assembly
--------

.MODEL MEDIUM
.DATA
        doublenum DQ 6765.89

.CODE
        PUBLIC QPrint
QPrint  PROC FAR
        push bp
        mov bp, sp
        push es
        push si
        push di

        push ds  ;set es==ds
        pop es

        mov si, offset dgroup:doublenum
        mov di, [bp+6]  ;LOAD VALUE INTO ADDRESS AT BP+6
        mov cx, 4
        rep movsw

        mov ax, [BP+6]  ;LOAD OFFSET OF TEMP VALUE IN AX and
        mov dx, ss      ;SS into DX

        pop di
        pop si
        pop es
        pop bp
        ret 2
QPrint  ENDP
        END


Output
------

6765.89
6765.89


                    AN ASSEMBLY FUNCTION RETURNING
                  A VARIABLE-LENGTH STRING TO Basic
                  =================================

Basic
-----

DECLARE FUNCTION Qprint$ (i%)
CLS
FOR i% = 1 TO 3
   d$ = Qprint$(i%)    ' i% is the length of the string to be created.
   PRINT d$, LEN(d$)
NEXT


Assembly
--------

.MODEL MEDIUM
.DATA
        str      db 10 dup (?)  ;my own string
        mystring dw ?           ;my own descriptor (length)
                 dw ?           ;(offset)
.CODE
PUBLIC QPrint
QPrint PROC FAR
       push bp       ;save registers for Basic
       mov bp, sp
       push ds
       push es
       mov bx, [bp+6] ;get the length off the stack
       mov cx, [bx]   ;and put it in CX
       push ds
       pop es
       mov di, offset dgroup:str     ;load the offset into DI
       mov ax, 'a'                   ; load character to fill
       rep stosb                     ;store "a" into the string
       mov cx, [bx]
       mov bx, offset dgroup:mystring ;put offset of descriptor in
                                     ;  BX
       mov [bx], cx                  ;length in first two bytes
       mov [bx+2], offset dgroup:str ;offset into second two bytes
       move ax, bx                   ;load address of descriptor
                                     ; into AX
       pop es
       pop ds
       pop bp        ;restore BP for Basic
       ret 2         ;return skipping the passed parameters
QPrint ENDP
       END


Output
------

a     1
aa    2
aaa   3


                    USING SETMEM TO ALLOCATE SPACE
                  FOR MEMORY ALLOCATION IN ASSEMBLY
                  =================================

Basic
-----

DECLARE SUB AMem(BYVAL AllocSize AS INTEGER)

CLS
' Decrease the size of the far heap so AMem can use a DOS
' interrupt to get dynamic memory
BeforeCall% = SETMEM(-2048)
CALL AMem(1024%)
' Return the memory to the far heap; use a larger value so
' all space goes back into the heap.
AfterCall% = SETMEM(3500)

LOCATE 2, 1
IF AfterCall% <= BeforeCall% THEN
   PRINT "Memory not reallocated"
ELSE
   PRINT "Memory was successfully reallocated"
END IF

END


Assembly
--------

MODEL MEDIUM, Basic
.DATA
        Fail    DB 'Failed to allocate memory$'
        Success DB 'Successfully allocated memory$'
.CODE
        PUBLIC AMem
AMem    PROC
        push bp
        mov bp, sp                ; set stack frame
        push cx
        push es

        mov ax, [bp+6]            ; get number of bytes free
        mov cl, 4                 ; divide by 16 to get number of
        shr ax, cl                ;   paragraphs of memory
        mov bx, ax
        mov ah, 48h
        int 21h                   ; DOS interrupt to allocate block
        mov es, ax                ;   of memory
        mov ah, 9
        jnc NoFail                ; carry flag clear if successful
        mov dx, OFFSET Fail       ; display failed message
        int 21h
        jmp Exit                  ; go back to Basic

NoFail: mov dx, OFFSET Success    ; display success message
        int 21h
        mov ah, 49h
        int 21h

Exit:   pop es
        pop cx
        pop bp
        ret 2
AMem    ENDP
        END
                

Output

Successfully allocated memory
Memory was successfully reallocated


Additional query words: QuickBas BasicCom

Keywords: kbcode KB71275