Document revision date: 30 March 2001
[Compaq] [Go to the documentation home page] [How to order documentation] [Help on this site] [How to contact us]
[OpenVMS documentation]

OpenVMS VAX RTL Mathematics (MTH$) Manual


Previous Contents Index

1.7 Examples of Calls to Run-Time Library Mathematics Routines

1.7.1 BASIC Example

The following BASIC program uses the H-floating data type. BASIC also supports the D-floating, F-floating, and G-floating data types, but does not support the complex data types.


#1

10      !+ 
        ! Sample program to demonstrate a call to MTH$HEXP from BASIC. 
        !- 
 
        EXTERNAL SUB MTH$HEXP ( HFLOAT, HFLOAT ) 
 
        DECLARE HFLOAT X,Y      ! X and Y are H-floating 
        DIGITS$ = '###.#################################' 
        X = '1.2345678901234567891234567892'H 
        CALL MTH$HEXP (Y,X) 
        A$ = 'MTH$HEXP of ' + DIGITS$ + ' is ' + DIGITS$ 
        PRINT USING A$, X, Y 
        END 
 
      

The output from this program is as follows:


MTH$HEXP of  1.234567890123456789123456789200000 
is 3.436893084346008004973301321342110 

1.7.2 COBOL Example

The following COBOL program uses the F-floating and D-floating data types. COBOL does not support the G-floating and H-floating data types or the complex data types.

This COBOL program calls MTH$EXP and MTH$DEXP.


#1

IDENTIFICATION DIVISION. 
PROGRAM-ID.    FLOATING_POINT. 
* 
*  Calls MTH$EXP using a Floating Point data type. 
*  Calls MTH$DEXP using a Double Floating Point data type. 
* 
ENVIRONMENT DIVISION. 
DATA DIVISION. 
WORKING-STORAGE SECTION. 
01 FLOAT_PT     COMP-1. 
01 ANSWER_F     COMP-1. 
01 DOUBLE_PT    COMP-2. 
01 ANSWER_D     COMP-2. 
PROCEDURE DIVISION. 
P0. 
        MOVE 12.34 TO FLOAT_PT. 
        MOVE 3.456 TO DOUBLE_PT. 
 
        CALL "MTH$EXP" USING BY REFERENCE FLOAT_PT GIVING ANSWER_F. 
        DISPLAY " MTH$EXP of ", FLOAT_PT CONVERSION, " is ", 
                                               ANSWER_F CONVERSION. 
 
        CALL "MTH$DEXP" USING BY REFERENCE DOUBLE_PT GIVING ANSWER_D. 
        DISPLAY " MTH$DEXP of ", DOUBLE_PT CONVERSION, " is ", 
                                               ANSWER_D CONVERSION. 
        STOP RUN. 
 
 
 
 
      

The output from this example program is as follows:


MTH$EXP of  1.234000E+01 is  2.286620E+05 
MTH$DEXP of  3.456000000000000E+00 is 
3.168996280537917E+01 

1.7.3 Fortran Examples

The first Fortran program below uses the G-floating data type. The second Fortran program below uses the H-floating data type. The third Fortran program below uses the F-floating complex data type. Fortran supports the four floating data types and the three complex data types.


#1

C+ 
C This Fortran program computes the log base 2 of x, log2(x) in 
C G-floating double precision by using the RTL routine MTH$GLOG2. 
C 
C Declare X and Y and MTH$GLOG2 as double precision values. 
C 
C MTH$GLOG2 will return a double precision value to variable Y. 
C- 
 REAL*8 X, Y, MTH$GLOG2 
 X = 16.0 
 Y = MTH$GLOG2(X) 
 WRITE (6,1) X, Y 
1 FORMAT (' MTH$GLOG2(',F4.1,') is ',F4.1) 
 END 
 
      

The output generated by the preceding program is as follows:


MTH$GLOG2(16.0) is  4.0 

#2

