Compaq COBOL AAQ2G1FTK User Manual

Page 456

Advertising
background image

Interprogram Communication
12.7 Calling Non-COBOL Programs from Compaq COBOL

Example 12–12 (Cont.) Calling a Fortran Program from a COBOL Program

DATA DIVISION.
WORKING-STORAGE SECTION.
01

INPUT-NUMBER.
03

INTEGER

PIC 9(5).

03

DEC-POINT

PIC X(1).

03

DECIMAL

PIC 9(8).

01

WORK-NUMBER.
03

INTEGER

PIC 9(5).

03

DECIMAL

PIC 9(8).

01

WORK-NUMBER-A REDEFINES WORK-NUMBER

PIC 9(5)V9(8).

01

DISPLAY-NUMBER

PIC ZZ,ZZ9.9999.

PROCEDURE DIVISION.
STARTER SECTION.
SBEGIN.

MOVE SPACES TO INPUT-NUMBER.
DISPLAY "Enter number (with decimal point): "

NO ADVANCING.

ACCEPT INPUT-NUMBER.
IF INPUT-NUMBER = SPACES

GO TO ENDJOB.

CALL "SQROOT" USING BY DESCRIPTOR INPUT-NUMBER.

IF INPUT-NUMBER = ALL "*"

DISPLAY "** INVALID ARGUMENT FOR SQUARE ROOT"

ELSE

DISPLAY "The square root is: " INPUT-NUMBER
INSPECT INPUT-NUMBER

REPLACING ALL " " BY "0"

MOVE CORRESPONDING INPUT-NUMBER TO WORK-NUMBER
WORK-NUMBER-A TO DISPLAY-NUMBER
DISPLAY DISPLAY-NUMBER.

GO TO SBEGIN.

ENDJOB.

STOP RUN.

Example 12–13 shows the Fortran program SQROOT called by the program in
Example 12–12 and sample output from the programs’ execution.

The SQROOT subroutine accepts a 14-character string and decodes it into a
real variable (DECODE is analogous to an internal READ). It then calls the
SQRT function in the statement that encodes the result into the 14-character
argument.

Example 12–13 Fortran Subroutine SQROOT

SUBROUTINE SQROOT(ARG)
CHARACTER*14 ARG
DECODE(14,10,ARG,ERR=20)VAL

10

FORMAT(F12.6)
IF(VAL.LT.0.)GO TO 20
ENCODE(14,10,ARG)SQRT(VAL)

999

RETURN

20

ARG=’**************’
GO TO 999
END

12–26 Interprogram Communication

Advertising