HP Pascal/iX [ HP FORTRAN 77/iX Programmer's Guide ] MPE/iX 5.0 Documentation
HP FORTRAN 77/iX Programmer's Guide
HP Pascal/iX
HP Pascal/iX is the ANSI standard version of Pascal for the HP 3000
Series 900 computer.
An HP Pascal/iX procedure or function can be called from an HP FORTRAN
77/iX program and an HP FORTRAN 77/iX program can call an HP Pascal/iX
procedure or function if the data types of the parameters match (see
Table 8-1 ). The language code of the ALIAS compiler directive should
be used for correctly passing parameters.
Table 8-1. HP FORTRAN 77/iX and HP Pascal/iX Types
-------------------------------------------------------------------------
| | |
| HP FORTRAN 77/iX Type | HP Pascal/iX Type |
| | |
-------------------------------------------------------------------------
| | |
| INTEGER*2 | SHORTINT |
| | Integer subrange in the range |
| | -32768 to +32767 |
| | |
-------------------------------------------------------------------------
| | |
| INTEGER*4 | INTEGER |
| | Integer subrange in the range |
| | -2147483648 to +2147483647 |
| | |
-------------------------------------------------------------------------
| | |
| REAL*4 | REAL |
| | |
-------------------------------------------------------------------------
| | |
| REAL*8 | LONGREAL |
| | |
-------------------------------------------------------------------------
| | |
| CHARACTER*1 | CHAR |
| | |
-------------------------------------------------------------------------
| | |
| CHARACTER*n | PACKED ARRAY [1..n] OF CHAR |
| | |
-------------------------------------------------------------------------
| | |
| LOGICAL*1 (BYTE) | Integer subrange in the range |
| | -128 to +127 |
| | |
-------------------------------------------------------------------------
| | |
| LOGICAL*2 | Integer subrange in the range |
| | -32768 to +32767 |
| | SET (1 word) |
| | |
-------------------------------------------------------------------------
| | |
| LOGICAL*4 | Integer subrange in the range |
| | -2147483648 to +2147483647 |
| | SET (2 words) |
| | |
-------------------------------------------------------------------------
| | |
| COMPLEX*8 | RECORD |
| | real_part : REAL; |
| | imag_part : REAL; |
| | END; |
| | |
-------------------------------------------------------------------------
| | |
| COMPLEX*16 | RECORD |
| | real_part : LONGREAL; |
| | imag_part : LONGREAL; |
| | END; |
| | |
-------------------------------------------------------------------------
Calling HP Pascal/iX from HP FORTRAN 77/iX
HP FORTRAN 77/iX cannot pass arrays by value, so you cannot call an HP
Pascal/iX routine with a value parameter of a type corresponding to an HP
FORTRAN 77/iX array type. You must use the %VAL parameter of the ALIAS
compiler directive for other types of HP Pascal/iX value parameters.
All data transferred between HP FORTRAN 77/iX and HP Pascal/iX must be
passed through parameter lists because HP FORTRAN 77/iX cannot specify
global variables and HP Pascal/iX cannot specify common blocks. The
calling HP FORTRAN 77/iX program can have a common area, but the external
HP Pascal/iX procedure or function cannot access this common area.
Parameter checking should be turned off because HP Pascal/iX generates
different type check values from HP FORTRAN 77/iX values. To turn off
the checking, specify $CHECK_ACTUAL_PARM 0$ in the HP FORTRAN 77/iX
program, or specify $CHECK_FORMAL_PARM 0$ in the HP Pascal/iX procedure.
HP FORTRAN 77/iX program that calls an HP Pascal/iX procedure:
PROGRAM call_pascal
c Calling an HP Pascal/iX procedure
$ALIAS pasprog PASCAL(%REF)
CHARACTER str*30
str='Pass this string'
CALL pasprog(str)
PRINT *,str
END
External HP Pascal/iX procedure:
$SUBPROGRAM$
PROGRAM pascal;
TYPE charstr = PACKED ARRAY[1..30] OF CHAR;
{ Turn parameter checking off because HP Pascal/iX generates different
parameter type check values than HP FORTRAN 77/iX. }
$CHECK_FORMAL_PARM 0$
PROCEDURE pasprog(VAR str:charstr);
VAR output : TEXT;
BEGIN
{ Open OUTPUT so we can display the string to verify that
it was passed correctly }
REWRITE(output,'$STDLIST');
WRITELN(output,str);
{ Add to the string }
strmove(strlen(' back again'),' back again',1,str,17);
END;
BEGIN
END.
Calling HP FORTRAN 77/iX from HP Pascal/iX
An HP FORTRAN 77/iX subroutine or function can be called from an HP
Pascal/iX program if the data types of the parameters match (see Table
8-1 ). However, be careful when passing character strings. HP
FORTRAN 77/iX expects an additional word that describes the maximum
length of the string, while PAC's (packed array of char) in Pascal do
not. When an HP Pascal/iX character string is passed to HP FORTRAN
77/iX, the compiler expects the string to be passed by reference (the
address of the string) and then expects the maximum length of the string
to be passed by value. If the HP FORTRAN 77/iX routine is declared
EXTERNAL FTN77 in the HP Pascal/iX program, the length is automatically
passed as HP FORTRAN 77/iX expects it.
HP Pascal/iX cannot access an HP FORTRAN 77/iX common area and cannot
pass a file or a label to an external HP FORTRAN 77/iX routine.
The following example shows how to pass character strings between HP
Pascal/iX and HP FORTRAN 77/iX.
HP Pascal/iX program that calls an HP FORTRAN 77/iX subroutine:
PROGRAM callfort(OUTPUT);
CONST str_stuff='Pass this string to FORTRAN 77';
TYPE pac = PACKED ARRAY[1..50] OF CHAR;
VAR str : pac;
cur_len:integer;
{ Declare the external HP FORTRAN 77/iX program as EXTERNAL FTN77 so the
PAC is passed correctly and so compatible data type information is
generated for the Link Editor. Two parameters are passed: the
the PAC by reference (or the address of the string) and a one-
word integer by reference, which is the current length of the PAC.
HP Pascal/iX passes the maximum length of str (50 in this example)
by value between these two arguments to satisfy HP FORTRAN 77/iX
requirements for passing character data. }
PROCEDURE fortprog(VAR str:pac;
VAR cur_len:integer);
EXTERNAL FTN77;
BEGIN
str:=str_stuff;
{ Get the current length of the PAC }
cur_len:=strlen(str_stuff);
WRITELN(str);
{ Call the HP FORTRAN 77/iX subroutine and pass the PAC
and the current length of the PAC }
fortprog(str,cur_len);
{ Do a linefeed to print the concatenated string on the following line}
WRITELN;
WRITELN(str);
END.
HP FORTRAN 77/iX subroutine:
SUBROUTINE fortprog(str,cur_len)
c The formal parameters are the character string and the current
c length of the string; the maximum length of the character
c string is a hidden parameter that HP FORTRAN 77/iX uses.
IMPLICIT NONE
INTEGER*4 cur_len
c Use maximum length (the 2nd actual parameter) as the character length:
CHARACTER str*(*)
c Concatenate the strings and print result
str = str(1:cur_len) // ' and then back again'
PRINT *,str
RETURN
END
MPE/iX 5.0 Documentation