Avoiding Pitfalls in Multi-Language Programming Page 1 of 14 Jazz home > Papers & Training Avoiding pitfalls in multilanguage programming » Return to original page by James Overman Sue Meloy Walter Murray Jim Scaccia Don Jenkins Language Team members in the Software Technology Lab of the Support Technology Center of the Worldwide Customer Support Organization of: Hewlett-Packard Company 8000 Foothills Boulevard Roseville, CA 95747-5613 (916) 785-5672 This paper is a review of the features involved in p
Avoiding Pitfalls in Multi-Language Programming Page 2 of 14 Debugging Tips POSIX Environment This paper will not address the issues of interfacing with the older compatibility mode languages and data types. That it is possible at all to intermix routines from multiple languages is due to the HP Precision Architecture Procedure Calling Convention as described in the Procedure Calling Conventions Manual, which is listed in the Bibliography.
Avoiding Pitfalls in Multi-Language Programming Page 3 of 14 Longint NA S9(18)COMP NA NA I(18) Longreal REAL*8 NA double REAL R(7) #1 PAC of n CHARACTER*n PIC X(n) char [n] x$ X(n) #2 String CHARACTER*(*) NA char [n] x$ X(n) #2 Real REAL*4 NA float SHORT REAL R(6) #1 Shortint INTEGER*2 S9(4) COMP short SHORT INTEGER I(4) NOTES: #1 Transact also has a type E (Real Scientific Notation) that is the same as REAL in storage. Fortran has a REAL*16 that has no other language equivalents.
Avoiding Pitfalls in Multi-Language Programming Page 4 of 14 Subranges 0..255 ~BYTE NA unsigned char NA NA 0..65535 ~INTEGER*2 ~COMP 9(4) unsigned short ~SHORT INTEGER K(4) #3 NOTES: #3 Integers may hold unsigned integer values with the first bit being interpreted as a sign rather than the larger unsigned magnitudes. Transact has 12-byte integer types with no equivalents in other languages. #4 COMPLEX storage equivalent is two real numbers in a record/structure or two-element array.
Avoiding Pitfalls in Multi-Language Programming Page 5 of 14 Use parameters to pass shared data rather than global data items. Extensible parameter lists should be avoided, when possible. System Intrinsics (as opposed to language intrinsics) should always be externally defined via the automatic language specification that uses the SYSINTR.PUB.SYS intrinsic specification file. Details: Procedure names (except intrinsics) are downshifted by default for all languages except C (which uses mixed-case names).
Avoiding Pitfalls in Multi-Language Programming Page 6 of 14 and other information. Fortran uses hidden parameters for assumed-size arrays and for extensible parameters lists. Pascal uses hidden parameters for ANYVAR, generic strings, multi-dimensional arrays, and extensible parameter lists. In Pascal, use of the language specifier FTN77 on the EXTERNAL directive will automatically provide the hidden array size for Fortran subroutine calls. RPG programs may not be compiled as subroutines.
Avoiding Pitfalls in Multi-Language Programming Page 7 of 14 other language. In the called routine, declare the data as a record/structure with data items that correspond to those for the Fortran or Basic common block. Compilation Options General: Frequently, we forget to use the simple compiler options available that provide very useful information for program debugging. TABLE or MAP options can provide symbol lists with type, size, and alignment information.
Avoiding Pitfalls in Multi-Language Programming Page 8 of 14 Different languages have different requirements for parameter type checking. The linker PARMCHECK option can be used to relax the type checking done. Shared globals With MPE/iX 5.0, global data symbols can now be visible from an executable library (XL). This allows sharing data between a program file and XLs, but beware that these symbols could now conflict with definitions in the program or in other XLs.
Avoiding Pitfalls in Multi-Language Programming Page 9 of 14 The Basic BRK function can be used to reset Basic traps if trap handling has been changed by a foreign routine or by explicit calls to the trap intrinsics. HALT is simulated in Basic by checking for control-y being pressed twice within a short time period. In compiled code, the check for the HALT condition is done at the end of each statement and within certain Basic library routines.
Avoiding Pitfalls in Multi-Language Programming Page 10 of 14 If a Pascal routine is called from a foreign outer block, the input and/or output standard files must be opened in the Pascal routine with the reset and rewrite functions. If a Pascal file number is passed to a foreign routine, the eof function can be used, upon return, to reestablish the file position, reflecting any changes made to the file while not under control of Pascal.
Avoiding Pitfalls in Multi-Language Programming Page 11 of 14 Turn on range and overflow checking in languages that support it. For languages that support level 2 optimization, the optimizer can sometimes detect uninitialized variables and give a warning. C, Cobol, Fortran and Pascal support the XDB and Toolset symbolic debuggers. Use compiler options to print code offsets and symbol maps for assembly-level debugging.
Avoiding Pitfalls in Multi-Language Programming Page 12 of 14 these run in block mode, you must redirect I/O to a hardwired terminal before running the program. To redirect I/O for VPLUS applications, get the file name used for the terminal (eg., the RPG program F-spec defining the workstation). File equate this name to the LDEV number of the hardwired terminal. For RSI applications, the name RSIIO must be file equated to the hardwired terminal LDEV.
Avoiding Pitfalls in Multi-Language Programming Page 13 of 14 General Information: Data Types Conversion Programmer's P/N 32650-90015 Oct 1989 Guide Communicator 3000 MPE/iX P/N 30216-90124 Jan 1995 Compiler Library/XL Reference Manual P/N 32650-90029 Oct1988 Chapter 3: describes procedures for converting numeric data of various types,including floating-point. Chapter 4: describes procedures for manipulating packed- decimal data in languages that do not support that data type. General Release 5.
Avoiding Pitfalls in Multi-Language Programming Page 14 of 14 Cobol II/iX: HP COBOL II/XL Reference Manual P/N 31500-90001 Jul 1991 Chapter 7: describes data representation. See especially the description of the SYNCHRONIZED clause and the USAGE clause. Chapter 11: documents the mechanics of procedure calls. Appendix B: describes the various compiler options. Appendix H: contains much useful information for the Cobol programmer making calls to and from other languages.