Calling Non-COBOL Subprograms [ HP COBOL II/XL Programmer's Guide ] MPE/iX 5.0 Documentation
HP COBOL II/XL Programmer's Guide
Calling Non-COBOL Subprograms
Your COBOL program can call subprograms and intrinsics written in C,
FORTRAN 77, Pascal, and SPL. For each call to such a subprogram, the
COBOL compiler generates the following information for the linker:
* The type of the identifier in the GIVING clause of the CALL
statement.
* The alignment of each identifier in the USING clause of the CALL
statement (for parameters that are passed by value, the type is
generated also).
* The number of parameters.
You must ensure that the types of the actual parameters in the CALL
statement are compatible with the types of their corresponding formal
parameters in the non-COBOL subprogram. (Compile-time checking is
impossible, because COBOL does not support forward declarations unless
CALLINTRINSIC is used.)
The Control options CALLALIGNED and CALLALIGNED16 cause the compilers to
issue a "Questionable" message for each parameter that is not aligned on
a 32-bit or 16-bit boundary, respectively. The "Questionable" message
applies to actual parameters.
Calling Subprograms Written in C
Your COBOL program can call a subprogram written in C if the parameters
of the C routine are of types that have compatible COBOL types. If the C
routine is a function, it must return a type that has a compatible COBOL
type, and the identifier in the GIVING clause of the CALL statement must
be of that compatible COBOL type.
Table 4-4. Compatible COBOL and C Types
------------------------------------------------------------------
| | |
| COBOL Type | C Type |
| | |
------------------------------------------------------------------
| | |
| PIC X | char |
| | |
------------------------------------------------------------------
| | |
| PIC X(n) | char [n][REV BEG] |
| | |
------------------------------------------------------------------
| | |
| PIC S9 to S9(4) (1) [REV END] | short int[REV BEG] |
| USAGE COMP or BINARY | |
| level 01 or 77, or SYNC | |
| | |
------------------------------------------------------------------
| | |
| PIC S9(5) to S9(9) (1) [REV END] | int |
| USAGE COMP or BINARY | |
| level 01 or 77, or SYNC | |
| (but not $CONTROL SYNC16). | |
| | |
------------------------------------------------------------------
(1) For best results, use the largest value in the range.
A C parameter is either passed by value or its address is passed by
value. The latter is preceded by an asterisk (*) in the formal parameter
declaration.
If the formal C parameter itself is passed by value, pass the actual
COBOL parameter to it by value (enclose it in backslashes). If the
address of the formal C parameter is passed by value, pass the actual
COBOL parameter to it by reference.
Example.
The following is a C subprogram that returns a nonvoid value:
# 1 "CGRANDE.PUBS.COBOL"
int grande (arr,len)
int *arr;
int len;
{
int largest = arr [0], i;
for (i = 1; i< len; i++)
if (largest < arr [i])
largest = arr[i];
return largest;
}
The following is a C subprogram that returns a void value:
# 1 "CREVERS.PUBS.COBOL"
void reverses (s)
char *s;
{
int right = strlen (s) -1, left = 0;
char t;
for (; left < right; right--, left++) {
t = s [right];
s [right] = s [left];
s [left] = t;
}
}
Many C routines expect a null byte at the end of each ASCII string. The
routine reverses, above, is an example of such a C routine. The
following COBOL program, which calls reverses, declares a null-terminated
ASCII string in COBOL. First it declares the null byte as a PIC X data
item (which can be byte-aligned).
The following is a COBOL program that calls the two C subprograms above:
00001 COBCNTL 000010* Defaults for Compatibility Mode compiler follow.
00002 COBCNTL 001100*CONTROL LIST,SOURCE,NOCODE,NOCROSSREF,ERRORS=100,NOVERBS,
WARN
00003 COBCNTL 001200*CONTROL LINES=60,NOMAP,MIXED,QUOTE=",NOSTDWARN,SYNC16,
INDEX16
00004 COBCNTL 001210*
00005 COBCNTL 001300* Defaults for Native Mode compiler follow.
00006 COBCNTL 001400*
00007 COBCNTL 001600*CONTROL LIST,SOURCE,NOCODE,NOCROSSREF,ERRORS=100,NOVERBS,
WARN
00008 COBCNTL 001700*CONTROL LINES=60,NOMAP,MIXED,QUOTE=",NOSTDWARN,SYNC32,
INDEX32
00009 COBCNTL 001800*CONTROL NOVALIDATE,OPTIMIZE=0
00010 COBCNTL 001900*
00011 COBCNTL 002000* For any other options, redirect COBCNTL.PUB.SYS using
00012 COBCNTL 002100* a file equation.
00013 COBCNTL 002200*
00014 001000 ID DIVISION.
00015 002000 PROGRAM-ID. CALLC.
00016 003000
00017 004000 DATA DIVISION.
00018 005000 WORKING-STORAGE SECTION.
00019 006000 01 TABLE-1.
00020 007000 05 TABLE-EL OCCURS 9 PIC S9(9) BINARY SYNC.
00021 008000 01 LARGST PIC S9(9) BINARY SYNC.
00022 008100 01 STRING-REC.
00023 009000 05 STRING-1 PIC X(9) VALUE "ABCDEFGHI".
00024 009100 05 STRING-NULL PIC X VALUE LOW-VALUE.
00025 091100
00026 009200 01 LEN PIC S9(9) BINARY SYNC.
00027 011000
00028 012000 PROCEDURE DIVISION.
00029 013000 01-TEST.
00030 014000
00031 015000 MOVE 10 TO TABLE-EL(1).
00032 016000 MOVE 8 TO TABLE-EL(2).
00033 017000 MOVE 14 TO TABLE-EL(3).
00034 018000 MOVE 9 TO TABLE-EL(4).
00035 019000 MOVE 18 TO TABLE-EL(5).
00036 020000 MOVE 98 TO TABLE-EL(6).
00037 021000 MOVE 7 TO TABLE-EL(7).
00038 022000 MOVE 23 TO TABLE-EL(8).
00039 023000
00040 025100 MOVE 8 TO LEN.[REV BEG]
00041 025200 CALL "GRANDE" USING TABLE-1 \LEN\ GIVING LARGST.[REV END]
00042 026000 DISPLAY LARGST.
00043 027000
00044 028000
00045 029000
00046 030000 DISPLAY STRING-1 " BACKWARDS IS " WITH
NO ADVANCING
00047 031000 CALL "REVERSES" USING STRING-1.
00048 032000 DISPLAY STRING-1.
The following are commands that compile, link, and execute the C
subprograms and the COBOL program above:
:ccxl cgrande,cgrandeo,$null
:ccxl crevers,creverso,$null
:cob85xl callc,callco,$null
:link from=callco,cgrandeo,creverso;to=pcallc
:run pcallc
The COBOL program displays the following:
+000000098
ABCDEFGHI BACKWARDS IS IHGFEDCBA
[REV BEG]
NOTE The COBOL function REVERSE is more efficient than the above example
in C.
[REV END]
Calling Subprograms Written in FORTRAN 77
Your COBOL program can call a subprogram written in FORTRAN 77 if the
parameters of the FORTRAN 77 routine are of types that have compatible
COBOL types.
Table 4-5 shows compatible COBOL and FORTRAN 77 types. FORTRAN 77
types that are not in Table 4-5 do not have compatible COBOL types.
The number n is an integer.
Table 4-5. Compatible COBOL and FORTRAN Types
---------------------------------------------------------------------------
| | |
| COBOL Type | FORTRAN 77 Type |
| | |
---------------------------------------------------------------------------
| | |
| Pass two variables to describe the FORTRAN string: | CHARACTER*n |
| (1) A variable that is a group item or of | [REV BEG] |
| type PIC X, that contains the string. | |
| (2) A variable of type PIC S9(9) BINARY SYNC, | |
| that contains the length of the string, | |
| enclosed in backslashes. | |
| | |
---------------------------------------------------------------------------
| | |
| PIC S9 to S9(4) (1) [REV END] | [REV BEG]INTEGER*2[REV END]
| USAGE COMP or BINARY. | [REV BEG] |
| Level 01 or 77, or SYNC. | |
| | |
---------------------------------------------------------------------------
| | |
| PIC S9(5) to S9(9) (1) [REV END] | INTEGER*4 |
| USAGE COMP or BINARY. | |
| Level 01 or 77, or SYNC | |
| (but not with $CONTROL SYNC16). | |
| | |
---------------------------------------------------------------------------
(1) For best results, use the largest value in the range.
FORTRAN 77 integer parameters are always passed by reference. FORTRAN 77
character parameters are passed by descriptor (address, length, and
value, in that order). If your COBOL program calls a FORTRAN 77
subprogram, it must pass the actual parameters by reference or by
content.
Your COBOL program can call FORTRAN 77 functions of the types INTEGER*2
and INTEGER*4. The identifier in the GIVING clause of the CALL statement
in your program must be of a type that is compatible with the type of the
FORTRAN 77 function.
Your COBOL program cannot call FORTRAN 77 character functions, because
the data name in the GIVING clause must be numeric.
Example.
The following is a FORTRAN 77 subprogram:
INTEGER*4 FUNCTION LARGER(A,L)
INTEGER*4 A(8)
INTEGER*4 LARGST,L
C
C THIS SUBROUTINE FINDS THE LARGEST VALUE IN AN ARRAY
C OF 'L' INTEGERS.
C
LARGST = A(1)
DO 100 I = 2,L
IF (LARGST .LT. A(I)) LARGST = A(I)
100 CONTINUE
LARGER = LARGST
RETURN
END
C ******************************************************
C * SUBROUTINE BACKWRDS *
C * THIS SUBROUTINE REVERSES AN ARRAY OF 'L' CHARACTERS*
C ******************************************************
SUBROUTINE BACKWRDS(STR)
CHARACTER STR(10)
CHARACTER N
J = 10
DO 100 K = 1,5
N = STR(K)
STR(K) = STR(J)
STR(J) = N
J = J - 1
100 CONTINUE
RETURN
END
[REV BEG]
NOTE The COBOL function REVERSE is more efficient than the above example
in FORTRAN.
[REV END]
The following COBOL program calls the FORTRAN 77 subprogram above:
001000 IDENTIFICATION DIVISION.
002000 PROGRAM-ID. CALLFTN.
003000 DATA DIVISION.
004000 WORKING-STORAGE SECTION.
005000 01 TABLE-INIT.
006000 05 PIC S9(9) COMP SYNC VALUE 10.
007000 05 PIC S9(9) COMP SYNC VALUE 8.
008000 05 PIC S9(9) COMP SYNC VALUE 14.
009000 05 PIC S9(9) COMP SYNC VALUE 9.
010000 05 PIC S9(9) COMP SYNC VALUE 18.
011000 05 PIC S9(9) COMP SYNC VALUE 98.
012000 05 PIC S9(9) COMP SYNC VALUE 7.
013000 05 PIC S9(9) COMP SYNC VALUE 23.
014000 01 TABLE-1 REDEFINES TABLE-INIT.
015000 05 TABLE-EL OCCURS 8
016000 PIC S9(9) COMP SYNC.
017000
018000 01 LARGEST-VALUE PIC S9(9) COMP SYNC.
019000
020000 01 STRING-1 PIC X(10) VALUE "ABCDEFGHIJ".
021000 01 LEN PIC S9(9) COMP SYNC.
022000
023000 PROCEDURE DIVISION.
024000 P1.
025000****************************************************************
026000* Call FORTRAN 77 subroutine "LARGER" to find the largest *
027000* element in a table on "LEN" elements. *
028000****************************************************************
029000
030000 MOVE 8 TO LEN.
031000 CALL "LARGER" USING TABLE-1, LEN GIVING LARGEST-VALUE.
032000 DISPLAY LARGEST-VALUE " IS THE LARGEST VALUE IN THE TABLE".
033000
034000****************************************************************
035000* Call FORTRAN 77 subroutine "BACKWARDS" to reverse a string of*
036000* 10 characters. *
037000* Shows passing character strings to FORTRAN 77 subroutine *
038000****************************************************************
039000
040000 MOVE 10 TO LEN.
041000 DISPLAY STRING-1 " BACKWARDS IS " WITH NO ADVANCING.
043000 DISPLAY STRING-1.
The following commands compile and link the FORTRAN 77 subprogram and the
COBOL program:
:cob85xl callftn, callftno, $null
:ftnxl fortsub, fortsubo, $null
:link from=callftno,fortsubo;to=callftnp
The following command executes the COBOL program:
:callftnp
The COBOL program displays the following:
+000000098 IS THE LARGEST VALUE IN THE TABLE
ABCDEFGHIJ BACKWARDS IS JIHGFEDCBA
Calling Subprograms Written in Pascal
Your COBOL program can call a subprogram written in Pascal if the
parameters of the Pascal subprogram are of types that have compatible
COBOL types. Table 4-6 shows compatible COBOL and Pascal types,
assuming default Pascal alignment. See the note below. Pascal types
that are not in Table 4-6 do not have compatible COBOL types. The
number n is an integer.
Table 4-6. Compatible COBOL and Pascal Types
-----------------------------------------------------------------------
| | |
| COBOL Type | Pascal Type |
| | |
-----------------------------------------------------------------------
| | |
| PIC X | CHAR |
| | |
-----------------------------------------------------------------------
| | |
| PIC X(n) | PACKED ARRAY [n] OF |
| | where n is the length of |
| | the array.[REV BEG] |
| | |
-----------------------------------------------------------------------
| | |
| PIC S9 to S9(4) (1) [REV END] | SHORTINT[REV BEG] |
| USAGE COMP or BINARY. | |
| Level 01 or 77, or SYNC. | |
| | |
-----------------------------------------------------------------------
| | |
| PIC S9(5) to S9(9) (1) [REV END] | INTEGER |
| USAGE COMP or BINARY. | |
| Level 01 or 77, or SYNC | |
| (but not with $CONTROL SYNC16) | |
| | |
-----------------------------------------------------------------------
(1) For best results, use the largest value in the range.
NOTE You can specify any alignment for a Pascal type with the Pascal
compiler option ALIGNMENT. Particularly, you can specify byte
alignment (the COBOL default in the absence of SYNC) for all Pascal
types.[REV BEG] Refer to the HP Pascal/XL Reference Manual for more
information[REV END] on the ALIGNMENT compiler option.
Pascal VAR, UNCHECKABLE ANYVAR, and READONLY parameters are passed by
reference. All other Pascal parameters are passed by value. If your
COBOL program calls a Pascal subprogram, it must pass actual parameters
to formal VAR parameters by reference, and pass numeric actual parameters
to non-VAR parameters by value. (Parameters passed by value are enclosed
in backslashes. For example: \X\).
NOTE Your COBOL program cannot call a Pascal program that has ANYVAR (as
opposed to UNCHECKABLE ANYVAR) parameters, because each ANYVAR
parameter has a hidden parameter that COBOL cannot detect.
Your COBOL program can call Pascal functions of types that have
compatible COBOL types. The identifier in the GIVING clause of the CALL
statement in your program must be of a type that is compatible with the
type of the Pascal function.
Example.
The following is a Pascal subprogram:
$SUBPROGRAM$
PROGRAM PASCSUB;
TYPE
STRING_TYPE = PACKED ARRAY[1..10] OF CHAR;
ARRAY_TYPE = ARRAY[1..8] OF INTEGER;
(* ***************************************** *)
(* PROCEDURE REVERSE *)
(* ***************************************** *)
(* THIS PROCEDURE WILL REVERSE A STRING OF *)
(* 'LEN' CHARACTERS. *)
PROCEDURE REVERSE(VAR STRING1 : STRING_TYPE;
LEN : INTEGER);
VAR
J, K : INTEGER;
TEMP : CHAR;
BEGIN
J := LEN;
FOR K := 1 TO LEN DIV 2 DO
BEGIN
TEMP := STRING1[K];
STRING1[K] := STRING1[J];
STRING1[J] := TEMP;
J := J - 1;
END;
END;
(* ***************************************** *)
(* PROCEDURE GRANDE *)
(* ***************************************** *)
(* THIS PROCEDURE WILL FIND THE LARGEST *)
(* ITEM IN AN ARRAY OF 'L' ELEMENTS *)
FUNCTION GRANDE( VAR ARR : ARRAY_TYPE;
L : INTEGER) : INTEGER;
VAR
K : INTEGER;
LARGEST : INTEGER;
BEGIN
LARGEST := ARR[1];
FOR K := 2 TO L DO
IF LARGEST < ARR[K] THEN
LARGEST := ARR[K];
GRANDE := LARGEST;
END;
BEGIN
END.
[REV BEG]
NOTE The COBOL function REVERSE is more efficient than the above example
in Pascal.
[REV END]
The following COBOL program calls the Pascal subprogram above:
001000 ID DIVISION.
002000 PROGRAM-ID. IC807R.
003000
004000 DATA DIVISION.
005000 WORKING-STORAGE SECTION.
006000 01 TABLE-1.
007000 05 TABLE-EL OCCURS 8 PIC S9(9) BINARY SYNC.
008000 01 LARGST PIC S9(9) BINARY SYNC.
009000 01 STRING-1 PIC X(10) VALUE "ABCDEFGHIJ".
010000 01 LEN PIC S9(9) BINARY SYNC.
011000
012000 PROCEDURE DIVISION.
013000 0001-TEST.
014000
015000 MOVE 10 TO TABLE-EL(1).
016000 MOVE 8 TO TABLE-EL(2).
017000 MOVE 14 TO TABLE-EL(3).
018000 MOVE 9 TO TABLE-EL(4).
019000 MOVE 18 TO TABLE-EL(5).
020000 MOVE 98 TO TABLE-EL(6).
021000 MOVE 7 TO TABLE-EL(7).
022000 MOVE 23 TO TABLE-EL(8).
023000
024000 MOVE 8 TO LEN.
025000 CALL "GRANDE" USING TABLE-1 \8\ GIVING LARGST.
026000 DISPLAY LARGST.
027000
028000
029000 MOVE 10 TO LEN.
030000 DISPLAY STRING-1 " BACKWARDS IS STRING " WITH NO ADVANCING.
031000 CALL "REVERSE" USING STRING-1 \10\.
032000 DISPLAY STRING-1.
The following commands compile, link, and execute the program and
subprogram:
:pasxl pascsub,pascsubo,$null
:cob85xl callpas,callpaso,$null
:link from=callpaso,pascsubo;to=callpasp
:run callpasp
The COBOL program displays the following:
+000000098
ABCDEFGHIJ BACKWARDS IS STRING JIHGFEDCBA
Pascal and COBOL variables are both byte-aligned if:
* The Pascal subprogram includes the option $ALIGNMENT 1$.
* The COBOL program does not specify SYNC on elementary items in
records.
If a COBOL program and a Pascal subprogram share a record that contains
both 16- and 32-bit integers, the COBOL program must specify FILLER to
ensure that COBOL aligns the 16-bit integers as Pascal does. Otherwise,
COBOL aligns 16- and 32-bit integers on 32-bit boundaries[REV BEG] (if
SYNC is specified),[REV END] while Pascal aligns 16-bit integers on
16-bit boundaries and 32-bit integers on 32-bit boundaries.
Example.
The following COBOL program passes a record to a Pascal procedure:
001000 ID DIVISION.
002000 PROGRAM-ID. CPASREC.
003000
004000 DATA DIVISION.
005000 WORKING-STORAGE SECTION.
006000 01 PASCAL-RECORD.
007000 05 CHAR1 PIC X.
008000 05 FILLER PIC X.
009000* INT-16-BITS is not synchronized because that would place it on
010000* a 32 bit boundary. FILLER bytes were added to make sure that
011000* it is on a 16 bit boundary.
012000 05 INT-16-BITS PIC S9(4) BINARY.
013000 05 INT-32-BITS PIC S9(9) BINARY SYNC.
014000 05 STRING-VAR PIC X(10).
015000
016000 PROCEDURE DIVISION.
017000 0001-TEST.
018000 CALL "DISPLAY-RECS" USING PASCAL-RECORD.
019000
020000 DISPLAY "A 1 BYTE CHAR, 16, AND 32 BIT INTEGERS"
021000 " AND A STRING"
022000 " PASSED FROM A PASCAL RECORD".
023000 DISPLAY CHAR1.
024000 DISPLAY INT-16-BITS.
025000 DISPLAY INT-32-BITS.
026000 DISPLAY STRING-VAR.
The following Pascal program contains a procedure that the COBOL program
calls:
$SUBPROGRAM$
PROGRAM PASREC;
TYPE
PASCAL_RECORD = RECORD
CHAR1 : CHAR;
INT_16_BITS : SHORTINT;
INT_32_BITS : INTEGER;
STRING : PACKED ARRAY [1..10] OF CHAR;
END;
PROCEDURE DISPLAY_RECS( VAR PREC : PASCAL_RECORD);
BEGIN
WITH PREC DO
BEGIN
CHAR1 := 'A';
INT_16_BITS := 9999;
INT_32_BITS := -888888888;
STRING := 'LMNOPQRSTU';
END;
END;
BEGIN
END.
The following commands compile, link, and execute the COBOL and Pascal
programs above:
:pasxl pasrec,pasreco,$null
:cob85xl cpasrec,cpasreco,$null
:link from=cpasreco,pasreco;to=cpasrecp
:run cpasrecp
The Pascal types shortint and integer are not byte-aligned by default
(shortint is two-byte-aligned and integer is four-byte-aligned). The
option $ALIGNMENT 1$ degrades performance.
Calculations with byte-aligned numbers do work in Pascal, but you can
improve efficiency by assigning byte-aligned variables to temporary
variables that have the default alignment and manipulating the temporary
variables.
[REV BEG]
Elementary items in the following COBOL record are byte-aligned.[REV END]
COBOL record:
01 PACKED-REC.
05 P1 PIC X(3).
05 P2 PIC S9(4) COMP.
05 P3 PIC X(2).
05 P4 PIC S9(9) COMP.
[REV BEG]
To achieve byte-alignment in the corresponding Pascal record, use
$ALIGNMENT 1$ as shown below:[REV END]
In the Pascal record, the types shortint_1 and integer_1 are declared as
follows:
shortint_1 = $ALIGNMENT 1$ shortint;
integer_1 = $ALIGNMENT 1$ integer;
Equivalent Pascal record:
packed_record = RECORD
p1 : PACKED ARRAY [1..3] OF char;
p2 : shortint_1;
p3 : PACKED ARRAY [1..2] OF char; {For PIC X(2)}
p4 : integer_1;
END;
Calling Subprograms Written in SPL
Your COBOL program can call a subprogram written in SPL if the parameters
of the SPL subprogram are of types that have compatible COBOL types.
Table 4-7 shows compatible COBOL and SPL types. SPL types that are
not in Table 4-7 do not have compatible COBOL types. The number n is
an integer.
Table 4-7. Compatible COBOL and SPL Types
-----------------------------------------------------------------------
| | |
| COBOL Type | SPL Type |
| | |
-----------------------------------------------------------------------
| | |
| PIC X(n) | BYTE ARRAY[REV BEG] |
| | |
-----------------------------------------------------------------------
| | |
| PIC S9 to S9(4) (1) [REV END] | INTEGER[REV BEG] |
| USAGE COMP or BINARY. | |
| Level 01 or 77, or SYNC. | |
| | |
-----------------------------------------------------------------------
| | |
| PIC S9(5) to S9(9) (1) [REV END] DOUBLE[REV BEG] |
| USAGE COMP or BINARY. | |
| Level 01 or 77, or SYNC | |
| | |
-----------------------------------------------------------------------
| | |
| PIC S9(10) to S9(18) (1) [REV END]xact type is not available. |
| USAGE COMP or BINARY. | Declare it as an INTEGER ARRAY[REV BEG]
| SYNC. | (with four elements) in the[REV END]
| | SPL subprogram. |
| | |
-----------------------------------------------------------------------
| | |
| PIC S9(n) USAGE DISPLAY | Exact type is not available. |
| | Declare it as a BYTE ARRAY |
| | in the SPL subprogram. |
| | |
-----------------------------------------------------------------------
| | |
| PIC S9(n) USAGE COMP-3 | Exact type is not available. |
| | Declare it as a BYTE ARRAY |
| | in the SPL subprogram. |
| | |
-----------------------------------------------------------------------
(1) For best results, use the largest value in the range.
Writing Switch Stubs.
The SPL compiler runs only in Compatibility Mode, while the COBOL
compiler runs in both Compatibility Mode and Native Mode. If your Native
Mode COBOL program calls a Compatibility Mode SPL subprogram, then you
must write a switch stub to switch from one mode to the other and pass
parameters. The steps are:
1. Write the SPL and COBOL programs.
2. Use SWAT (Switch Assist Tool) to generate a Pascal switch stub.
See "Switch Stubs" for more information.
3. Compile the SPL program.
4. Using the segmenter, put the SPL program USL into an SL.
5. Compile the COBOL program.
6. Compile the switch stub using the HP Pascal/XL compiler.
7. Link the COBOL program and the switch stub.
8. Execute the COBOL program.
NOTE When a Native Mode program calls a Compatibility Mode program, the
Compatibility Mode program must be in an SL. When a Compatibility
Mode program calls a Native Mode program, the Native Mode program
must be in an executable library.
Example.
The following illustrates the steps for a Native Mode COBOL program to
call a Compatibility Mode SPL program.
Step 1.
Write the SPL program:
$CONTROL SUBPROGRAM
BEGIN
<<*****************************************************************>>
<< CASCII >>
<< Convert a number in base 2,8,10,16 to ascii string for double >>
<< Parms: DINT is DOUBLE integer to convert (VALUE) >>
<< BASE is INTEGER one of 2,8,10,16 (VALUE) >>
<< STRING is BYTE ARRAY to convert into (REFERENCE) >>
<< returns: NUMCHARS INTEGER is number of characters in string >>
<<*****************************************************************>>
INTEGER PROCEDURE cascii( dint, base, string );
VALUE dint,base;
DOUBLE dint;
INTEGER base;
BYTE ARRAY string;
BEGIN
INTEGER i;
LOGICAL lint = dint + 1; << for bit extraction >>
BYTE ARRAY hexstring(0:15);
INTRINSIC dascii;
IF base = 8 OR base = 10 THEN BEGIN
cascii := dascii( dint, base, string );
IF base = 8 THEN cascii := 11;
END
ELSE IF base = 16 THEN BEGIN
MOVE hexstring := "0123456789ABCDEF";
FOR i := 7 STEP -1 UNTIL 0 DO BEGIN
string(i):=hexstring(lint.(12:4));
dint := dint & DLSR(4);
END;
cascii := 8; << always hex string length >>
END
ELSE IF base = 2 THEN BEGIN
FOR i := 31 STEP -1 UNTIL 0 DO BEGIN[REV BEG]
IF lint.(15:1) THEN string(i) := "1"
ELSE string(i) := "0";[REV END]
dint := dint & DLSR(1);
END;
cascii := 32;
END
ELSE cascii := 0;
END; << cascii >>
END.
Step 1 Continued.
Write the COBOL program:
001000 ID DIVISION.
002000 PROGRAM-ID. CALLSPL.
003000
004000 DATA DIVISION.
005000 WORKING-STORAGE SECTION.
006000 01 INTEGER PIC S9(9) BINARY SYNC.
007000 01 BASE PIC S9(4) BINARY SYNC.
008000 01 STRING-VALUE PIC X(32) VALUE SPACES.
009000 01 LEN PIC S9(4) BINARY.
010000 PROCEDURE DIVISION.
011000 0001-TEST.
012000 MOVE 123 TO INTEGER.
013000 MOVE 2 TO BASE.
014000 CALL "CASCII" USING \INTEGER\ \BASE\ @STRING-VALUE
015000 GIVING LEN.
016000 DISPLAY STRING-VALUE.
Step 2.
Use SWAT to generate the switch stub:
To invoke SWAT, type the following command at the MPE XL prompt:
:SWAT
Screen 1.
The first screen is the FILE screen. Type in the name of the file where
you want the switch stub to go. In this case the file name is SWCASCII.
Then press the Enter key.
____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool FILE |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| |
| |
| [SWCASCII] FILENAME |
| |
| |
| |
| SCRIPT PROCESSING ERRORS |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| GOTO ENTER REFRESH NEXT HELP EXIT |
| MAIN MODE SCREEN |
____________________________________________________________________________________
Figure 4-2. The FILE Screen
Screen 2.
The next screen is the MAIN screen. Here you specify the name of the
Compatibility Mode procedure and its parameters. Here these are cascii,
dint, base, and string, respectively.
____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool MAIN |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| [swcascii] NAME OF FILE TO HOLD GENERATED SOURCE CODE |
| [cascii ] NAME OF TARGET CM PROCEDURE |
| |
| P #1 [dint ] #2 [base ] |
| A [string ] [ ] |
| R [ ] [ ] |
| A [ ] [ ] |
| M [ ] [ ] |
| A [ ] [ ] |
| T [ ] [ ] |
| E [ ] [ ] |
| R [ ] [ ] |
| [ ] [ ] |
| N [ ] [ ] |
| A [ ] [ ] |
| M [ ] [ ] |
| E [ ] [ ] |
| S [ ] [ ] |
| #31 [ ] #32 [ ] |
| |
| |
| GOTO GOTO ENTER REFRESH NEXT HELP EXIT |
| FILFORM COMMIT MODE SCREEN |
____________________________________________________________________________________
Figure 4-3. The MAIN Screen
Screen 3.
The next screen is the PROCINFO screen. Here you specify information
about the Compatibility Mode procedure.
____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool PROCINFO |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| [cascii ] NAME OF TARGET ROUTINE |
| |
| LOCATION OF TARGET PROCEDURE RETURN CONDITION CODE |
| [x] GROUP SL [ ] YES, RETURN CONDITION CODE |
| [ ] PUB SL [x] NO, DO NOT RETURN CODE |
| [ ] SYSTEM SL |
| |
| FUNCTION RETURN TYPE |
| [ ] NONE |
| [ ] BYTE |
| [x] INTEGER |
| [ ] LOGICAL |
| [ ] DOUBLE |
| [ ] REAL |
| [ ] LONG |
| |
| |
| GOTO GOTO ENTER REFRESH PREV NEXT HELP EXIT |
| MAIN COMMIT MODE SCREEN |
____________________________________________________________________________________
Figure 4-4. The PROCINFO Screen
Screen 4.
The next three screens are the PARMINFO screens where you specify
information about each of the parameters of the Compatibility Mode
procedure.
____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool PARMINFO |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| [DINT ] PARAMETER NAME |
| |
| ADDRESSING METHOD I/O TYPE |
| [ ] REFERENCE [x] INPUT ONLY |
| [x] VALUE [ ] OUTPUT ONLY |
| [ ] INPUT/OUTPUT |
| |
| DATA TYPE ARRAY SPECIFICATION |
| [ ] BYTE [x] NOT AN ARRAY |
| [ ] INTEGER [ ] AN ARRAY |
| [ ] LOGICAL |
| [x] DOUBLE |
| [ ] REAL |
| [ ] LONG |
| |
| |
| GOTO GOTO ENTER REFRESH PREV NEXT HELP EXIT |
| MAIN COMMIT MODE SCREEN |
____________________________________________________________________________________
Figure 4-5. The PARMINFO Screen for Parameter DINT
Screen 5.
____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool PARMINFO |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| [BASE ] PARAMETER NAME |
| |
| ADDRESSING METHOD I/O TYPE |
| [ ] REFERENCE [x] INPUT ONLY |
| [x] VALUE [ ] OUTPUT ONLY |
| [ ] INPUT/OUTPUT |
| |
| DATA TYPE ARRAY SPECIFICATION |
| [ ] BYTE [x] NOT AN ARRAY |
| [x] INTEGER [ ] AN ARRAY |
| [ ] LOGICAL |
| [ ] DOUBLE |
| [ ] REAL |
| [ ] LONG |
| |
| |
| GOTO GOTO ENTER REFRESH PREV NEXT HELP EXIT |
| MAIN COMMIT MODE SCREEN |
____________________________________________________________________________________
Figure 4-6. The PARMINFO Screen for Parameter BASE
Screen 6.
____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool PARMINFO |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| [STRING ] PARAMETER NAME |
| |
| ADDRESSING METHOD I/O TYPE |
| [x] REFERENCE [ ] INPUT ONLY |
| [ ] VALUE [ ] OUTPUT ONLY |
| [x] INPUT/OUTPUT |
| |
| DATA TYPE ARRAY SPECIFICATION |
| [x] BYTE [ ] NOT AN ARRAY |
| [ ] INTEGER [x] AN ARRAY |
| [ ] LOGICAL |
| [ ] DOUBLE |
| [ ] REAL |
| [ ] LONG |
| |
| |
| GOTO GOTO ENTER REFRESH PREV NEXT HELP EXIT |
| MAIN COMMIT MODE SCREEN |
____________________________________________________________________________________
Figure 4-7. The PARMINFO Screen for Parameter STRING
Screen 7.
The next screen is the ARRAYLEN screen where you specify information
about the array parameter STRING.
____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool ARRAYLEN |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| [STRING ] PARAMETER NAME |
| |
| LENGTH OF ARRAY |
| [32 ] CONSTANT VALUE |
| [ ] NAME OF PARAMETER CONTAINING LENGTH |
| |
| ARRAY LENGTH USAGE |
| [x] NUMBER OF ELEMENTS |
| [ ] NUMBER OF BYTES |
| [ ] NEGATIVE = BYTES / POSITIVE = ELEMENTS |
| |
| |
| |
| |
| |
| GOTO GOTO ENTER REFRESH PREV NEXT HELP EXIT |
| MAIN COMMIT MODE SCREEN |
____________________________________________________________________________________
Figure 4-8. The ARRAYLEN Screen for Parameter STRING
Screen 8.
The final screen is the COMMIT screen where you start the code generation
process.
_____________________________________________________________________________________
| |
| HP30363A.01.00 Switch Assist Tool COMMIT |
| COPYRIGHT (C) HEWLETT-PACKARD 1986. ALL RIGHTS RESERVED. |
| |
| Press F2 when ready to begin generating code. |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| GOTO GENERATE ENTER REFRESH PREV HELP EXIT |
| MAIN SOURCE MODE SCREEN |
_____________________________________________________________________________________
Figure 4-9. The COMMIT Screen
When you press softkey F2, the SWAT tool starts generating code and
displays status messages. When SWAT is finished, it displays the FILE
screen again. Press softkey F8 to exit.
This is the switch stub generated:
$check_actual_parm 0$
$check_formal_parm 0$
$os 'MPE/XL'$
$standard_level 'ext_modcal'$
$tables off$
$code_offsets off$
$xref off$
$type_coercion 'representation'$
{******************************************************}
{* *}
{* Generated: THU, OCT 8, 1987, 5:46 PM *}
{* *}
{* Switch Assist Tool HP30363A.00.00 *}
{* *}
{******************************************************}
PROGRAM Hp__stub_outer_block(input, output);
CONST
Hp__Pidt_Known = 0; { By number }
Hp__Pidt_Name = 1; { By name }
Hp__Pidt_Plabel = 2; { By PLABEL }
Hp__System_Sl = 0;
Hp__Logon_Pub_Sl = 1; { Logon PUB SL }
Hp__Logon_Group_Sl = 2; { Logon GROUP SL }
Hp__Pub_Sl = 3; { Program's PUB SL }
Hp__Group_Sl = 4; { Program's GROUP SL }
Hp__Method_Normal = 0; { Switch copy mode }
Hp__Method_Split = 1;
Hp__Method_No_Copy = 2;
Hp__Parm_Value = 0; { value parameter }
Hp__Parm_Word_Ref = 1; { reference parm, word addr }
Hp__Parm_Byte_Ref = 2; { reference parm, byte addr }
Hp__Ccg = 0; { condition code greater (>) }
Hp__Ccl = 1; { condition code less (<) }
Hp__Cce = 2; { condition code equal (=) }
Hp__All_Ok = 0; { Used in status check }
TYPE
Hp__BIT8 = 0..255;
Hp__BIT16 = 0..65535;
Hp__BIT8_A1 = $ALIGNMENT 1$ Hp__BIT8;
Hp__BIT16_A1 = $ALIGNMENT 1$ Hp__BIT16;
Hp__CM_PROC_NAME = PACKED ARRAY [1..16] OF CHAR;
Hp__GENERIC_BUFFER = PACKED ARRAY [1..65535] OF CHAR;
Hp__SCM_PROCEDURE =
PACKED RECORD
CASE Hp__p_proc_id_type : Hp__BIT8 OF
Hp__Pidt_Known:
(Hp__p_fill : Hp__BIT8_A1;
Hp__p_proc_id : Hp__BIT16_A1);
Hp__Pidt_Name:
(Hp__p_lib : Hp__BIT8_A1;
Hp__p_proc_name : Hp__CM_PROC_NAME);
Hp__Pidt_Plabel:
(Hp__p_plabel : Hp__BIT16_A1);
END; { record }
Hp__SCM_IO_TYPE = SET OF (Hp__input, Hp__output);
Hp__PARM_DESC =
PACKED RECORD
Hp__pd_parmptr : GLOBALANYPTR;
Hp__pd_parmlen : Hp__BIT16;
Hp__pd_parm_type : Hp__BIT16;
Hp__pd_io_type : Hp__SCM_IO_TYPE;
END;
Hp__SCM_PARM_DESC_ARRAY = ARRAY [0..31] OF Hp__PARM_DESC;
HP__STATUS_TYPE =
RECORD
CASE INTEGER OF
0:
(Hp__all : INTEGER);
1:
(Hp__info : SHORTINT;
Hp__subsys : SHORTINT);
END; { record }
{ Declare all types which can be passed to this stub }
{ so that 16 bit alignments are allowed. }
HP__SHORTINT = $ALIGNMENT 2$ SHORTINT;
HP__INTEGER = $ALIGNMENT 2$ INTEGER;
HP__REAL = $ALIGNMENT 2$ REAL;
HP__LONG = $ALIGNMENT 2$ LONGREAL;
HP__CHAR = $ALIGNMENT 1$ CHAR;
PROCEDURE HPSWITCHTOCM;
INTRINSIC;
PROCEDURE HPSETCCODE;
INTRINSIC;
PROCEDURE QUIT;
INTRINSIC;
{ End of OUTER BLOCK GLOBAL declarations }
$PAGE$
FUNCTION CASCII $ALIAS 'CASCII'$
(
DINT : HP__INTEGER;
BASE : HP__SHORTINT;
ANYVAR STRING : Hp__GENERIC_BUFFER
) : HP__SHORTINT
OPTION UNCHECKABLE_ANYVAR;
VAR
Hp__proc : Hp__SCM_PROCEDURE;
Hp__parms : Hp__SCM_PARM_DESC_ARRAY;
Hp__method : INTEGER;
Hp__nparms : INTEGER;
Hp__funclen : INTEGER;
Hp__funcptr : INTEGER;
Hp__byte_len_of_parm : Hp__BIT16;
Hp__cond_code : SHORTINT;
Hp__status : HP__STATUS_TYPE;
VAR Hp__retval : HP__SHORTINT;
VAR Hp__loc_DINT : HP__INTEGER;
VAR Hp__loc_BASE : HP__SHORTINT;
begin { STUB procedure CASCII }
{******************************************************}
{* *}
{* Generated: THU, OCT 8, 1987, 5:46 PM *}
{* *}
{* Switch Assist Tool HP30363A.00.00 *}
{* *}
{******************************************************}
{ Initialization }
{ Setup procedure information--name, lib, etc. }
Hp__proc.Hp__p_proc_id_type := Hp__Pidt_Name; { By name }
Hp__proc.Hp__p_lib := Hp__Group_Sl;
Hp__proc.Hp__p_proc_name := 'CASCII ';
{ Setup misc. variables }
Hp__method := Hp__Method_Normal;
Hp__nparms := 3;
{ Setup length/pointers for functional return if this }
{ is a FUNCTION. Set length to zero, pointer to NIL }
{ if this is not a FUNCTION. }
Hp__funclen := SIZEOF(Hp__retval);
Hp__funcptr := INTEGER(LOCALANYPTR(ADDR(Hp__retval)));
{ Make a local copy of all VALUE parameters }
Hp__loc_DINT := DINT;
Hp__loc_BASE := BASE;
{ Build parameter descriptor array to describe each }
{ parameter. }
{ DINT -- Input Only by VALUE }
Hp__byte_len_of_parm := 4;
Hp__parms[0].Hp__pd_parmptr :=
ADDR(Hp__loc_DINT);
Hp__parms[0].Hp__pd_parmlen := Hp__byte_len_of_parm;
Hp__parms[0].Hp__pd_parm_type := Hp__Parm_Value;
Hp__parms[0].Hp__pd_io_type := [Hp__input];
{ BASE -- Input Only by VALUE }
Hp__byte_len_of_parm := 2;
Hp__parms[1].Hp__pd_parmptr :=
ADDR(Hp__loc_BASE);
Hp__parms[1].Hp__pd_parmlen := Hp__byte_len_of_parm;
Hp__parms[1].Hp__pd_parm_type := Hp__Parm_Value;
Hp__parms[1].Hp__pd_io_type := [Hp__input];
{ STRING -- Input/Output by REFERENCE }
Hp__byte_len_of_parm := 32;
Hp__parms[2].Hp__pd_parmptr :=
ADDR(STRING);
Hp__parms[2].Hp__pd_parmlen := Hp__byte_len_of_parm;
Hp__parms[2].Hp__pd_parm_type := Hp__Parm_Byte_Ref;
Hp__parms[2].Hp__pd_io_type := [Hp__input, Hp__output];
{ Do the actual SWITCH call }
HPSWITCHTOCM(Hp__proc, { Procedure info }
Hp__method, { Switch copy method }
Hp__nparms, { Number of parameters }
Hp__parms, { Parm descriptor array }
Hp__funclen, { func ret value length }
Hp__funcptr, { Addr of func return }
Hp__cond_code, { cond. code return }
Hp__status); { SWITCH status code }
if (Hp__status.Hp__all
Hp__all_ok) then
BEGIN { SWITCH subsystem error }
QUIT(Hp__status.Hp__info);
END; { SWITCH subsystem error }
CASCII := Hp__retval;
end; { STUB procedure }
BEGIN { Program Outer block code }
END. { Program Outer block code }
Step 3.
Compile the SPL program.
:spl cascii,casciio,$null
Step 4.
Using the segmenter, put the SPL program USL in an SL:
:segmenter
HP32050A.02.00 SEGMENTER/3000 (C) HEWLETT-PACKARD CO 1985
-buildsl sl,300,1
-usl casciio
-listusl
USL FILE CASCIIO.PUBS.COBOL74
SEG'
CASCII 152 P A C N R
FILE SIZE 144000( 620. 0)
DIR. USED 235( 1. 35) INFO USED 161( 0.161)
DIR. GARB. 0( 0. 0) INFO GARB. 0( 0. 0)
DIR. AVAIL. 14143( 60.143) INFO AVAIL. 127217( 535. 17)
-addsl seg'
-listsl
SL FILE SL.PUBS.COBOL74
SEGMENT 0 SEG' LENGTH 160
ENTRY POINTS CHECK CAL STT ADR
CASCII 0 C 1 0
EXTERNALS CHECK STT SEG
DASCII 0 2 ?
1
USED 1600( 7. 0) AVAILABLE 111200( 445. 0)
-exit
END OF SUBSYSTEM
Step 5.
Compile the COBOL and switch stub programs:
:cob85xl callspl,callsplo,$null
:pasxl swcascii,swcascio,$null
Step 6.
Link the COBOL program and the switch stub:
:link from=callsplo,swcascio;to=callsplp
Step 7.
Execute the COBOL program:
:run callsplp
MPE/iX 5.0 Documentation