C+ 
C This Fortran program computes the log base 2 of x, log2(x) in 
C H-floating precision by using the RTL routine MTH$HLOG2. 
C 
C Declare X and Y and MTH$GLOG2 as REAL*16 values. 
C 
C MTH$HLOG2 will return a REAL*16 value to variable Y. 
C- 
 REAL*16 X, Y 
 X = 16.12345678901234567890123456789 
 CALL MTH$HLOG2(Y, X) 
 WRITE (6,1) X, Y 
1 FORMAT (' MTH$HLOG2(',F30.27,') is ',F30.28) 
 END 
 
      

The output generated by the preceding program is as follows:


MTH$HLOG2(16.123456789012345678901234568) is 4.0110891785623860194931388310 

#3

C+ 
C    This Fortran example raises a complex base to 
C    a NONNEGATIVE integer power using OTS$POWCJ. 
C 
C    Declare Z1, Z2, Z3, and OTS$POWCJ as complex values. 
C    Then OTS$POWCJ returns the complex result of 
C    Z1**Z2:   Z3 = OTS$POWCJ(Z1,Z2), 
C    where Z1 and Z2 are passed by value. 
C- 
        COMPLEX Z1,Z3,OTS$POWCJ 
        INTEGER Z2 
C+ 
C    Generate a complex base. 
C- 
        Z1 = (2.0,3.0) 
C+ 
C    Generate an integer power. 
C- 
        Z2 = 2 
 
C+ 
C    Compute the complex value of Z1**Z2. 
C- 
        Z3 = OTS$POWCJ( %VAL(REAL(Z1)), %VAL(AIMAG(Z1)), %VAL(Z2)) 
        TYPE 1,Z1,Z2,Z3 
  1     FORMAT(' The value of (',F10.8,',',F11.8,')**',I1,' is 
     +  (',F11.8,',',F12.8,').') 
        END 
 
      

The output generated by the preceding Fortran program is as follows:


The value of (2.00000000, 3.00000000)**2 is 
(-5.00000000, 12.00000000). 

1.7.4 MACRO Examples

MACRO and BLISS support JSB entry points as well as CALLS and CALLG entry points. Both MACRO and BLISS support the four floating data types and the three complex data types.

The following MACRO programs show the use of the CALLS and CALLG instructions, as well as JSB entry points.


#1

        .TITLE  EXAMPLE_JSB 
;+ 
;  This example calls MTH$DEXP by using a MACRO JSB command. 
;  The JSB command expects R0/R1 to contain the quadword input value X. 
;  The result of the JSB will be located in R0/R1. 
;-    
        .EXTRN  MTH$DEXP_R6     ;MTH$DEXP is an external routine. 
        .PSECT  DATA, PIC, EXE, NOWRT 
X:      .DOUBLE 2.0             ; X is 2.0 
        .ENTRY  EXAMPLE_JSB, ^M<> 
        MOVQ    X, R0           ; X is in registers R0 and R1 
        JSB     G^MTH$DEXP_R6   ; The result is returned in R0/R1. 
        RET 
        .END    EXAMPLE_JSB 
 
 
 
      

This MACRO program generates the following output:


R0 <-- 732541EC 
R1 <-- ED6EC6A6 
 
That is, MTH$DEXP(2) is 7.3890560989306502 

#2

        .TITLE EXAMPLE_CALLG 
;+ 
;  This example calls MTH$HEXP by using a MACRO CALLG command. 
;  The CALLG command expects that the address of the return value 
;  Y, the address of the input value X, and the argument count 2 be 
;  stored in memory; this program stores this information in ARGUMENTS. 
;  The result of the CALLG will be located in R0/R1. 
;-       
        .EXTRN  MTH$HEXP        ; MTH$HEXP is an external routine. 
        .PSECT  DATA, PIC, EXE, WRT 
ARGUMENTS: 
        .LONG   2               ; The CALLG will use two arguments. 
        .ADDRESS Y, X           ; The first argument must be the address 
                                ;  receiving the computed value, while 
                                ;  the second argument is used to 
                                ;  compute exp(X). 
X:      .H_FLOATING 2           ; X = 2.0 
Y:      .H_FLOATING 0           ; Y is the result, initially set to 0. 
        .ENTRY  EXAMPLE_G, ^M<> 
        CALLG   ARGUMENTS, G^MTH$HEXP ; CALLG returns the value to Y. 
        RET 
        .END    EXAMPLE_G 
 
 
 
      

The output generated by this MACRO program is as follows:


address of Y <-- D8E64003 
             <-- 4DDA4B8D 
             <-- 3A3BDCC3 
             <-- B68BA206 
 
That is, MTH$HEXP of 2.0 returns 
7.38905609893065022723042746057501 

#3

        .TITLE EXAMPLE_CALLS 
;+ 
;  This example calls MTH$HEXP by using the MACRO CALLS command. 
;  The CALLS command expects the SP to contain the H-floating address of 
;  the return value, the address of the input argument X, and the argument 
;  count 2. The result of the CALLS will be located in registers R0-R3. 
;-    
      .EXTRN  MTH$HEXP        ; MTH$HEXP is an external routine. 
      .PSECT  DATA, PIC, EXE, WRT 
Y:    .H_FLOATING 0           ; Y is the result, initially set to 0. 
X:    .H_FLOATING 2           ; X = 2 
      .ENTRY  EXAMPLE_S, ^M<> 
      MOVAL   X, -(SP)        ; The address of X is in the SP. 
      MOVAL   Y, -(SP)        ; The address of Y is in the SP 
      CALLS   Y, G^MTH$HEXP   ; The value is returned to the address of Y. 
      RET 
      .END    EXAMPLE_S 
 
 
 
      

The output generated by this program is as follows:


address of Y <-- D8E64003 
             <-- 4DDA4B8D 
             <-- 3A3BDCC3 
             <-- B68BA206 
 
That is, MTH$HEXP of 2.0 returns 
7.38905609893065022723042746057501 

#4

        .TITLE  COMPLEX_EX1 
;+ 
;   This example calls MTH$CLOG by using a MACRO CALLG command. 
;   To compute the complex natural logarithm of Z = (2.0,1.0) register 
;   R0 is loaded with 2.0, the real part of Z, and register R1 is loaded 
;   with 1.0, the imaginary part of Z. The CALLG to MTH$CLOG 
;   returns the value of the natural logarithm of Z in 
;   registers R0 and R1. R0 gets the real part of Z and R1 
;   gets the imaginary part. 
;-    
        .EXTRN  MTH$CLOG 
        .PSECT  DATA, PIC, EXE, NOWRT 
ARGS:   .LONG   1               ; The CALLG will use one argument. 
        .ADDRESS REAL           ; The one argument that the CALLG 
                                ;  uses is the address of the argument 
                                ;  of MTH$CLOG. 
REAL:   .FLOAT  2               ; real part of Z is 2.0 
IMAG:   .FLOAT  1               ; imaginary part Z is 1.0 
        .ENTRY  COMPLEX_EX1, ^M<> 
        CALLG   ARGS, G^MTH$CLOG; MTH$CLOG returns the real part of the 
                                ;  complex natural logarithm in R0 and 
                                ;  the imaginary part in R1. 
        RET 
        .END    COMPLEX_EX1 
 
 
      

This program generates the following output:


R0 <---  0210404E 
R1 <---  63383FED 
 
That is, MTH$CLOG(2.0,1.0) is 
(0.8047190,0.4636476) 

#5

        .TITLE  COMPLEX_EX2 
;+ 
;   This example calls MTH$CLOG by using a MACRO CALLS command. 
;   To compute the complex natural logarithm of Z = (2.0,1.0) register 
;   R0 is loaded with 2.0, the real part of Z, and register R1 is loaded 
;   with 1.0, the imaginary part of Z.  The CALLS to MTH$CLOG 
;   returns the value of the natural logarithm of Z in registers R0 
;   and R1. R0 gets the real part of Z and R1 gets the imaginary 
;   part. 
;- 
        .EXTRN  MTH$CLOG 
        .PSECT  DATA, PIC, EXE, NOWRT 
REAL:   .FLOAT  2               ; real part of Z is 2.0 
IMAG:   .FLOAT  1               ; imaginary part Z is 1.0 
        .ENTRY  COMPLEX_EX2, ^M<> 
        MOVAL   REAL, -(SP)     ; SP <-- address of Z. Real part of Z is 
                                ;  in @(SP) and imaginary part is in 
        CALLS   #1, G^MTH$CLOG  ;  @(SP)+4. 
                                ; MTH$CLOG return the real part of the 
                                ;  complex natural logarithm in R0 and 
                                ;  the imaginary part in R1. 
        RET 
        .END    COMPLEX_EX2 
 
 
      

This MACRO example program generates the following output:


R0 <---  0210404E 
R1 <---  63383FED 
 
That is, MTH$CLOG(2.0,1.0) is 
(0.8047190,0.4636476) 

1.7.5 Pascal Examples

The following Pascal programs use the D-floating and H-floating data types. Pascal also supports the F-floating and G-floating data types. Pascal does not support the complex data types.


#1

{+} 
{ Sample program to demonstrate a call to MTH$DEXP from PASCAL. 
{-} 
 
PROGRAM CALL_MTH$DEXP (OUTPUT); 
 
{+} 
{ Declare variables used by this program. 
{-} 
 
VAR 
    X : DOUBLE := 3.456;        { X,Y are D-floating unless overridden } 
    Y : DOUBLE;                 { with /DOUBLE qualifier on compilation } 
 
{+} 
{ Declare the RTL routine used by this program. 
{-} 
 
[EXTERNAL,ASYNCHRONOUS] 
                  FUNCTION MTH$DEXP (VAR value : DOUBLE) : DOUBLE; EXTERN; 
BEGIN 
    Y := MTH$DEXP (x); 
    WRITELN ('MTH$DEXP of ', X:5:3, ' is ', Y:20:16); 
END. 
 
 
      

The output generated by this Pascal program is as follows:


MTH$DEXP of 3.456 is  31.6899656462382318 

#2

{+} 
{ Sample program to demonstrate a call to MTH$HEXP from PASCAL. 
{-} 
 
PROGRAM CALL_MTH$HEXP (OUTPUT); 
 
{+} 
{ Declare variables used by this program. 
{-} 
 
VAR 
    X : QUADRUPLE := 1.2345678901234567891234567892; { X is H-floating } 
    Y : QUADRUPLE;                                   { Y is H-floating } 
 
{+} 
{ Declare the RTL routine used by this program. 
{-} 
 
[EXTERNAL,ASYNCHRONOUS] PROCEDURE MTH$HEXP (VAR h_exp : QUADRUPLE; 
value : QUADRUPLE); EXTERN; 
 
BEGIN 
    MTH$HEXP (Y,X); 
    WRITELN ('MTH$HEXP of ', X:30:28, ' is ', Y:35:33); 
END. 
 
 
      

This Pascal program generates the following output:


MTH$DEXP of 3.456 is  31.6899656462382318 

1.7.6 PL/I Examples

The following PL/I programs use the D-floating and H-floating data types to test entry points. PL/I also supports the F-floating and G-floating data types. PL/I does not support the complex data types.


#1

/* 
*                                                                           * 
*       This program tests a MTH$D entry point                              * 
*                                                                           * 
*/ 
TEST:   PROC OPTIONS (MAIN) ; 
 
        DCL (MTH$DEXP) 
                ENTRY (FLOAT(53)) RETURNS (FLOAT(53)); 
        DCL OPERAND FLOAT(53); 
        DCL RESULT FLOAT(53); 
 
/*** Begin test ***/ 
        OPERAND = 3.456; 
        RESULT = MTH$DEXP(OPERAND); 
        PUT EDIT ('MTH$DEXP of ', OPERAND, ' is ', 
            RESULT)(A(12),F(5,3),A(4),F(20,15)); 
 
END TEST; 
 
 
      

The output generated by this PL/I program is as follows:


MTH$DEXP of 3.456 is   31.689962805379165 

#2

/* 
*                                                                           * 
*       This program tests a MTH$H entry point.                             * 
*       Note that in the PL/I statement below, the /G-float switch          * 
*       is needed to compile both G- and H-floating point MTH$ routines.    */ 
 
TEST:   PROC OPTIONS (MAIN) ; 
 
        DCL (MTH$HEXP) 
                ENTRY (FLOAT (113), FLOAT (113)) ; 
        DCL OPERAND FLOAT (113); 
        DCL RESULT FLOAT (113); 
 
/*** Begin test ***/ 
        OPERAND = 1.234578901234567891234567892; 
        CALL MTH$HEXP(RESULT,OPERAND); 
        PUT EDIT ('MTH$HEXP of ', OPERAND, ' is ', 
            RESULT) (A(12),F(29,27),A(4),F(29,27)); 
 
END TEST; 
 
 
      

To run this program, use the following DCL commands:


$ PLI/G_FLOAT EXAMPLE
$ LINK EXAMPLE
$ RUN EXAMPLE

This program generates the following output:


MTH$HEXP of 1.234578901234567891234567892 is 
3.436930928565989790506225633 

1.7.7 Ada Example

The following Ada program demonstrates the use of MTH$ routines in a manner that an actual program might use. The program performs the following steps:

  1. Reads a floating-point number from the terminal
  2. Calls MTH$SQRT to obtain the square root of the value read
  3. Calls MTH$JNINT to find the nearest integer of the square root
  4. Displays the result

This example runs on Compaq Ada for OpenVMS VAX.


#1

-- This Ada program calls the MTH$SQRT and MTH$JNINT routines. 
-- 
with FLOAT_MATH_LIB; 
    -- Package FLOAT_MATH_LIB is an instantiation of the generic package 
    -- MATH_LIB for the FLOAT datatype.  This package provides the most 
    -- common mathematical functions (SQRT, SIN, COS, etc.) in an easy 
    -- to use fashion.  An added benefit is that the Compaq Ada compiler 
    -- will use the faster JSB interface for these routines. 
with MTH; 
    -- Package MTH defines all the MTH$ routines.  It should be used when 
    -- package MATH_LIB is not sufficient.  All functions are defined here 
    -- as "valued procedures" for consistency. 
with FLOAT_TEXT_IO, INTEGER_TEXT_IO, TEXT_IO; 
procedure ADA_EXAMPLE is 
    FLOAT_VAL: FLOAT; 
    INT_VAL: INTEGER; 
begin 
    -- Prompt for initial value. 
    TEXT_IO.PUT ("Enter value: "); 
    FLOAT_TEXT_IO.GET (FLOAT_VAL); 
    TEXT_IO.NEW_LINE; 
 
    -- Take the square root by using the SQRT routine from package 
    -- FLOAT_MATH_LIB.  The compiler will use the JSB interface 
    -- to MTH$SQRT. 
    FLOAT_VAL := FLOAT_MATH_LIB.SQRT (FLOAT_VAL); 
 
    -- Find the nearest integer using MTH$JNINT.  Argument names are 
    -- the same as those listed for MTH$JNINT in the reference 
    -- section of this manual. 
    MTH.JNINT (F_FLOATING => FLOAT_VAL, RESULT => INT_VAL); 
 
    -- Write the result. 
    TEXT_IO.PUT ("Result is: "); 
    INTEGER_TEXT_IO.PUT (INT_VAL); 
    TEXT_IO.NEW_LINE; 
end ADA_EXAMPLE; 
 
      

To run this example program, use the following DCL commands:


$ CREATE/DIR [.ADALIB]
$ ACS CREATE LIB [.ADALIB]
$ ACS SET LIB [.ADALIB]
$ ADA ADA_EXAMPLE
$ ACS LINK ADA_EXAMPLE
$ RUN ADA_EXAMPLE

The preceding Ada example generates the following output:


Enter value: 42.0
Result is:               6


Previous Next Contents Index

  [Go to the documentation home page] [How to order documentation] [Help on this site] [How to contact us]  
  privacy and legal statement  
6117PRO_001.HTML