vax fortran to fortran 77 translator

15
VAX Fortran to Fortran 77 translator RICHARD E. HESSEL and STEPHEN B. CHICO Mechanical and Industrial Engineering Department, Clarkson University, Potsdam, NY 136 76, USA A Fortran preprocessor is described which maps VAX Fortran into standard Fortran 77. Supported extensions include long variable names, DO WHILE loops, ENDDO loop terminations, Vax Fortran tab convention, INCLUDE f'de processing, and a MODULE facility to limit the access of external programs to subprogram and common block names. The software is available in 'standard' Pascal and Software Tools Pascal form. INTRODUCTION The Fortran language is much maligned, especially by those in computer science circles, for its deficiencies compared to more modern programming languages. ~'~ We agree with these criticisms. However, as a practical matter almost all engineering software is written in Fortran. The extensive libraries of high quality mathematical software alone are a great incentive to use Fortran in our computations. 3 While Fortran 77 made a significant step in improving the language, Fortran still suffers from many serious flaws. The next version of the language, Fortran 8x, should remove most of these flaws. 4 In the mean time we are faced with a situation similar to that of the 1970's when many compiler writers supplemented Fortran IV with extensions to overcome its deficiencies. Several computer vendors, for example DEC and Gould, have extended their Fortran 77 compilers. The DEC VAX Fortran is a particularly attractive version of Fortran 77. 5 The extensions it supports include long variable names, end of line comments, a general DO-WHILE loop, and an ENDDO statement to eliminate the need for statement numbers as the objects of DO loops. Also included is an IMPLICIT NONE statement which requires the type of every variable to be explicitly declared. Experience with this compiler has shown that use of these extensions, especially the long variable names, result in ~nuch more readable programs. However, such programs suffer from lack of portability. In the spirit of the multitude of Fortran IV preproces- sors, 6'7 we combined some of our old programs for detecting long variable names and translating DO-WHILE loops to produce input for the macro processor from Software Tools in Pascal by Kernighan and Plaguer a to create a new translator which maps VAX Fortran into Fortran 77. The features of this translator include : Long names: The program assumes that IMPLICIT NONE has been used (or at least that all variable names that are six characters or longer have been declared in type statements). The program will then attempt to truncate Accepted January 1985. Discussion closes September 1985 names which are longer than six characters to a readable six character name. If the name cannot be shortened without conflict then a unique name is generated. DO loops: DO-WHILE loops of the form: DO WHILE (condition) ENDDO are translated into appropriate IF's and GOTO's. Conven- tional DO loops which are terminated with ENDDO's instead of a line with a statement number are translated into the legal Fortran 77 form with statement numbers. End of line comments: Any text which appears between an exclamation point (!) which is not in a quoted string and the end of the line is considered to be a comment. These comments are moved to the line preceding the current line as standard Fortran comments. The program understands Fortran continuation lines. Include statements: The source file may contain 'C$INCLUDE file' statements which are replaced by the contents of the file before any other processing is done. These statements may be nested, i.e. the included file may contain other include statements. Include statements are used to build source files comprised of many routines in separate files. Common block declarations can be stored in a file and included when needed to avoid typing errors. Modules: Fortran 77 supports only one level of global name. This makes it difficult to hide implementation details from users of library routines. Using this option, all global names, i.e. subprogram and common block names, are mapped into special inaccessible names except for those names which the user selects to be 'visible'. The writer of a 'module' would specify that certain routines or common blocks could be accessed by other routines outside of the module. All other global names would be transformed into a four letter module name and a two character sequence to form a unique six character name. IMPLEMENTATION OF THE TRANSLATOR The translator is implemented in Pascal. Two versions are available: one using 'standard' Pascal and one using the Pascal environment developed in ref. 8. The programs were written for portability with carefully isolated system dependent sections, e.g. opening flies. The output of the translator is fed to a general purpose macro processor to perform long variable name substitution. A suitable macro processor is 'define' from ref. 8. All of the progra~ns described in ref. 8 are available frown the publisher for a nominal charge. A 'standard' Pascal version is supplied with the translator software. The translator makes several passes over the program text. the passes are: 0141-1195/85/030142-15 $2.00 142 Adv. Eng. Software, 1985, Vol. 7, No. 3 © 1985 CML Publications

Upload: richard-e-hessel

Post on 21-Jun-2016

301 views

Category:

Documents


27 download

TRANSCRIPT

Page 1: VAX Fortran to Fortran 77 translator

VAX Fortran to Fortran 77 translator

RICHARD E. HESSEL and STEPHEN B. C H I C O

Mechanical and Industrial Engineering Department, Clarkson University, Potsdam, N Y 136 76, USA

A Fortran preprocessor is described which maps VAX Fortran into standard Fortran 77. Supported extensions include long variable names, DO WHILE loops, ENDDO loop terminations, Vax Fortran tab convention, INCLUDE f'de processing, and a MODULE facility to limit the access of external programs to subprogram and common block names. The software is available in 'standard' Pascal and Software Tools Pascal form.

INTRODUCTION

The Fortran language is much maligned, especially by those in computer science circles, for its deficiencies compared to more modern programming languages. ~'~ We agree with these criticisms. However, as a practical matter almost all engineering software is written in Fortran. The extensive libraries of high quality mathematical software alone are a great incentive to use Fortran in our computations. 3

While Fortran 77 made a significant step in improving the language, Fortran still suffers from many serious flaws. The next version of the language, Fortran 8x, should remove most of these flaws. 4 In the mean time we are faced with a situation similar to that of the 1970's when many compiler writers supplemented Fortran IV with extensions to overcome its deficiencies.

Several computer vendors, for example DEC and Gould, have extended their Fortran 77 compilers. The DEC VAX Fortran is a particularly attractive version of Fortran 77. 5 The extensions it supports include long variable names, end of line comments, a general DO-WHILE loop, and an ENDDO statement to eliminate the need for statement numbers as the objects of DO loops. Also included is an IMPLICIT NONE statement which requires the type of every variable to be explicitly declared.

Experience with this compiler has shown that use of these extensions, especially the long variable names, result in ~nuch more readable programs. However, such programs suffer from lack of portabil i ty.

In the spirit of the multi tude of Fortran IV preproces- sors, 6'7 w e combined some of our old programs for detecting long variable names and translating DO-WHILE loops to produce input for the macro processor from Software Tools in Pascal by Kernighan and Plaguer a to create a new translator which maps VAX Fortran into Fortran 77.

The features of this translator include :

Long names: The program assumes that IMPLICIT NONE has been used (or at least that all variable names that are six characters or longer have been declared in type statements). The program will then at tempt to truncate

Accepted January 1985. Discussion closes September 1985

names which are longer than six characters to a readable six character name. If the name cannot be shortened without conflict then a unique name is generated.

DO loops: DO-WHILE loops of the form:

DO WHILE (condit ion)

ENDDO

are translated into appropriate IF 's and GOTO's. Conven- tional DO loops which are terminated with ENDDO's instead of a line with a statement number are translated into the legal Fortran 77 form with statement numbers.

End of line comments: Any text which appears between an exclamation point (!) which is not in a quoted string and the end of the line is considered to be a comment. These comments are moved to the line preceding the current line as standard Fortran comments. The program understands Fortran continuation lines.

Include statements: The source file may contain 'C$INCLUDE file' statements which are replaced by the contents of the file before any other processing is done. These statements may be nested, i.e. the included file may contain other include statements. Include statements are used to build source files comprised of many routines in separate files. Common block declarations can be stored in a file and included when needed to avoid typing errors.

Modules: Fortran 77 supports only one level of global name. This makes it difficult to hide implementat ion details from users of library routines. Using this option, all global names, i.e. subprogram and common block names, are mapped into special inaccessible names except for those names which the user selects to be 'visible'.

The writer of a 'module ' would specify that certain routines or common blocks could be accessed by other routines outside of the module. All other global names would be transformed into a four letter module name and a two character sequence to form a unique six character name.

IMPLEMENTATION OF THE TRANSLATOR

The translator is implemented in Pascal. Two versions are available: one using 's tandard' Pascal and one using the Pascal environment developed in ref. 8.

The programs were written for portabil i ty with carefully isolated system dependent sections, e.g. opening flies.

The output o f the translator is fed to a general purpose macro processor to perform long variable name substitution. A suitable macro processor is 'define' from ref. 8. All of the progra~ns described in ref. 8 are available frown the publisher for a nominal charge. A 's tandard ' Pascal version is supplied with the translator software.

The translator makes several passes over the program text. the passes are:

0141-1195/85/030142-15 $2.00 142 Adv. Eng. Software, 1985, Vol. 7, No. 3 © 1985 CML Publications

Page 2: VAX Fortran to Fortran 77 translator

Pass 1 : All C$INCLUDE file statements are replaced by the contents of the named file.

Pass 2: The DO WHILE, ENDDO, and DO without a statement number are translated into IF's, CONTINUE's, and GOTO's. End of line comments are moved in this pass and the VAX Fortran tab convention is converted to blanks.

Pass 3: Long variable, subprogram, and common block names are mapped into unique names. CSMODULE and CSVISIBLE statements control the visibility of global names.

Pass 4: The define statements produced in pass 3 to drive the macro processor are merged at the beginning of the program source and are passed to the macro processor.

Command procedures are provided to illustrate how to implement the translator on VAX/VMS and Unix operating systems.

Detailed usage instructions may be found in the manual pages. Extensive prologue comments in the code aid in implementing the program on the users system.

USING THE TRANSLATOR

The module aspects of the translator are especially useful in writing large programs. The program could be broken into logical sections and written by different programmers. Each program section could access only those subprograms and common blocks of another section which had been made visible. Thus each programmer could use descriptive names for internal .subprograms and common blocks without worrying about possible conflict with other sections of the program.

Visible names should not be longer than six characters to work properly with most Fortran compilers and linkers. Other subprogram and common block names will be processed the same way as long variable names.

The translator requires that all variable names which are six characters in length or longer be explicitly declared. Six character names are needed to determine if a long name can safely be truncated to its first six characters. If it cannot then a unique six-letter name is generated. We recommend that all variable names be declared.

THE PROGRAMS

Two versions o f each program are provided. One uses the Software Tools s primatives while the other is in 'standard' Pascai. The Software Tools version has been tested on VAX/VMS. The 'standard' Pascal version has been tested on VAX/VMS and Unix. Command procedures are supplied for each of these operating systems.

A version of the define program from ref. 8 in 'standard' Pascal is included.

A prospective user can port the primatives described in ref. 8 to his or her system and use the Software Tools version and the other tools described in ref. 8. This version is especially useful to users who already are using Software Tools.

An alternative is to use the 'standard' Pascal versions. These programs should compile without modification on most Pascal compilers.

The programs include extensive prologue comments w/rich describe in detail the programs. Limitations and possible extensions are enumerated.

Sample Fortran programs are included to test the programs when they have been installed on a prospective user's computer:

Program VF2F77 - VAX Fortran to Fortran 77 translator

Usage VF2F77 infile outfile

Function VF2F77 reads VAX Fortran source code and outputs

commands for a macro processor and translated code. After being processed by a macro processor, the output is standard Fortran 77 code.

VAX DO WHILE (condi t ion) . . . ENDDO and DO index = i l , i2, i3 . . . ENDDO are translated.

Text following an unquoted exclamation point (!) is moved to the preceding line as a comment.

IMPLICIT NONE statements are changed into comments. All lower case letters not in quoted strings are mapped

into upper case. A tab character in columns 1 through 6 causes the next

character to logically be in column 7 if the character is alphabetic. If the character is a number other than zero (0) it is placed in column 6 to indicate a continuation line.

All variable names greater than or equal to six characters should be declared in type statements. A list of macro processor commands will be generated to map names longer than six characters into six character names by truncation, if possible, or by generating a unique name.

The following translator directives are supported:

C$ INCLUDE 'filename'

This line will be replaced by the contents of the file 'filename'. Include statements may be nested as deeply as desired.

CSMODULE xxxx

Marks the beginning of module xxxx. Global names (subprogram and common block names) which the user wishes to be hidden are mapped into 'hidden names' which begin with xxxx. If xxxx is no longer than four characters it will be truncated. If there is no CSMODULE directive global names will follow the same rules as variable names.

All global names are hidden unless they appear in a CSVISIBLE statement, cSVISIBLE namel [ n a m e 2 . . . ] .

The global names listed in this statement are to be unchanged by the translator. These are the global names visible to the rest of the program. As many CSVISIBLE statements as required may be used. Names on the CSVISI- BLE statement are separated by blanks, tabs, or commas.

Bugs Underscore characters (_ ) are not supported in variable

names because most macro processors do not recognize them as characters. Modifications to VF2F77 are documented if your macro processor treats them properly.

An exclamation point in a Hollerith field, e.g. 5HBUG!, will be treated as an end of line comment indicator. Hollerith fields are not officially part of Fortran 77. 9

Multiple common blocks are not allowed in the same COMMON statement. E.G. COMMON/BLK1/A,B,C/BLK2/ X,Y.

Adv. Eng. Software, 1985, Vol. 7, No. 3 143

Page 3: VAX Fortran to Fortran 77 translator

REFERENCES

1 Dijkstra, E. W. How do we tell troths that might hurt?, Selected Writings on Computing: A Personal Perspective, Springer-Verlag, New York, 1982

2 Wilson, K. G. Planning for the Future of US Scientific and Engineering Computing, CA CM 1984, 27(4)

3 IMSL Library General Information, International Mathematical and Statistical Libraries, Inc, Houston, TX, 1983

4 Smith, B. T. Status Report on Fortran 8x as of August 1983, SIGNUM Newsletter 1983, 18(4)

5 VAX Fortran Reference Manual 3.0, Digital Equipment Corpora- tion, 1983

6 Kernighan, B. W. RatJbr - A Preprocessor for a Rational Fortran, Unix Programmer's Manual, Vol. 2B, Bell Telephone Laboratories, Inc., Murray Hill, NJ, 1979

7 Cook, A. J. and Shustek, L. J. A User's Guide to Mortran 2, Stanford Linear Accelerator Center, California 94305, 1975

8 Kernighan, B. W. and Plauger, P. J. Software Tools in Pascal. Addison Wesley, 1981

9 American National Standard Programming Language FORTRAN, ANSI X3.1978

DIRECTORY OF PROGRAMS

The first two programs are used to obtain the source and destination files, and send them through the translator programs. The actual program names used in the two driver routines will have to be modified to be compatible with the environment the translator is implemented in. For example:

'USER1 : [C 100.STEVE.TRANS.STAND] DEFINE.EXE'

Programs with the .PAS extension are written in 's tandard' Pascal, those with the .SFT extention are designed to use the software tools primitives.

All the following programs read from standard input and write to standard output :

V F 2 F 7 7 . C O M - V A X / V M S command procedure used to run the translator programs.

U N I X . S C R - U n i x shell script to run the translator pro- grams.

I N C L U D E . P A S - U s e d to include external files into the main source code. Note: Pascal File 1/O is system dependent and may have to be modified, currently set up for VAX/VMS operating system.

WH2STD.PAS-Conve r t s non-standard do loops into a form compatible with standard FORTRAN 77, plus processes end of line comments, VAX tab conventions, and maps text not in quotes to upper case.

L O N G N M . P A S - Creates a list of define statements to redefine long variable names. The list should be affixed to the beginning of the output from WH2STD.PAS for use with the define program.

D E F I N E . P A S - R e a d s from standard input and replaces every occurrence of ' s t r l ' with 's tr2 ' following the define command: def ine(s t r l , str2).

The following programs perform the same functions as those above, but are designed to work in the software tools environment:

INCLUDE.SFT WH2STD.SFT LONGNM.SFT DEFINE.SFT

The next programs are used as test programs. TEST.F is the source, MATADD.SUB, and MATMULT.SUB are separate subroutines that are included with the include program:

T E S T . F - Main program that calls MATADD.SUB and MATMULT.SUB.

MATADD.SUB - Subroutine that adds two matricies together.

MATMULT.SUB - Subroutine that multiples two matricies together.

X X . O U T - T h e translated output from the three test programs.

VF2F77.COM VAX/VMS command procedure to run translator programs

$ ~ VAX/VMS comand procedure to dr,ve tile translat,~! $ ! The source code is passed through the followin~ l,rogram~ $ ! include -- includes external source files. $ I wh2std -- translates while loops $ I longnm -- processes long variable names

$ [ define -- processes the define statements generaL~,d by Iongnm $ t $ ! clear the directory of possible conflicting file:~ $ if fSsearch("temp*.txq;*") .nes. "" then $ delet!, lemp*.tKq; ~ $ ~

$ I get input and output fires $ infile =~ pl $ outfile ~= p2 $ if infile .eqs. "" then $ inquire inlile "source £~le" $ if outfile .eqs. "" then $ inquire outfile "output file" $ ~

$ ! if an output file is not mpecified then the output will $ ! go to ~tandard output and no output file will be saved $ ~

$ ! connect standard input and output to the appropriate files $ assign/user_mode "infile" sys$input [ input file spec $ as~ign/umer_mode templ.txq sys$output [ output from include $ run userl : IclO0.~teve.trans.stand] include .exe $ ~

$ assign/umer._~ode templ.txq sys$input [ output from include $ assign/u~er_mode temp2.txq sys$output [ output from wh2std $ run userl:[cl00.steve.trans.stand]wh2std.exe $ ~

$ delete te~p.~l.~txq;* $ ~ $ assign/u~er_mode temp2.txq sys$input I Output from while $ assign/user_mode temp3.txq sys$output I output from flung $ run userl : [cl00.steve.trans.stand] longnm.exe $ ~

$ I append the result of wh2std to the define table $ ~ check if there was shy output from the long name program $ ~

$ if fSsearch("temp3.txq;*") .eqs. ~'" then goto lablel $ append temp2.txq temp3.txq $ assign/user temp3.txq sys$input S goto fable2 $1ablel: $ assign/user_mode temp2.txq sys$input $1able2: $ if outfile .nes. "" then guru fable3 $ des ssign sys$output $ guru fable4 $1able3: $ assign/user "outfile" sys$output $1able4: $ run [clO0.steve.trans.stamd]define.exe $ t $ I delete the work files $ delete te~p*.txq;*

UNIX.SCR Unix shell script to run the translator programs

~ Transf77 - shell script to run the programs ~ necessary to translate VAX/V~L~ FORTRAN into # standard Fortran 77 #

# useage: tran~f77 infile.f outfile.f #

# process includes and pipe to "twhile" include <$I I twhile > txqpl #

# create list of defines in txpq2 longnm < txqpl > txqp2 #

# put list of defines on top of output from "twhile" # and pipe to the "define" program cat txqp2 txqpl I define >$2 #

~ remove temporary files rm txqpl rm txqp2

144 Adv. Eng. So f tware , 1985, Vol. 7, No. 3

Page 4: VAX Fortran to Fortran 77 translator

INCLUDE.SFT Copies external files into the main file

INCLUDE PROGRAM(aft) include -- replace c$include "file" by contents of file input is from standard input. output is to standard output. Both input and output are redirected to be the appropriate files This version is designed to run in the Software tools environment. The file l/O is isolated in "include" and "finclude"

REFERENCE Kernighan & Plauger, "Software Tools in Pascal " 198! Addison-Wesley Publishing Company, Reading, HA

( wrapper (CU) -- this is the wrapper for all the software tools { Rename this ~ile "name.pan", where name is the name of the tool. { F o r example: rename it filter.pan ( This next li~e inherits all the global definitions that go along { _ with the software tools. [inherit('userl:[bllb.softtool.environ]globdefs.env')]

program wrapped(input,output); { Include your program here. For example: ~incIude "filter.prc" )

{ include -- replace c$include "file" by contents of file }

p r o c e d u r e i n c l u d e ; v a t

incl : string; { value is "cSinclude ~

{ l o w e r - - r e t u r n "a" in l o w e r c a s e } FUNCTION lower( a : CRARACTER ) : ClinChER; { return~ ~ in lower ca~e } { a~mae~ difference between upper & lower cmse xs a constant } VAR ch : c h a r a c t e r ; Begin { l o w e r }

if a i~ [ o r d ( ' A ' ) . . o r d ( ' Z ' ) ] then c h :ffi a + ord('a') - ord('A') e l s e c h :" a ;

lower := c h ; End; {lower)

{ equal -- test two strings for equality } { modified t o e e g l e e t c a s e of t he strings ) function equal (vat strl, sir2 : string) : boolean; vat

i : integer; begin

i : - 1 ;

while ( l o w e r ( s t r l [ i ] ) = lower(str2[i])) and (strl[i] <> ENDSTR) do i := i + i;

equal :~ (lower(strl[i]) - lower(stri[i])) end;

{ finclude -- includes the file desc f }

p r o c e d u r e f~nclude ( f : f i l e d e s c ) ; vat

line, sir : string; loc, i : integer; fl : filedesc;

{ getword -- get word £rom s[i] into out ) function getword (vat s : string; i : integer;

vat out : string) : integer; vat

j : integer; begin

while (sli] in [BLANK, TAg, NEWLINE~) do i := i + i;

j :~ 1 ; while (not (s[i] in [ENDSTR,BLANK,TAB,NEWLINE])) do begin

o u t [ j ] : = s [ i ] ; i :~ i + i; j := j + 1

e n d ; o u t [ j ] := ENDSTR; if (~[i] - ENDSTR) then

getword :- 0 else

getword := i e n d ; begin

while (getline(line, f, MAXSTR)) do begin foe :~ getword(line, l, s i r ) ; if ( n o t e q u a l ( a r t , i n c l ) ) t h e n

p u t s t r ~ l i n e , STDO~T) e l s e b e g i n

l o c := g e t w o r d ( [ i n e , I o c , s i r ) ; str[length(str)] := ENDSTR; { remove quotes } for i :- I to length(sir) do

str[i] := str[i+l]; fl := mustopen(str, IOREAD); finclude(fl); closef(fl)

end end

end; begin

{ s e t s t r i n g ( i n c l , " c $ i n c l u d e ' ) ; i n c l [ l ] := o r d ( ' c ' ) ; i n c l [ 2 ] := o r d ( ' $ ' ) ; incl[31 := o r d ( ' i ' ) ; i n c l [ 4 ] := o r d ( ' n ' ) ; i n c l [ 5 ] := o r d ( ' c ' ) ; i n c l [ 6 ] := o r d ( ' l ' ) ; i n c l [ 7 ] : " o r d ( ' u ' ) ; i n c l [ 8 ] := o r d ( ' d ' ) ;

incl[gJ := ord('e'); incl[10] :" ENDSTR;

finclude(STDIN) end; begin { wrapper }

iaitio; { Call program here. For example: filter } include

end. { wrapper }

WH2STD.SFT Processes nonstandard do loops, etc.

W~I2STD PROGRAM (sft) Program Overview

This program is used to convert some of the nice features of VAX FORTRAN into a form compatible with standard FORTRAN 77

The particular features handled in this program are: DOWHILE ( c o n d i t i o n i s t r u e )

:

b l o c k o f s t a t e m e n t s :

ENDDO

DO i n d e x v a t = l o w e r , u p p e r , s t e p :

b l o c k o f s t a t e m e n t s :

ENDDO

VAX t a b c o n v e n t i o n s w h i c h i s a t a b i n t h e £ i r s t 6 c o l u m n s f o l l o w e d by a d i g i t ( I . . 9 ) i s a c o n t i n u a t i o n o f t h e p r e v i o u s l i n e . I t i s p r o c e s s e d i n t o : 5 b l a n k s , t h e d i g i t , T A R S [ Z E - 6 b l a n k s , a n d t h e t e x t

End o f l i n e c o m m e n t s a r e s i g n i f i e d by a n " ! " . The t e x t b e t w e e n t h e "~" a n d t h e e n d o f t h e l i n e i s a c o m m e n t . I t i s p r o c e s s e d i n t o a n o r m a l Comment a n d p l a c e d b e f o r e i t s l i n e o f o r i g i n

I M P L I C I T NONE s t a t e m e n t s a r e c o m m e n t e d o u t . T h i s i s f o r u s e w i t h t h e I o n g n a m e p r o g r a m .

T h e r e a r e two r u n t i m e o p t i o n s a v a i l a b l e t o t h e u s e r i m p l e m e n t e d a s comment c a r d s i n t h e s o u r c e c o d e . S p a c e s a r e n o t a l l o w e d i n t h e o p t i o n key w o r d s .

cSUPPER t r u e - - > maps a l l t e x t n o t i n q u o t e s t o u p p e r e a s e . f l a s e - - > d o e s n o t c h a n g e c a s e . D e f a u l t = t r u e .

C$DEBUG t r u e - - > o u t p u t s d i a g n o s t i c s t o s t a n d a r d o u t p u t . f a l s e - - > no d i a g n o s t i c s a r e o u t p u t . D e f a u l t ~ f a l s e .

U s e : cSUPPER f a l s e

F l o w o f t h e P r o g r a m

A b u f f e r i s f i l l e d w i t h a l l t h e t e x t n e c e s s a r y t o o b t a i n a c o m p l e t e FORTRAN s t a t e m e n t i n c l u d i n g a l l c o n t i n u e d l i n e s a n d a n y b l a n k l i n e s o r c o m m e n t s t h a t a r e i n t e r s p e r s e d i n t h e c o d e .

T h i s i s w h e r e t h e e n d o f l i n e c o m m e n t s a n d t a b c o n v e n t i o n s a r e p r o c e s s e d o u t

F r o m t h i s b u f f e r a s t r i n g " s t m t . t × t " i s o b t a i n e ~ . T h i s s t r i n g c o n t a i n s a l l t h e r e l e v a n t FORTRAN t e ~ t o f t h e e n t i r e s t a t e m e n t . This string is formed so that the procedures testing the statement do not have to know about column structure or continued lines.

If a nonstandard "DO" structure is found then the buffer is

processed (by the procedure "pr_do") as follows:

The "DO WNILE" statements are mapped into 3 lines:

IF( .NOT."

& (original "DOWRILE" argument)" -- Remains the same & )into xxxxx -- Is added to the end of the stmt.

The DO/ENDDO loops are maped into:

DO xxxxx" & ..... rest of the original "DO"

Note: The statements are broken up to prevent them from being pushed past column 72 when the additional characters are added.

Nested "DO" structures are processed recursivly.

The procedure "pr_do" repe~ts the process of getting a statement and testing it for do types until it finds an "ENDDO". If another nonstandard do structure is found while looking for the "ENDDO" "pr_do" then recursivly calls its self to process the new found do structure

When an "RNDDO" is found it is processed as follows:

When associated with a "DOkrHILE '' the keyword "ENDDO" is mapped into 2 lines:

GOTO yyyyy" "xxxxx CONTINUE"

For a DO / ENDDO loop the "ENDDO" is maped into:

"xxxxx CONTINUE"

For both cases if the "ENDDO" is labeled a continue statement with the original label is inserted before either of the two above enddo cases are processed.

Adv. Eng. Software, 1985, Vol. 7, No. 3 14$

Page 5: VAX Fortran to Fortran 77 translator

PROGKAM STRUCTURE: - - k n d e n t a t i o [ ~ : n ~ t c a t e s i e v , , J c,t n e s t k n g

PROGRAM w h 2 s t C m a i n r o u t i n e ~DN. l o w e r r e t u r n s a c h a r : I c i e s t i l l 1 ~wt t ~ t s e

I 'RO. p r v a × t a b - - R i O t , s > v a x t ~b ( ( ) n v , ' i [ 1o12 FUN. r e a l s t r u t d , t , i m l n : ~ i f s~ l i r w i ;t r e a l s t m l .

FUN. a l l b l a n k s a l ! b l a n k l a n e t r m ~ ; PRO. f l u s h b u f f e r d u m p s b u t l e r COl l t ( ' I [ s t o " d e s t l n "

PRO. c h a n g e c a s e - c h a n g e s t e x t t o c a p i t o l l e t t e l ~ P R O . p u t _ i n b u f f - p u t s a l i n e i n t h e b u f f e r

P R O . s t r i p c o m t a k e s o f f e n d o f l i n e c o m m e n t s P R O . d u m p e x c e s s - - d n m p s e x c e s s c o m m e n t s

PRO. p r o p t i o n - - p r o c e s s e s o p t i o n c o m m e n t c a r d s F U N . f i n d t r u e - - .-> t r u e i f " t r u e " l o l l o w s t i l e o p t i { ~ n

PRO. f i l l b u f f - - f i l l s b u f f w i t h e n t i r e s t a t e m e n t PRO. i s c o n t i n u e d - d e t e r m t n s i f t h e l i n e t s c o n t .

PRO. i n i t i a l i z e - - i n i t i a l i z e s s t r i n g s a n d f i l e s

PRO. g e t s t m t - - g e t s a F O R T ~ N s t a t e m e n t f r o m t h e b u f f e r . F U N . b e g i n i n g _ o f t e x t - - - > p o s o f 1 s t c D a r . o f l £ ~ e P R O . g e t _ t x t - - g e t s r e l e v a n t f o r t r a n s t m t . t e x t

PRO. p r s t :mr - p r o c e s s e s a s t a t e m e n t FUN. f i n d d o _ t y p e - - l t n d s t h e t y p e o f d o => do t y p e

F N R . ~ s ~ e n d d o - - z l s t r u t , i s a n e n d d o => t r u e F U N . i s d o w h ~ l e - - t f s t m t . i s a d o w h i l e - > ~ r u e F U N . d o . l o o p _ t y p e . . . . > do t y p e F U N . f i n d r p a r e n - - => r i g h t p a r e n t h e s i s p o s k t i o n

PRO. p r d o - - p r o c e s s e s a d o s t a t e m e n t PRO. i n s e r t - - i n s e r t s a l i n e i n t h e b u f f e r FHN. f ~ n d d o ~ o s - => b u f f e r l i n e w i t h do s t a t m e n t PRO. c b t o s i r c o n v e r t s i n t e g e r k n t o a c b r s t r i n g FUN. h a s _ a n u m b e r i f s t m t . i s l a a e l e d - > t r u e PRO. p r _ d o w h i l e - p r o c e s s e s a d o w h i l e s t a t e m e n t PRO. p r _ d o n n p r o c e s s e s a d o w i t h o u t a l a b e l P R O . p r e n d d o - - p r o c e s s e s a n e n d d o s t a t e m e n t

PRO. h l d e _ ~ m p _ n o n e - - c o m m e n t s o u t i m p l i c z t n o n e s t r u t .

* * * ~ * * * * * * * * * * NOTES : * * * * * * * * * * * *

THe p r o g r a m k n o w s n o t h i n g o f H o l o r i t h i i e l d a n d w o u l d

c o n s i d e r a n " ~ " i n s u c h a f i e l d a s a n e n d o f f i n e c o ~ e ~ t . I t w o u l d a l s o c h a n g e t h e c a s e o f l e t t e r s i n a t t o l e r t t h f o r m a t

~ f t h e c h a n g e c a s e m o d e i s a c t i w , .

An e x c l a m a t i o n m a r k ~n a q u o t e d ~ t r t n g k s x g n o r e d a s a n e n d o f

l i n e c o ~ e n t m a r k e r

S p a c e s i n t h e "DO W H I L E " a n d t h e "END DO" s t a t e m e n t a r e l e g a l . T h e w o r d s t D e m s e l v e s c a n n o t b e c o n t i n u e d , b u t t h e r e s t o f t h e s t a t e m e n t c a n b e s p l ~ t a s d e s i r e d .

O n l y s i n g l e q u o t e s m a r k a q . o t e d s t r i n g .

T h e o n l y [ i i ~ ( n o r m a l t e x t i s c h a n g e r a r o u n d i s w H e u t h e r e a~e

a l o t o f c o m m e n t s . I n o r d e r I o p r e v e n t b u l l e t o v e r f l o w t h e y a r e d u m p e d o u t s a v i n g o n l y t h e r e a l s t a t e m e n t l i n e s i n t h e b u f f e r . ( s e e p r n c e d u r e " d u m p e x ; o g s " i n " p u t i n b u l l " )

U n d e r s c o r e e s a r { ~ u s e d t h r o u g b t t b c , o d ( t o l l : tHr~vt ' r e a d k b l l k t > U n d e r s c o r e s a r e m~[ standard t a s c a l s c i f y.)u~ ( o m p i l e r do~ , s lkOt

a u p o r t t h i e i u s e t h e y c a n b ' / e l ( t t A ~ l l h ] t i l t , r ~ r s~l: c a l l [ t i t

TDe p r o g r a m u s p s t h e p r l a / a t i r e s a n n c b a r e c t e : s+,t d # ~ w ' l o p e d a n

" S o f t w a r o T o o l s ~n P a s c a l " By K e r n i g h a n a n d P l a u g e r .

D k c k H a n s e l J a n u a r y 8 , 1 9 8 3

r e w r i t t e n w i t h e x t e n t t o n 8 b y S t e v e O h [ c o F o b u r a r y 1 9 ~

{ w r a p p e r (CU) - - t h i s z s t h e w r a p p e r f o r a l l t l~e s o i t w a r e t o o l s { T h i s n e x t l i n e ~ n h e r i t s a l l t h e g l o b a l d e f i n i t i { m s t h a t g o a l o n g { with the software tools.

{ ~nherit ('user i : [bllb. soft tool .environlglobdef s .env')]

PROGRAM wrapper{ input ,out put) ;

PROCEHURE wh~le! 77 ;

CDNST { c o l u m n c o u s t a n t s }

COL I - 1 ; CDL 11 - 1 i ; COL 2 - 2 ; COL 12 - 1 2 ; COL 3 - 3 ; COL 13 - 1 3 ; COL 4 - 4; COL 14 14;

COL 5 - 5 ; COL 1 5 - 1 5 ; (;Ol. 6 = 6 ; COL 16 - 1 6 ; COL 7 - 7 ; COl, 17 - 1 7 ; ( O L 8 8 ; COL 1 8 = I R ; COL 9 - 9 ; COL 1 9 "- 1 9 ; COh l 0 i0; COL 20 20;

COL 72 - 7 2 ;

TABSIZE = 8 ; STARTING L I N E RUM - l O 0 0 0 ; { s 1 ~ r ~ i n s n u m b e r f o r c r e a t e d s t m t s . CONTINUE CHAR - AMPER; { "&" }

MAX STMT LENGTH - 1 3 2 0 ; { 20 l i n e s x 66 c h a r / l i n < }

MAX B U f F LENGTH - 1 0 0 ; { b u f f e r c a n h o l d I 0 0 l i n e s o t t e x t } BUFF PROTECT 9 5 ; { p r e v e n t s o v e r f l o w o f t h e b u f f e r }

VAR

t buff line = I..MAXBUFF_LENGTII;

t_text - ARRAY [I..MAR STMT LENGTH] OF CRARACTER~

t strut - RECORD

t x t : t t e x t ; { a c t u a l t e x t u : t h e ~ t a t e m ~ n t ) t x t _ _ l e n : i . . ~ 4 a × . S T ~ r LENGTH; { l e n g t h o t s t a t e m e n t t e x t

END; { s t m t r e c o r d } t o f _ d o ( D O W R I L E , D O NN,ENDDO,NORM DO,N{ 7)~) ,

l e t : i n t e g e r ; { k ~ e p s t r ~ c k o f ~* o : ] l n , , s i n s t m ~ } l ~ n e f l a g : b o o l e a n ; { i n H i c a t e s e n d o l f i i e w h e n t a l s ~ ) l i n e h u m : i n t e g e r ; { l i n e n u m b e r ( c r e a t e d a.~ p r o g r a m ) )

buffer : arrayIl..MAX BUFF_LENGTR] of STRING;

buff ct : integer~ {keeps track of the # of ]ini!s zn the burfor)

{ STRING constanLs ~

CAP_C : CHARACTER;

dowH, s c o n t z n u e , s , f n o t , s g o t o , s e n d : S T R ! N G ; l i n e : S T R I N G ;

s t m t : t _ s t m t ;

DEBUG : b o o l e a n ; c a s e _ f l a g : b o o l e a n ; { t r u e => a l l u p p e r : f a l s e - > d o n ' t c h a n g e } t e n : a r r a y [ O . . 4 ] o f i n t e g e r ; { p o w e r s o f 10 } s o u r c e : F 1 L E D E S C ; { o r i g i n a l v a x s o u r c e c o d e w i t h " w h i l e s " }

d e ~ t i n : F I L E D E S C ; { " w h i l e l o o p s " r e p l a c e d w i t h s t a n d a r d f 7 7 c o d e }

{1 * * * * l o w e r * * * * } FUNCTION l o w e r { a : CHARACTER ) : CHARACTER; { r e t u r n s a i n l o w e r c a s e } ( a s s u m e s d i f f e r e n c e b e t w e e n u p p e r & l o w e r c a s e i s a c u n s t a n t }

VAR c h : c h a r a c t e r ; B e g i n { l o w e r }

i f a t n [ o r d ( ' A ' ) . . o r d ( ' Z ' ) ] t h e n c h : - a + o r d ( ' a ' ) - o r d ( ' A * ) e l s e c h : = a ;

l o w e r : - o h ; E n d ; { l o w e r }

{ 1 * * * * * * * * * p r _ v a x t a b * * * * * * * * * } { p r o c e s s e s l i n e s c o n t i n u e d w i t h v a x TAB c o n v e n t i o n s } { u s e s t h e o r i g i n a l t a b c h a r a c t e r a n d r e p l a c e s t h e f i r s t t a b } { w i t h t h e n u m b e r o f s p a c e s n e e d e d t o p u t t h e f i r s t c h a r a c t e r } { i n c o l u m n 7 , o r c o l u m n 6 i f i t i s a c o n t i n u i o n l i n e } PROCEDURE p r v a x t a b ( V A R l i n e : S T R I N G } ; VAR t _ l i n e : S T R I N G ;

j , k : i n t e g e r ; v t c : i n t e g e r ; { v a x t a b c o n t i n u a t i o n o f s e t } t a b p o s : i n t e g e r ; { t a b p o s i t i o n }

B e g i n { p r v a x t a b } j : = 0 ; t a b p o s : = 0 ; { i f a c o m m e n t l i n e t h e n g o r e e n d a n d r e t u r n } i f n o t ( l i n e [ C O L 1 ] i n [CAP C , L E T C , S T A R I ) t h e n b e g ~ n

r e p e a t j : = j + t ; i f l i n e [ j ] - TAB t h e n t a b p o s : - j ;

u n t i l ( t a b p o s <> 0 ) o r ( j > - COl, 6 ) ;

i f t a b p o s > 0 t h e n b e g i n

f o r j : 1 t o ( t a b p o s 1) d o t l i n e i J ] : l i n e [ l ] ;

~ f I i n e [ t a b p o s + l } i n [ o r d ( * l ' ) . . o r d ( ' 9 " ) } t D e n v t c : - 1 e l s e v t c : - 0 ;

f o r j : - t a b p o s t o ( C O l + v t c ) H~, t l i n v [ i l : B I ~ N K ;

j : - (COl, 6 v t c ) ; k : - t a b p o s ; r e p e a t

~ : = j + l ;

k : = k + i ;

t _ l i n e [ j ] : = l i n e [ k ! ; u n t i l { l i n e [ k ] = ENDSTR) o r ( k >= M A X S T R ) ;

l ~ n e : - t _ l ~ n e ; e n d ; { i f t a b p o s > 0 }

e n d ; { i f . o f a c o m m e n t } E n d ; { p r _ v ~ t a b }

{ 1 * * * * * * r e a l s t m t * * * * * * * } FUNCTION r e a l _ s t m t ( l i n e : S T R I N G ) : b o o l e a n ;

VAR r s : b o o l e a n ; { 2 * * * * * * a l l b l a n k s * * * * * * * } FUNCTION a l l b ~ a n k s ( V A R l ~ n e : S T R I N G ) : b o o l e a n ;

VAR i : i n t e g e r ; Hi : b o o l e a n ; { a l l b l a n k s f l a g }

B e g i n i : - 0 ; b f : = t r u e ; r e p e a t

i : - ; + 1 ; i f n o t ( l i n e [ i ] i n [ B I & N K , T A B , N E W L I N E , E N D S T R ] ) t i l e n

b f : f a l s e ; u n t i l ( b f = f a l s e ) o r ( l ~ n e [ i ] = E N D S T R ) ;

a l l b l a n k s : - b f ; E n d ; { a l l b l a n k s }

B e g i n { r e a l s t m t } i f ( ( i i n T [ i ] i n t a T A R , C A P C , l e t c ] ) OR a f I _ b l a n k s ( l i n e ) ) t h e n

r s : = f a l s e e l s e r s : - t r u e ; r e a l s t m t : = I S ;

E n d ; { T e a l s t m t }

{ 1 * * * * * * * * * f l u s h _ b u f f * * * * * * * * * * * * * * }

PROCEDURE f l u s h . _ b u f f e r ; VAR i , j : i n t e g e r ;

l i n e : S T R I N G ;

{ 2 * * * * * * * * c h a n g e c a ~ e * * * * * * * * } PROCEDURE c h a n g e _ c a s e ( v a t l ~ n e : S T R I N G } ; { c h a n g e s a l l l o w e r c a s e l e t t e r s t o u p p e r c a s e ~f t h e y a r e n o t } { q u o t e s . A s s u m e s t h a t t h e d i f f e r e n c e B e t w e e n u p p e r a n d l o w e r c a s e }

{ ~s a c o n s t a n t } VAR i : i n t e g e r ;

, n q u o t e : b o o l e a n ; B e g i n { c h a n g e c a s e }

i n q u o t e : f a l s e ; i :- 0;

repeat

i : - i + i ; i f 1 ~ n e [ i ] - SQUOTE t h e n k n q u o t e : - n o t : n q u o t e ;

i f ( l i n e [ i ] i n [ o r d ( ' a ' ) . . o r d ( ' z ~ } ] ) a n d ( n o t i n q u o t e ) t h e n

I i n e [ i l : = ] i n e [ i ] + ( o r d ( ' A ' ) { ~ r d ( * a ' ) )

146 Adv. Eng. Software, 1985, Vol. 7, No. 3

Page 6: VAX Fortran to Fortran 77 translator

until line[i] = ENDSTR; End; { cbangecase }

Begin

for i := I to buff ct do begin if case_flag then change_case(buffer[it); putstr(buffer[i],destin);

end; { for i } buff_ct := O;

End; { flush_buffer }

( 1 ********* put_xn_buff ************** } { puts the llne in the buffer after striping off the end of { line comment and puling it in the buffer first PROCEDURE put_in_bnff(VAR line : STRING ); VAR i : integer;

{ 2 ******** strip_tom ********* } PROCEDURE strip_com(VAR line : STRING); { used to convert end of line co~ents to standard form } { Also used to test if the length of non-comment lines is 72 } V~dR inquote : boolean;

endline : integer; i,j : integer; comstr : STRING;

Begin { strip_tom } i := I; inquote :ffi false; while (i <= MAXSTR) and (line[i] <> ENDSTR) do begin

if line[it = SQUOTE then inquote := not inquote else if (line[it = EXCLAM) and (not inquote) then begin

endline := i; comstr[l] := CAp_c; j : = 1 ; repeat

i := i+l; j := j + l ; comstr[j] := line[i];

u n t i l ( line[it = ENDSTR ); buff ct := buff_or + i; buffer[buff ct] := comstr; line[endline] := NEWLINE; line[endline+1] := ENDSTR; i := endline;

end; { else if } i := i + i;

end; { while } if ((i - 2) > COL_72) and { subtract 2 for NEWLINE and ENDSTR (not (line[COL l] in [CAP-C,LETC,STAR])) then begin

message('>>>>>>> ERROR <<<<<<<<'); putstr(line,STDOUT); message('line with more than 72 characters found'); message('Could be a result of converting tabs into spaces')

end; End; { s t r i p _ t o m )

{ 2 *********** dump_excess **************** } PROCEDURE dump._excess;

This procedure i s used to remove the non e s e n t i a l l i n e s } from the buffer in order to keep it from overflowing due } to a large ammount of comments. The main use of this will } probably be at the begining of the program where there is } often a large number of header comments }

} NOTE: the comments are dumped to the destination file first} which will change the order of the comments in relation to } the statement lines. This is only done when the buffer } count reaches BUFF_PROTECT (95) }

VAR i,hreal : integer; Begin { dump_excess }

i := 0; b_real :- 0; repeat

i := i + I; if real_stmt(buffer[i[) then beg in

b real := b_real + l; b~ffer[b_real] := buffer[it

end e l s e putstr(buffer[i],destin);

until (i = BUFF_PROTECT); buff ct :" b_real;

End; { ~ump_excess } { 2 ****** pr_option ******* } PROCEDURE pr_option(card : STRING); { sets the boolean flags for debuging and changin~ case } vat opt_~o~ : integer;

{ 3 ****** find true ****** } FUNCTION find_t~ue(cpt : integer) : boolean; { determines if there is a true after the option card } { only checks for the letter "t" } v a t flag : boolean;

Begin { find true } while (ept < MAXSTR) and (card[cptl in [BLA~FK,TAB]) do

opt := opt + I;

if (lower(cardlcpt]) ~ ord('t')) then flag := true else flag := false;

find true := flag; End; { find_true }

Begin { pr_option } opt~os := 3; { check if debug or upper option } if (lower(card[opt_pos]) = ord('d')) and

(lower(card[opt_pos+l]) ~ ord('e')) and (lower(card[opt_pos+2]) = ord('b')) and (lower(card[opt_pos+3]) = ord('u')) and ( l o w e r ( c a r d [ o p t _ ~ o s + 4 ] ) = o r d ( ' g ' ) ) then

DEBUG := find_true(opt~os + 5)

e l s e i f ( l o w e r ( c a r d [ o p t ~ o o s ] ) = o r d ( ' u ' ) ) and ( l o w e r ( c a r d [ o p t ~ o $ + l ] ) = o r d ( ' p ' ) ) and ( l o w e r ( c a r d [ o p t _ p o s + 2 ] ) = o r d ( ' p ' ) ) and ( l o w e r ( c a r d [ o p t ~ o o s + 3 ] ) = o r d ( ' e ' ) ) and (lower(card[opt_pos+4]) = ord('r')) then

case_flag := find_true(opt~os + 5);

End; { pr_optlon )

Begin { put_in_buff } if (line]COL i] in [LETC,CAP_C]) and

(line[COL 2] = DOLLAR) then pr_option(line); strip_tom(line); buff ct := buff_el + I; buffer[buff ct] := line; if buff_ct >= BUFF_PROTECT then dump_excess;

End; { put_in_buff }

{ I ********* fill_buff ********** } { fills the buffer with a fortran statement including any cou~ents ) { v~ tab conventions and end of line comments are processed out } { otherwise the text remains unchanged ) PROCEDURE fill buff; FAR real_line : boolean;

continued : boolean; i : integer;

( 2 ******* is continued ******** ) FUNCTION is_co~tinued(VAR line : STRING):boolean; vat flag : boolean;

i : integer;

Begin ( is_continued } { find first non blank character. } i := i; while (lineli] = BLANK) and (i <= COL 6 ) do

i := i + I;

if i <> COL 6 then flag := false else if lin~ICOL_61 in lord('0"),BLANK] then

flag := false else flag := true;

is_continued := flag; if DEBUG then writeln('is a continuation line: ",flag);

End; ( is_continued }

Begin { fill buffer }

{ first time "line" comes from procedure "initialize") { after that it is left over from "fill_buff" since } { it has to check if the next line is a continuation } ( of the current line )

p u t _ i n _ b u f f ( l i n e ) ; cont inued :ffi f a l s e ; r e a l _ l l n e :ffi f a l s e ; i f l i n e _ f l a g then r e p e a t

i :ffi 1; if g e t l i n e ( l i n e , s o u r c e , M A X S T R ) then ' begin

p r _ v a x t a b ( l i n e ) ; while (i < MAXSTR) and (line[it in [BLANK,TAB]) do

i := i + I;

if (i = COL I) and (line[COL_l] = EXCLAM) then line[l[ := CAP_C;

if (line[i] ~ EKCLAM) and ( i <> COL_6 ) then begin line[i] :- BLANK; line[l] :ffi CAP-C;

end;

i f l i n e [ l ] in [CAP_C,LETC,STAR] then p u t _ i n _ b u f f ( l i n e ) else if line[i] in [NEWLINE,ENDSTR] then put_in_buff(line)

{ else it is a non trivial line and has to be checked for } { c o n t i n u a t i o n (TAB or normal) or nons tandard do t y p e . }

e l s e begin real line := true; if i~_continued(line) then begin

continued := true; put_in_buff(llne);

end else continued := false;

end; end { if getline then } e l s e begin

line_flag := false; flush_bur fer;

end; until (real_line and not continued) or (not line_flag); if DEBUG then writeln('fill buff: buff_or = ",buff_ct:l);

End; { fill_buff }

{l **** initialize **** ) PROCEDURE initialize; { initialize constants, etc. } VAR j : integer;

ch : CH~CTER; Begin { initialize }

{string constants} CAP_C :- ord('C');

dowh[l] := o r d ( ' d ' ) ; s i f n o t [ l ] := o r d ( ' I ' ) ; dowh[2] : " o r d ( ' o ' ) ; s i f n o t [ 2 ] := o r d ( ' F ' ) ; dowh[3] := o r d ( ' w ' ) ; s i f n o t [ 3 ] :" o r d ( ' ( ' ) ; dowh[4] :- o r d ( ' h ' ) ; s i f n o t [ 4 1 :- o r d ( ' . ' ) ; dowh[b] : " o r d ( ' i ' ) ; s i f n o t [ 5 ] := o r d ( ' N ' ) ; do~h[6] : - o r d ( ' l ' ) ; $ i f n o t [ 6 ] := o r d ( ' O ' ) ;

Adv. Eng. Software, 1985, Vol. 7, No. 3 147

Page 7: VAX Fortran to Fortran 77 translator

d o w h [ l ] := o r d ( ' e ' ) ; dowh[8} :~ ENDSTR;

s c o n t l n u e [ l ] s c o n t t n u e [ 2 ] s c o n t t n u e [ 3 ] s c o n t ~ n u e [ 4 ] s c o n t ~ n u e [ 5 ] s c o n t ~ n u e [ 6 ] s c o n t z n u e [ 7 ] s c o n t t n u e [ 8 /

sifnot[7] := ord('T'); sifnot[8] := ord('.');

:= ord('C'); sgoto[l] := ord('G'); :- ord('O'); sgoto[2] :- ord('O'); :- ord('N'); sgoto[3] :- ord('T'); := ord('T'); sgotoI4] :- ord('O*); := o r d ( ' I ' ) ; := o r d ( ' N ~ ) ; s e n d [ l ] : - o r d ( ~ e ' ) ; : - o r d ( ' U ' ) ; s e n d { 2 [ : - o r d ( ' n ' ) ; := o r d ( ' E ' ) ; s e n d { 3 [ : - o r d ( ' d ' ) ;

s e n d [ 4 ] := o r d ( ' d ' ) ; send[5[ := ord('o'); send[6[ := ENDSTR;

{ startimg value of statement numbers } line_hum := STARTING LINE NUM;

{ powers of I0 } t e n { O [ :~ 1 ; f o r j := 1 t o 4 do t e n { j [ : - t e ~ [ j - l l * I 0 ;

s o u r c e := STDIN; { s o f t t o o l s c o n s t a n t s } destin := STDOUT;

case flag := true; DEBUG := false;

{ get the string " l~ne " for till bull ] line_flag := getline(line,source,MAXSTR); if line_flag then pr_vaxtab(line);

End; {initialize}

{l **~****** get_stmt *********~ } FUNCTION get_stmt( VAR stmt : t stmt ):boulean; { Gets entire fortran statement, including continued lines, Into { s t m t . t e x t [ . . ] a n d t h e l i n e n n m b e r i f any i s s t o r e d ~n to { s t r u t . h u m [ . . ] } VAR

1 , b e : i n t e g e r ;

{ 2 * ~ * * * * * b e g i n i n g o t _ t e x t * * * ' * * ~ * } { f i n d s t h e p o s i t i o n o f t h e f i r s t c h a r a c t e r of ~he a c t u a l { s t a t e m e n t t e x t , ~ g n o r i n g b l a n k s , t a b s , :md s t a t e m e n t l a b e l s FUNCTION b e g i n i n g o i t e x t ( l i n e : STRING) : i n t e g e r ;

VAR j , i : i n t e g e r ;

B e g i n { h e g i n i n g ~ o f t e x t } i :~ COL 1 ; { i n t h e f i r s t s i x c o l u m n s t h e n c a n be a n u m b e r , b l a n k , o r a t a b

w h i l e ( i <= COL 6) a n d ( l i n e ~ i ] <> TAB) do b e g i n i := i ÷ 1 ;

e n d ; { w h i l e }

{ f i n d t h e f i r s t r e a l c h a r a c t e r o f t h e s t a t e m e n t l i n e } w h i l e ( i < MAESTR) a n d

( l i n e { i [ i n {TAB,BLANK I ) a n d ( n o t ( l i n e { i [ i n [NEWLINE,ENDBTR])) do l , eg~n

i := i + l ; e n d ; { w h i l e } { p o s i t i o n o f t h e f i r s t c h a r a c t e r ot t h e s t a t e m e n t } b e g i n i n g o f t e x t : - 1;

E n d ; { b e g i n i n ~ _ o f _ t e x t }

{ 2 ******** get_tit ******** } PROCEDURE get_txt(Iine : STRING; VAR let : integer); VAR j : integer;

inquote : boolean; Begin with stmt do begin

j := begining_of_text(l~ne); if ict = i then txt_len := O;

{ else txt fen starts where it left off last tlme } while (j <7 MAXSTR) and (not(line[j{ in [NEWLINE,ENDSTR]) do begin

txt len := txt len + I; _ t x t [ t x t fen] l i n e { j [ ; j : - j + l ;

e n d ; { w h i l e } e n d { w i t h } E n d ; { g e t _ t i t }

Begin { get_stmt }

if DEBUG then writeln(chr(10),chr(10),'****** GET STM~ ******',chr(10))

f~11 buff; stmt.txt_len := 0;

{ l~ne_flag indicates eof t[ lalse } { it is set in "fill buff" } if line_flag then begin

get_stmt :- true;

bc := 0 ; { buffer line p o s i t i o n p o l r / t ~ r / let ; O; { statement line count } repeat

bc := bc + 1 ; t f r e a l _ s t m t ( b u f f e r [ b c l ) t h e n > e g i n

l c t : - l e t + 1 ; g e t t x t ( b u f f e r [ b c ] , l e t ) ;

e n d ; { i f t h e n } u n t i l ( b c = b u f f c t ) ;

e n d { I f l i n e f l a g ) e l s e g e t s t m t : - f a l s e ;

E n d ; { g e t s t m t }

I * * * * * * * * * p r s t m t * ~ * * * * * * * * * * * }

determins if a statement is a do while or a non standard do loop } asd then processes the stmt if necessary }

PROCEDURE pr_stmt( VAR ~tmt : t stmt)~ VAR do_type : t_of_do;

i : integer; {used in DEBUG}

148 Adv. Eng Software, 1985, Vol. 7, No. 3

{ 2 ************ find_do_type ************** } { returns the type of do loop that is In the statement }

FUNCTION find ~o_type : t_of do; VAR tempdo ~ t_of_do;

{ 3 ************ is_enddo *******~****** ~ FUNCTION is_enddo : boolean; VAR flag : boolean;

i,j : integer; Begin with stmt do begin

i := COL I; j := COL i; flag := true; repeat

while txt[i] in [BLANK,TAB[ do i := i + l;

tf lower(tit[ill - send[j[ then begin i := i + I; j := j + I;

end

else flag := false; until (flag = false) or (send[j[ = ENDSTR);

is enddo := flag; end; ~ i~ith } End; { isenddo }

{ 3 ************ is_dowhlle ***************** } FUNCTION is_dowhlle : boolean;

VAR flag : boolean; i,j : integer;

Begin with stmt do begls

i:=l;j :=i; flag :- true; repeat

while txt[i] in IBLANK,TABI do i :- i + i if lower(txt[i[) = dowh[j] thuo begi~

~ := i + l; j := j * ~ ;

e n d e l s e f l a g := f a l s e ;

u n t i l ( f l a g ~ a l s e ) o r (dowh[ i[ ~ ENDSTR); i s d o w b i i e : - f l a g ;

end; ~ with } End; { is dowhile }

{ 3 *********** do_loop_type *************** } FUNCTION do_loop_type : t~of_do;

VAR o~s,i : integer;

i ~ o t e : boolean; t e m p _ d o : t__of_do;

{ ~ ~e*~******* f ind~rparen ************ } PROCEDURE find_rparen(txt : t_text; VAR i : integer[ { advances the pointer "i" to the last RPAREN of a set of } { parentheses. It handles nested parentheses recurstvly } { i must be given a value in the calling routine. } Begin

If DEBUG then writeln('find rparen: i - ",i:1); repeat

i :~ ~ + i;

~f txtlil = SQUOTE then inquote :- ~ot ~nquote else if txt]i] - LPAREN then find_rparen(txt,i);

nntil (i - stmt.txt fen) or (txt[1] = RPAREN); End~ { find_rparen >

Begin with stmt do begin { dn loo~type } temp do :- NO_DOs i :~ 2 ; if 1ower(txt[l]) = LETD the~

while txt[~] in [BLANK,TAB[ do I : - ~*l; if lower(txt[i]) <> LETO then temp do : NO_DO e l s e begin

o ~ o s := x;

i n q u o t e := f a l s e ; r e p e a t

i := x + i;

if txt[i] = SQUOTE then inquote := not inquote;

until ((txt[i] = EQUALS[ and (not inquote)) or (i >= txt fen) I

if txt[i] ~ EQUALS then begin repeat

i := i+l; if txt[i] = SQUOTE then inquote := not inquote

else if txt[i] - LPAREN then findrparen(txt, i); until (i = tit fen) or

((txt~i] = COM>~) and [not inquo[e))

if txt[i] - COMIiA then beg~n I := o~os ÷ l; while (txt[i] in [BLANK,TAB[) do ~ : i*l;

if txt[i] in [ord('0")..ord('9")] then temp do := NORM~DO

else temp do :- DO NN;

e n d { ~f comma [ else temp_do :- NO DO; { I~ no comma on line

end { il equals then } else temp_do := NO_DO; { else if not equals }

end; { else begin } do_loop type := temp do;

end; { with }

End; { do_loop_type }

Begin with stmt do begin { find_do type } temp_do := NO_DO; if lower(txt[l]) = LETE then begin

if is enddo then temp_do := ENDDO end else if lower(txt[l~) = LETD then

if is_dowhile then temp__do :- DOWBILE else temp_ do := do_loop_type;

Page 8: VAX Fortran to Fortran 77 translator

find_do_type := temp_do; end; { with )

if DEBUG then writeln(~find_do_type: temp_do = ~,temp_do); End; ( finddo_type }

{ 2 ********** pr_do ************ } PROCEDURE pr_do(VAR stmt : t_stmt; do_type : t_of_do); { p r o c e s s a "do" statement } TYPE num_str = array[1..5) of character;

VAR i,j : integer; { counter and loop indicia } slinel : nu~str; { line number string xxxxx if(.not } aline2 : hum_sir; { line number string "guru yyyyy" } curt_do : t_of_do; do~osition : t buff line; { buffer position of do stmt. }

{ 3 ****** insert ******** } { the STRING instr is inserted into the buffer in front of b~os} PROCEDURE insert( instr : STRING; VAR b~os : integer); VAR i,j : integer; Begin ( insert )

for i := buff ct + i downto b_.pos + I do buffs=liT := buffer[i-l);

buffer[b~s] := instr; buff_ct := buff_ct + I; b~pos := b~os + i;

End; { insert }

{ 3 ****** f i n d the do ******* } { a do statement is always the first non BLANK or } { non cogent line in a the buffer FUNCTION find the do : t buff line; VAR i : t buff line; Begin

i := 0; repeat

i := i + I; until real_star(buffer[i]) find the do :~ i;

End; { find the do }

{ 3 ****** ch t o s t r ******

PROCEDURE ch tO s t r (n : integer; VAR s t r n u m _ s t r ) ; { t r a n s l a t e s i n t e g e r n into 5 c h a r s t r i n g s t r } VAR j : integer;

Begin { c h _ t o _ s t r } for j :- 1 to 4 DO

s t r [ 6 - j l := ord('O') + (n mod t e n [ j ] - n mod t e n [ j - l ] ) d iv t e n [ j - l ]

s t r [ l ] := o r d ( ' 0 " ) + (n - n mod t e n [ 4 ] ) d i v t e n [ 4 ] ; End; ( ch_to_str }

{ 3 ******* has_a_number *******} FUNCTION h a s . _ a . _ ~ b e r (line : STRING) : boolean; { determins if there is an existing statement label for the { statement } VAR j : integer;

nu~exist : boolean; Begin { has_a_number }

j :E COL 5; { last legal column for a statement label } hum_exist := false;

r e p e a t if line[j] IN [ord('l')..ord('9")] then

mum_exist : - true { must be non 0 } else j : - j - I ;

until (j = O) or (hum_exist); has . a_number :~ num._exist ;

if DEBUG then writeln('has_a_number:', num._exist); End; {has_a._number)

{ 3 ********* pr_dowhile *********** } PROCEDURE pr_dowhile(VAR do_pos : t buff line); V~R a d d s t r : STRING;

i,j : integer; e~os : integer; { position of the e in "dowhile" ) last_real : integer;

Begin { put in line number - use existing number if it is there }

if has_a_n~ber(buffer[do_pos]) then begin j := I; for i := COL_I to COL 5 do

if bufferldo~os,i] in [ o r d ( ' 0 " ) . . o r d ( ' 9 " ) ] then begin

s l i n e l [ j ] := b u f f e r [do__Dos , i ] ; j :=j +l;

end; for i :2 j to COL_5 do slinel[i] := BLANK;

end e l s e begin

ch to str(line_num,slinel); line_hum := line_hum + I;

end;

{ pot i n if(.not." } { p o s i t i o n s 12345678901234 }

for i : - COL 1 t o C0~_5 do a d d s c r [ i ] := s l i n e l [ i ] ; a d d s t r [ C O L _ 6 ~ : - BLANK; for i : - COL 7 t o COL 1~ do a d d s t r [ i ] : - s i f n o t [ i - 6 ] ; a d d s t r [ C O L _ l ~ ) : " REWLINE; adds t r [COL 16] : - ENDSTR; i n s e r t ( a d d s t r , d o ~ o s ) ;

{ delete the "dowhile" and make the line a continuation of } { the "if(.not." }

i := O;

r e p e a t i := i ÷ l ;

until lower(buffer[do.us,t)) = LETE; e~os := i; { posit ion of the "e" in the dowbile } for i := COL I to COL_5 do addstr[il := BLANK; addstr[COL 6T := CONTINUE_CHAR; addstr[COL 7] := BLANK; j := e~os; i := 7; repeat

i :- i+l; j := j+l ; addstr[i] := buffer[do.us,j);

until (buffer[do_Dos,j) = EHDSTR); buffer[do__pos] :- addstr;

get 2nd line number, for the trailing guru ) on the "if(.not ..... " } ch_to_str(line_~, aline2); llne._num :E line_~um + l;

build addstr to be " & )GOTO xxxxx" ) addstr positions are 123456789012345678 }

for i :- COL l to COL_5 do addstr[ i) := BLANK; addstr[COL_6~ := CONTINUE_CHAR; addstr[COL_7] := BLANK; addstr[COL 8] := RPAREN;; for i :" COL 9 TO COL_S2 do addstr[i] :- sgoto[i-8]; addstr[COL_l~] := BLANK; for i := COL 14 to COL_18 do addstr[i] := sline2[i-13]; addstr[COLl 9] := NEWLINE; addstr[COL20] := ENDSTR;

the position to insert the return guru after the ) last real line in the buffer } for i :- I to buff ct do

if ~ea1_atmt(b~ffer[i]) t h e n last_real := i; last real :- last real + l; _ -- i n s e r t ( a d d s t r , l a s t r e a l ) ;

End; ( p r _ d o w h i l e )

{ 3 *********** pr_do_nn ************** } PROCEDURE pr_do_nn(¥A~ do_poe : t b u f f l i n e ) ; ¥ ~ a d d s t r : STRING;

i , j : i n t e g e r ; o_pos : i n t e g e r ; ( p o s i t i o n of the o i n t he "do" )

Begin i f h a s _ a _ n u m b e r ( b u f f e r [ d o . _ p o s ] ) t hen b e g i n

j : - 1; for i :" COL~I to COL 5 do

if buffer[do_pos,i~ in [ord('0")..ord('9")] t h e n b e g i n

addstr[j] :- buffer[do_pos,i]; j : = j + 1 ;

end ; f o r i := j to COL_6 do a d d s t r [ i ] : - BLANK;

end e l s e b e g i n

for i :- COL_I to COL_6 do a d d s t r [ i ] := BLANK; end ;

adds t r [COL_7) := o r d ( ' D ' ) ; adds t r [COL_8] := o r d ( ' O ' ) ; adds t r [COL_9] : - BLANK;

{ now g e t t he number to make a normal do l oop ) c h . _ t o _ s t r ( l l n e _ a ~ m , s l i n n 2 ) ; I tue._num : " line_num+l ;

f o r i := COL l 0 to COL~14 do a d d s t r [ i ] : " s l i n e 2 [ i - 9 ] ; adda t r [COL_l~ ] :- NEWLINE; addstr[COL_16] := ENDSTR; i n s e r t ( a d d s t r , d o ~ o s ) ;

{ now d e l e t e the "do" f rom the o r i g i n a l l i n e } { and make the original a continued line }

i := O; repeat

i := i+l; until (lower(buffer[do_pus,i)) - LETO); o._pos := i; { position of "o" in do } for i :2 COL I to COL_5 do addstr[i] := BLANK; adds t r [COL 6T := CONTINUE_C~AR; adds t r [COL 7] := BLANK; j := o_pos ; i := 7; r e p e a t

i : - i+l; j : - j+l; a d d s t r [ i ] := b u f f e r [ d o _ p o s , j ] ;

u n t i l ( b u f f e r [ d o _ p o s . j ] = ENDSTR); i f i > co1_72 t hen b e g i n

p u t s t r ( b u f f e r [ d o _ _ p o s ] , a t d e r r ) ; m e a s a g e ( ' S t r l u g l o n g e r t h e n 72 a f t e r b e i n g p r o c e s s e d ' ) ; e r r o r ( ' p r o b a b l y a t ab ( l c h a r . ) changed to 5 b l a n k s ' ) ;

end; buffe~[do_pos] :" addstr;

End; { pr_do_nn }

{ 3 ********* pr_enddo *********** } PROCEDURE p r _ e n d d o ( s l i n e l , s l i n e 2 : num._s i r ) ; { p r i n t s r e p l a c e m e n t f o r "ENDDO" l i n e a s s o c i a t e d w i t h a "WHILE" } VAR j : i n t e g e r ;

end_pos : t _ b u f f _ l i n e ; l_temp : STRING;

Eeg in { p r_enddo } i f DEBU~ t h e n w r i t e l n ( ' p r _ e n d d o : c u r r _ d o - " , c u r r . _ d o ) ;

Adv. Eng. Software, 1985, Vol. 7, No. 3 |~9

Page 9: VAX Fortran to Fortran 77 translator

e n d j o s := t t n d . . t h e _ d o ;

( i t the e n d d o l i n e h a s a n u m b e r Lben t u r i : at i' ( i n t o ##### c o n t l n u e /

i f ha~ a n u m b t . r ( b u [ f t . r [ t . n d ~ o ~ ) ) lh t ' t , ~ , ' , 1 , : _ . j l ; f o r t : - DOt 1 t o COl $ do

i t b u f l , . r [ e n : i ~ o ~ , i ~ I n [ o r d ( ' O ' J , . o t d ( ' 9 " ) l :hen begin

l._temp[ II : = but f e r Eend po~, ~ ] ; j : - j + 1;

e n d ; ~or i : " j t o COL_6 do 1 . t t .mp[* ] := BLANK; f o r l := COL 7 t o COL_I4 do _ t t . = p [ * ] : - ~ o n t : , : u t , [ t - h { , l _ t e m p [ C O L 15l := NEWI.1NE; l _ t e m p [ C O L 16] : - ENDSTR; £ n ~ e r t ( l _ t emp , e n d _ p o ~) ;

e n d ;

t f c u r t _ d o * I~)WHILE t h e n begxm w r ~ t e g o r e y y y y y , f o r j := COL I t o COL 6 do ] f i e m p [ j { ~ BIANK; / o r j :~ COL Y t o COL 10 dc i__r~mp[j ' , : - ~ g o t o ( l - ~ , ] ; l _ t e m p [ C O L 11{ ; - BI£NK;

~or j := C'~l. 17 t ~ COL !¢~ ~ I : , 'mp~ i : " , , l l n , . l { I l l ~ ; I_Lemp{COL 17] := NEWI. INE, l . . t e m p [ C O L 18] :~ ENDSTR; { h a v e t o ~ h i l t t h e i l n , ' s ,:; tt~, b u : : , . ~ It , u:,,K,, r, om { l o t t h , ' t ' x t l a l l n v l t l ~ . r t { i : , .ml, ,c*~a p o s ) ,

v n d , { :~ c u r t _ d e - :R)WHIIV : : , ~ ; ,

w r i t e x x x x x c e n t : n u n , t i l l s IS don, ' : o r b o t h ~vl,*'~ o: t, n c d o . .

f o r j := COl. I t o COL 5 do I t e m p [ ] } : - ~ , l l n e 2 [ J ] ; l _ t e m p [ C O L 6J := B ~ N K ;

t o t j : - COL ? t o COL 14 do l _ l e m p [ j [ := ~ c o n t ~ n u e [ j - b ] ;

I _ t e = p [ C O 1 . 15] : - NEWI.INE; l ._temp[COl. 16] : - ENDSTR;

{ r e p l a c e e n d d o w i t h I t e m p } b u l l e t [ e n d p o s t : - !. l e a p ; { d e l e t e ~ ; t b , . "ENDIgV'

f l u s h _ b u r l e t ; E n d ; { p r _ e n d d o }

Be~xn { pr._do } t : u r r _do : : d o _ t y p e ; d o 3 o s t t l o n : " i i n d . _ t h e _d~, t f D E B ~ L h e n w r t t e l n ( ' p r do : d o . t y p e r ' , v u r r , do~ ;

11 d o _ t y p e - ~ W H I I . E t h e n b e g i n

pr dowl n l e ( d o _ pos ~ t / o n } ; f l u s h _bur [~'r ;

, ,nd

t , l ~ e 1: d o _ t y p e = ~ _ N N t h e n b,-gl l : p r _ d o _ t m { do_ po~ i t i o n ) ; f l u s h b u f f e r ;

, ' n d ;

{ l o o k i o r t h e " e n d do" }

r e p e m t i ! g e t _ s t r u t ( s t r u t ) t h e n b t . g l u

do t y p e : = t l n d _ d o , t y p e ; i [ d o _ t y p e " E B D ~ t h e n p r . e n d d o ( s l i n e l , ~ l t n e 2 ) e l s e i f d o _ t y p e £n [ ~ N N , d o w h i l e ] t h e n p r _ d n ( ~ t m t , d o _ t y p e )

e l * e [ l u ~ h _ b u f f e r ; et ld e l s e

e r r o r ( ' m t * s ~ n g c n d d o t o m ~ t c k p r e v l m t s "do ~ t r u t t u r e s " " ) ;

u n t i l ( d o _ t y p e - E N D ~ ) ; E n d ; { p r _ d o }

B e g i n { p r _ s t m t ~ do. t y p v := l i t ld d o _ t y p e ; 1~ do t y p e i n [ D O . . N N . d o w b l l e ] t h v n pr d o ( s t o t , d o t yp , . ' .

v l s e f l u s h _ b ~ l l e t i

gt~d, { pr ~ t x l ?

I * * * * w h i l e I ; / * * * ~ BeRzu { w h z l e f / l )

~ n x t ~ a l z z e ;

i e p e a I L i n e _ f l a g : - get s t ~ t ( s t : : t ) . I f l i n e . f l ~ g ( h l . n p ~ _ ~ t m t ( s t m t ) ,

u n t i l ( l ~ n e . f l a g - 1 ~ 1 ~ } ;

E n d , { w h i l e 1 7 7 )

B e g i n { w r a p p e r )

l n z t i o ;

~ h z l e t ? ? gnO. { ~ r a p p e r ~

LONGNM.SFT Creates a list of define statements for long variable names

LONGNM PROGRAM ( s f t ) } P r o g r e ~ t o ! rod v a r i a b l e n a m e s l o n g e r t h a n 6 c h a r a c t e r s i n FORTI~N )

d e c l a r a t i o n s t a t e m e n t s and d e t e r m i n e a u n i q u e h c h a r a c t e r name to } be u~ed im p l a c e o t t h e l o n g n a m e . }

}

The u n i q u e ~ m e xs e i t h e r a t r u n c a t e d v e r s i o n o f t h , ' o r i g i n a l name }

o r t f t r u n c a t i o n c a u s e ~ a c o n f l i c t w i t h an e x ~ t t n g name, a new u n i q u e } name i~ g e n e r a t e d . Tile l x r a t f o u r c h a r a c t e r s o f t h e g ~ n e r a t e d name c a n } be s p e c i f i e d by t h e user w i t h a CSUNIQUE o p t i o n : a r d . The d e f a u l t f e z t h e p r e f i x x~ "UNIQ'*. Tile r e m a i n i n g twu L h a r a c t e r s a r e d e t t . t m t n ¢ ' d by

t h e o r d e r t h a t t h e name~ a r e g e n e r a t e d ; s t a r t i n g a t O0 and e n d i n ~ a t

ZZ. ThLs a l l o w s t o t 1296 u n i q u e names t o be g e n e r a t e d . T h i s s h o u l d be s u f f i c i e n t s i n c e a name i s g e n e r a t e d o n l y when a IonK name c a n n o t be t r u n c a t e d w i t h o u t c o n f l i c t .

A l l v a r i a b l e s t o be p r o c e s s e d ( p l u s s i x l e t t e r v a r i a b l e s ) m u s t be d e c l a r e d . The l o n g v a r i b l e s a r e o b t a i n e d by ~ c a n n l n g t u n d e c l a r a t i o n s .

The p r o g r a m c a n make t h e d ~ s t ~ n c t l u n b e t w v e n l o c a l and ~ [ o b m [ v a r x m b l ~ n a m e s . The o n l y ~ l o b a [ n a m e s ~n PORTRAN a r e s u h r n u t i n e , [ u n c [ l o ~ , a n d c o ~ o o b l o c k nmme~. G l o b a l name~ a r e t r , , a ~ e d ~n t h e ~ame way ~s l o c a l ~ a m e s .

[ [ t h e C$MODUI.E o p t i o n ~ ~ s e d thor : a l l g l o b a l n a m e s a r e m a p p e d

i n t o ~ u n i q u e name g e n e r m t e d f r o m a fm~r l e t t e r p r e f i x ~ h a t c a n be ~ p e c i [ i e d by t h e u ~ e r w i t h • CSMODOI.E o p t i o n c a r d . The l a s t ~wo c b ~ r a c t e r ~ a r e o b t a i n e d £n t h e ~ame way a s f o r t h e l o c a l n a m e ~ . The d e f a u l t £m " M O ~ " . H t h e u ~ r doe~ n o t w a n t a g l o b a l name c h a n g e d , t h e name m u ~ be p u t ~n ~ C $ V I S I 8 L E o p t i o n c a r d . Names on t h e v i s i b l e

o p t i o n caCd w i l l n o t be p r o c e m ~ e d £n a n y way , e v e n ~[ ~bey a r e l o n g e r t h e n s£~ c h a r a c t e r s . The n a m e s mus~ be s e p a r a t e d by : a c u b a , t a b , o r b l a n k . A~ many C~VISIBLE c a r d ~ u~ ~ v c , . ~ s a r y may be u ~ e o .

S i n c e t h e 5 o ~ w a r e T o o l ~ m a c r o p r o c e s s o r ~s ca~e ~ e p e n d e n t t h ~ p r o s r a m wam w r i t t e n t o be c a ~ e d e p e n d e n ~ . V a r [ m b l e s ~n d i f [ e r e n ~ c~me

mre d ~ [ ~ e r e n t v a r [ a b l e ~ e v e n when ~ p e l l e d t h e ~am~. [ t i s t h e u ~ r ~ r e s p o n s i b i l i t y t o b , c o n 6 ~ t a n ~ £~ u s i n g u p p e r and l u w e r ca6e name~

Code t h a t ~ u p p o r t s t h e oge o f u n d e ~ c o r v ~ as v a l i d ~ b ~ a c t e r s ~n v a r i a b l e names i s ~ n c l u d e d , bu¢ p r o t e c t e d by .~ b o o l o ~ : o u ~ t a n l b e c a u s e t h e ~ a c r o p r o c e s s o r ~ u s t be ¢ o d ~ [ [ e d : o t r ~ a ~ u n d e r s c o r e s a~ v a l i d a lphanumer i c c h a r a c t e I ~ . Tb,. Co~8~an[ "}'R_USCORE" c;t]~;[ ~)e s.,[

t o t r u e ~n o t t e r f o r i b i s p r o K r a m t o p r o c e s ~ : m d e I s c ~ , t , . s .

I m b e d e d b l a n k ~ ~() a v a r i a b l e name a r e i l l e g a l , l o n f i :ames o u ~ t ~ no t be s p l ~ t a c r n s 6 c a r d b o u n d a r l e ~ w i t h C o n l : n u a l l ( ~ n , , r : i~

A s y m b o l ~ t a ; , . t a b l e x~ u~ed : o det*.rml~,, ~ : . , :.[,~t,,m,.nI :s a i d e c l a r a t l o n to be ~cann~,(~.

The program ~ead~ [ tom s t a n d a r d ~nput and wr~ tea t : , ~ tanda rd o u t p u t }

INPUT . . . FORT~N aource t h a t has any C$1NChUDES processed OUt.

I t t h e r e a r e VAX t a b c o n v e n t i o n s , o r end o[ l i n e c o - - e a t s

~n t h e ~ o u r c e i t s h o u l d [ ~ r ~ t be p r o c e s s e d by "~H2STD". S t a l l n t n g t e r m i n a t e a wxth e o f .

OUTPUT . . . A [ l ~ L e l d e I L n e ~ t a t e m e n / ~ c o m p a r a b l e w l t h t h e S o l / w a r e

t o o I ~ m a c r o p r o c e s B o r .

USE O F O ~ I O N C O U N T CARDS - - e x a m p l e c $ f l e b u g t r u e - - d t a g a o s t i c s on ( t r u e ) , o [ f ( r a i s e ) - d e / ~ u l t c S m o d u l e b t < v - - y x , , I d a ~ i o b a l name~ "h~deO0 . . . . , h ~ d e Z Z " CSUNIQUE QXQX -- y L c l c s l o c a l ~ame& " Q X Q X 0 0 , . . . , Q X Q X Z Z " c S v i s £ b l , : p ~ o t l , p l o t 6 c a r ( c S w ~ i b l e ~ u b c a l DRAW,HOVE

name~ o[: u c S v l ~ x b [ o e a r n a r e n o t p r o c e s s e d t n a n y way

n o t e , The c a ~ e o f t h e o p t i o n k e y w o r d s doe~ no t m a t t e r . The c a s e o f t h e p a r a m e t e r b i~ p r e s e r v e d t t l r o u g h t ) u t t i l e

p r o c e s ~ ~n~.

BUG S : V a r i a b l e nome~ a r e c a ~ e dependent.

I f t b e r e ~ u l t l n g name t l o m p r o c e e d i n g a v a r i a b l e w i t h u n d e r s c o r e s

ks i e ~ s t h a n ~ lx c h a f e . C l e f s l [ w i l l u o t be c h e c k e d f o r c o n f l i c t i o n

w i t h o t h e r v a t i a b ) e s .

A u g u s t 1 9 ~

. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .

NESTING STURCTURE

P R ~ H longnam~" - - ~ i n r o u t i n e PUNCTION Lower - - maps a c h a i a c t t . r znto Low(.i c a s e

< FUNCTION t e ~ / a i p h a -- t r ue . t~ L e s t c h a r a c t e r [~ a l p h a b e t i c > < FUNCTION t e s t n u m e r x c - - t r u e i f t e a t c h a r a c t e r ks a d i g i t >

FONCTION e q u a l - - t r u e I f two s t r i n g ~ a r e e q u m l , n e g l e c t s c a s e FUNCTION i n l i s t - - t r u e i f name i a i n t h e l i s t FUNCTION h a s . . u n d ~ r ~ c o r e - - t r u t i f Dame ha~ a n u n d e r ~ c o r ~ FUNCTION p u t _ l n _ l z s t - - p u t s na~," t n a p p r o r x a L e l ~ $ t i f t t 1~ n o t t h e t e

FUNCTION g e / v a r - - g e t s a v a r i a b l e name

FUNCTION lind_subset -- L~u,. ~ s,*b~[r~ug Is found ~ t~.s} ~tr£nK

FUNCTION ~ezltn*. -. ~e~ a {{n,' from s~amdard zapu~

PROCEDURE g e n s y m t a b l t . . . . g e n e r a t e s a symbo l s t a r t ' t a b l ~ , PROCEDURE l u s t a l - - i t l s t a l s a ~ame i n t t i l e s y m b o l s t a t e : a b l , .

PROCEDU~ g e t n a m e ~ - - g e t ~ n a m e s t r o m d c i ~ t . a t e m e n t $ PROCEDURE s a y + . . n a m e - - ~av¢.s a v a r i a b l e name I n t h e a p p r o p r i a t e l i s t

PROCEDURE o u t p u t . d e f i n e s - * ~ u t p u t s the" d e f i t ~ e ~ t c ~ t a n d a r d o u t p u t PROCEDURE t r u n . a t v - - : i~l[)C;l:(.R .i txame, and ier.,)ve~ u n o , . r s c , , r e ~

PROCEDURE wr i t+ . , tn'w_DaGl," "" W l t t e ~ it t ln le lH l ' or mag : : i e :~am,"

PROCEDURE p r _ o p t l o n -- p re( :ews op t I on ca rdm PROCEDURE i n i t i a l i z e - - t u z t l a l l z v a l l c o n s t a n t v . i r l a b ] , ' ~ ;

FUNCTION c h e c k _ d c l - - t r u e i f s t a t e m e n t i s a d c l FUNCTION c o n t i n u e d - - t r i t e z f s t a t e m e n t i~ c o n t t n u e ~

. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . ~ . . . . . . . . . . . . . . . . . . . . . . . . . ~ . . . . . . . .

{ n e x t I * ~ l o h e r t t ~ t h e c o r ~ s t a n t ~ arid u t i l i t i e s ot t b e S o / t w a r e t o o l s [ i n h e r i t { ' ~ t e r l : [ b l lb .~( , f t t o o l . e n v x r o n ] g I o b d e f ~ .ellV" ) ]

P R ~ l o ~ n m m e ( a n p u t . o u t p u t ) a { i l l . i l l ; a ~ ~ t ~ t t t t t t ~ i t t ~ t t t t t t i t l i t t ~ t t ~ I t t t t ~ t t ~ t t w t t ~ l t t t t ~ t t ~ t t

CONST MAJ[YARLEN 32;

MA~LIST - 1296;

CARDLENGTH 72; MAX~TRIN(; 81;

SY~M~ABSIZE tO0;

PR_USCORE " TRUE; STDSIZE = b;

COL6 6; PREFIXLEN " ~

a r b t t r a y m a x i m u n v a r i a b l e l e n g h t ) max imum n u m b e r o t u n i q u e nam eg } I , * n g t b o t c a r d t o s c a n } m a x i m u ~ st r ~ n g L~ngLL ~' ~ t Z v o[ symbo~ s ~ a t e t a b l e }

t r u e --> p[oc~s under~core~ }

standard vorlabD, name szzv }

culumn 6 } u n i q u e name p r e f i x length }

150 Adv. Eng. Software, 1985, Vol. 7, No. 3

Page 10: VAX Fortran to Fortran 77 translator

TYPE namestr c h r i s t t . _ l l s ~ t _ v a r l ~ s t t _ . n a m e l i s t

w a r card : s t r i n g ; e n d _ d c l : z n t e g e r ; i n _ s i x l i s t : 0 . . ~ X L I S T ; n a m e l i s t : t _ n a m e l z s t ; i n v s ¢ l i s t : O..MAXLIST; v i e _ l i s t : t _ v a r l i s t ; v i s l i s t c t : z n t e g e r ; s i x c h a r l i s t : t _ v a r l z a t ; l a s t w a s d c l : boolean;

: p a c k e d a r r a y [ l . . ~ A X V A R L E N ] o f C~ARACTER; - s e t of 0 . . 1 2 7 ; { C~L~RACTER - eodfile } - ( G L O B A I . , I . O C A L , V I S I B I . E L I S T , S I X I . I S T ) ; : a r r a y l l . . ~ A X L l g T ] of n a m e s t r ; ~ a r r a y l l . . , ½ A X L l g T l o f r e c o r d

s c o p e : t _ l i s t ; t x t : n a m e s t r ;

e n d ; { r e c o r d }

l i n e of f o r t r a n code } e n d o f dcl name } c u r r e n t n u m b e r i n s t x _ c h a r _ l i s t } record of l o n g names a n d scopes } c u r r e n t n u m b e r in namelist } g l o b a l names n o t to be c h a n g e d } c u r r e n t n u m b e r i n v i a _ l i s t } l i s t of s i x c h a r . v a t . n a m e s } c o n t i n u a t i o n c a r d f l a g }

s y l l a b l e m o d u l e _ f l a g : b o o l e a n ; DEBDG : b o o l e a n ;

{ s t r i n g c o n s t a n t s } s r e a l : namestr s i n t g r : n s m e s t r s l g c l : n a m e s t r I cmp l x : n a m e s t r ; s b y t e : n s ~ e s t r ; s d b l e : n s m e s t r ; s c h a r : n a m e s t r ; s f n c t n : namestr; s co~ ~ namestr; subr tn : namestr;

de fs t r ; namestr;

( opt ion s~rings ) sdebug n a ~ s t r ; v i s i b l e n a ~ e . t r ~ mo~mle n a m e s t r ; unique n a m e m t r ; g l o b _ p r e f l x n ~ e s t r ; l o t _ p r e f i x n ~ e s t r ;

delimiters alpha alp~nu~er~c

: a r r a y [ L E T A . . L E T Z , I . .SYHTABSIZE] of i n t e g e r ; { t r u e if m o d u l e option xs i n v o k e d } { t r u e - - > w r i t e o u t d z a g n o s t i c s }

resl } z n t e g e r ) l o g i c a l ~ c o m p l e x } b y t e } d o u b l e p r e c i s i o n ) c h a r a c t e r } function ) c o - - o n } s u b r o u t i n e )

define - - f o r o u t p u t }

{ p r e f i x f o r g l o b a l n a m e s } { p r e f i x f o r l o c a l n a ~ e s }

c h r s e t ; { o n a s ~ l l e r ~ c h i n e t h e s e } c h r i s t ; { s e t s c o u l d be s l d e s m a l l e r } c h r s e t ; { t h a n t h e f u l l a s c i i s e t i f n e c e s s a r y }

( * * * * * * * * * * * * * * * * * * * * * * g e n e r a l t e s t f u n c t i o n s * * * * * * * * * * * * * * * * * * * * * * * }

{1 . . . . . . . . . . . . . . . . . l o w e r . . . . . . . . . . . . . . . . . } FUNCTION l ~ e r ( i n _ c h : CIL~RACTER) : CHARACTER; { r e t u r n s a i n l o w e r case } { a s s u m e s d i f f e r e n c e b e t w e e n u p p e r ~ l o w e r c a s e i s a c o n s t a n t } v a t c h : CHARACTER; B e g i n { l o w e r )

i f i u _ ¢ h i n [ o r d ( ' A ' ) . . o r d ( ° Z ' ) ] t h e n c h : - i n c h ÷ o r d ( ' a ° ) - o r d ( ' A ' ) _

e l s e ch : - i n c h ; l o w e r : - c h ;

E n d ; { l ~ e r }

( ~ <><><><~<><><><><><><><><><><><><><><><><><><><><><><><><><><><><>

{ t h e f o l I ~ i u g 2 r o u t i ~ s a r e ~ l o n g e r u s e d b u t c a n be u s e d ) ( i n p l a c e o f t h e s e t s " ~ [ p h a " a n d " a I p h a n ~ e r i c " [ n came t h e } ( a a c h £ ~ t h i s £s ~ p [ ~ ¢ e d o n d o s e n o t a l [ ~ m a t s c h a t b~g }

( I . . . . . . . . . . . . . . . . . t e s t a l p h a . . . . . . . . . . . . . . . . . ) FUNCTION [ e s c a I p h ¢ ( c h : C ~ C ~ R ) : b o o l e a n ; { t e s t [ [ a c h a r a c t e r i s a n a l p h a a s s u m e s c o n t ~ n i o u s } ( a n d s e q u e n t i a l c h a r a c t e r s e~ } ~ g £ n { t e s t a l p h a }

t e s t a l p h a : - ( l o ~ e r ( c b ) i n [ o r d ( ' n ' ) . . o r d ( ' z ' ) ] ) ; E n d ; ( t e s t a [ p h a }

{I . . . . . . . . . . . . . . . . . t e n t h , e r i c . . . . . . . . . . . . . . . . . } FUNCTION c e a t o ~ e r £ c ( o h : C ~ E R ) : b o o l e n n ; ( t e s t £f a c h a r a c t e r i s n ~ e r [ c n s s u m e s c o a t £ n ~ o u s } { a n d s e q u e n t i a l s e t o f n u m b e r s } B e g i n { t e s t n u ~ e r i c }

t e s t n u m e r i ¢ : - f a l s e ; i f ( o h i n [ o r d ( ' 0 " ) . . o r d ( ' 9 " ) ] ) t h e n c e s t n ~ m e r £ c : - ~ r u e e l s e [ f ( c h - U ~ E R L I ~ E ) a n d (PR_USCORE) t h e n t e s t n u ~ e r i c : - t r u e ;

E n d ; { t e s t n u m e r t c } { < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > < > ~ )

{I . . . . . . . . . . . . . . . . . . . s e q o s l . . . . . . . . . . . . . . . . . . . . . . } ~ u n c t i o n s e q u a l ( w a r e a r l , s i r 2 : n a m e s t r ) : ~ o l e a n ; ( ~he p r o g r a ~ i n g e n e r a l £s c a s e d e p e n d e n t boa t h i s { r o u ¢ £ ~ i s o n l y u s e d w i t h t h e o p t i o n c a r d s , £n { w h i c h c a s e ~he c a s e d o s e ~ m a t t e r , t h e r e f o r e t h i s

( f u n c t i o n ~ g l e c t s t h e c a s e o f t h e s t r i n g s t e s t e d

v a t i : i n t e g e r ;

b e ~ i ~ { e e q ~ l } i : - 1 ; ~ b i l e { l o n e r ( e a r l [ i l l - l ~ e r ( e t r 2 [ i ] ) ) a n d ( s t r i [ i ] <> E N ~ ) do

i : " i + I ; s e q u a l : - ( l o ~ e r ( s c r l [ i J ) - I o w e r ( s t r 2 [ i ] ) ) ;

e n d ; { s e q u s l )

(1 . . . . . . . . . . . . . . . . i n l i s t . . . . . . . . . . . . . . . . . ) F U N ~ I O N i n l i s ~ ( n ~ e : n a m e s ~ r ;

l i a r : t _ v a r l i s t ; l i s c _ s i : ~ : i n t e g e r ) : b o o l e a n ;

( d e c e r a i n s i f t h e name i s i n ~he s p e c i f i e d l i s t l i s t ) v a t j , i : i n r e g e r ;

f l a g : b o o l e a n ; B e g i n ( i n l i n t }

t : " O; r e p e a t

i : " i ÷ 1 ; f l a g :- t r u e ; j : " 1 ; w h i l e ( j < 8AKVARI, EN) a n d ( n a m e [ j ] <> ENDSTR) a n d f l a g do b e g i n

i f n a m e [ j ] <> l i s t [ i , j ] t h e ~ f l a g : - f a l s e ;

j : - j + l ; e n d ; { w h i l e }

u n t i l ( i >= l i s t _ s i z e ) o r f l a g ; i n l i g t := f l a g ;

E n d ; ( i n l i s t }

( I . . . . . . . . . . . . . . . ham_underscore . . . . . . . . . . . . . . . . . . . . )

EUNCTION ham_underscore(name : namestr ) : boo lean ; { r e t u r n s t r u e i f s name h a s a n u n d e r s c o r e i n i t ) va t j : i n t e g e r ;

flag : boolean; g e g i n { ham_underscore }

j :- O; f l a g : - f a l s e ; repeat

j : - j . l ; i f n a m e [ j ] " UNDERLINE t h e n f l a g : " t r u e ;

until (name[j} = ENDSlIt) or (flag); h a m _ u n d e r s c o r e : - f l a g ;

End; ( has_underscore }

(1 . . . . . . . . . . . . . . . . . . . . . . . . . p u t _ i n _ l i s t . . . . . . . . . . . . . . . . . . . . . ) procedure p u t _ i n . _ l i s t ( n a m e : names t r ; l t y p e : t _ l i s t ) ;

( pu ts m ~ i n the s p e c i f i e d l i s t i f i t is not i l r e a d y t he re ) { INPUTS u~me - - name t o be p u t i n l i s t ) ( l t y p e - - l i s t t y p e , d e t e ~ i n e s w h i c h l i s t name g o e s i n } vat i,j : i m t e g e r ;

f L s g : b o o l e s n ;

b e g i n came l t y p e o f

LOCAL, GLOBAL : begin

i :-0; r e p e a t

i : - i * l ; f l a g : - t r u e ; j : - l ; while (j < ~ V A ~ L F ~ ) and

(name{j] <) END$~) and flag do begin if uame[jl <> namelist[i].txt[j] then

flag :" false; j :=j ÷I;

end;{ while } { if flag makes it through the while and is } { s t i l l t r u e then t h e ~ m e was i n the l i s t }

u n t i l ( i > - i n v a t l i s t ) o r f l a g ; i f n o t f l a g t h e n b e g i n

i n v a t l i s t : " i n v a t l i s t * I ; n a m e l i s t | i n _ v a t _ l i s t ] . t x t : - n ~ a e ; n a m e l i s t [ i u . _ v a r _ l i s t ] . s c o p e : - I t y p e ;

e n d ; { i f n o t f l ag } e n d ; { l o c a l , g l o b a l }

S I X L I S T : b e g i n i f not i n l i s t ( n ~ m e , s i ~ _ c h a r _ l i s t , i n _ s i x l i s t ) t h e n b e g i n

i n _ s i x l i s t : - i n _ s i x l i s t * 1; six c h a r l i s t [ i n _ s ~ x l i s t ] : - n a m e ;

e n d ; { i f ) end; ( s i x l i s t }

V I S I g L E ~ I S T : b e g i n i f n o t i n l i s t ( n a m e , v i s _ l i s t , v i s _ l i s t _ e t ) t h e u b e g i n

v im l i s t c t : - v im l i s t c t + 1 ; v i a _ l i s t [ v i e _ l i s t _ e l ] : - n a m e ;

e n d ; { i f } e n d ; { v i s l i s t }

e n d ; { c a s e } e n d ; ( p u t _ i n _ l i s t }

(1 . . . . . . . . . . . . . . . . . . . . g e t v a r . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . } f u n c t i o n g e t v a r ( v a t s : s t r i n g ; v a t v a r s t a r t : i n t e g e r ;

v a t o u t : n a m e s t r ; v s r l e a : i n t e g e r ) : i n t e g e r g e t s s v a r i a b l e name d e l i m i t e d by w h i t e s p a c e o r a c o ~ a . a s s u m e s v a r i a b l e name s t a r t s w i t h I n a l p h a c h a r a c t e r . INPUTS s - - e a r i n g t o g e t v a r l a h l e f r o m

v s r s t a r t - - s t a r t l o o k i n g f o r v a r i a b l e

OUTPUTS o u t - - v a r i a b l e n a ~ e f o u n d , t e r m i n a t e d w i t h a ENDSTR c h a r a c t e r .

l e u - - l e n g t h o f v a r i a b l e o b t a i n e d v a r s t a r t - - f i r s t c h a r o f t h e v a r i a b l e

i ~ T ~ I $ o~e o f t h e t o l l o ~ i u ~ i n t e g e r s - - t h e p o l i t i o n o f t h e f i r s t d e l ~ i t i n g c h a r a c t e r

a f t e r t h e v a r i a b l e - - 0 i n d i c a t e s l a s t v a r i a b l e o n l i n e was g o t t e n - - -1 i n d i c a t e s no v a r i a b l e was g o t t e n a n d s o l

v a t j , t p , i : i n t e g e r ;

b e g i n ( & e t ~ a r }

i : - v l r s t a r t ; w h i l e ( n o t ( s i l l i n a l p h a ) ) a n d

( s [ i l <> ENDSTR) a n d ( i < - I~KSTBING) do i : - i + 1 ;

v a r s t a r t : - i ; j : - l ; w h i l e ( s [ i ] i n a l p h a n u m e r i c ) d o b e g i n

o , t i j l : - , [ i ] ;

Adv. Eng. Software, 1985, Vol. 7, No. 3 t[[1

Page 11: VAX Fortran to Fortran 77 translator

L : - k + l ; j : - j ¢ 1

~ n d ; ( ~ h i l e }

o u t [ j l : - Eb~)ST~; t p : - i ; l e n : " j - l ;

i f n o t ( * [ i l ; n d e l i m i t e r s ) t h e n b e g i n m e a s a g e ( ' G E ~ t A R : i l l e g a l c h a r a c t e r in v a r l a b l e h a m s ' ) ; p u t s t r ( a , S ~ D O U T ) ;

e n d ; { i f oat i n d e l i m i t e r ~ }

{ see i f v a r i a b l r i s t h e l a s t one on t h v i u : , ' / w h i l e ( n o t ( s [ i ] in a l p h a ) ) and

( i < ~{AXSTRING) and ( s i L l <> ENDSTR) do t :- t ÷ ~;

I f ( s [ x [ = ENDSTR) th,,n ~t ( j > 1) t h e n getvar : : 0 { l a s t w,~rd on ~l t : r } e l s e g e t v a r := -'1 { no word ,~n [ l u r ~

e l s e g e t v a r : - r p ; { gains Wt'[~; ~I: [l:c : It;'* •

i t d e b u g t h e n b e g i n wr i te ( 'gETVAR: v a r " " i ; t := l ; r e p e a t

w r i t e ( o u t [ ~ l ) ; i : - i + 1;

u n t i l ( o u t { ~ ] " ENUSTR) o r l i " ~ X V ^ R I . E N ) ;

~ r t t e l n , e n d ; { d e b u g )

e n d ; { g e t v a r }

{1 . . . . . . . . . . . . . . . . . f t n d _ s u b s t r . . . . . . . . . . . . . . . . . } FUNCTION f i a d _ s u b s t r ( s t r : s t r i n g ; s u b s t r : n a m e s t r ;

~ u b l e n : ~ n t e g e r ; ~a~ ~ n d s ~ b ~ t r : l n t e g e r ) : b o o l e a n ;

S e a r c h e s f o r # s u b s t r in t h e a r t I n p u t . I f a c h a r a c t e r f a l l s t h e s e a r c h t s c a r r i e d out u s i n g t h a t c h a r a c t ~ . r and s h i f t i n g t h e window p o s i t i o n . When a c h a r a c t e r I s marcher% t h e c o m p a r i s o n s c o n t i n u e and wrap a r o u n d t h e window. D i s r e g a r d s t h e cane of b o t h the s t r i n g ant* t h e s u b s [ r i n g . R e f . "Ads f o r r i p e r | a n t e d P r o g r a m ~ . r s "

v a t m a t c h e d : i n t e g e r ; wpos : i n t e g e r ; s u b l n d ¢ ' t l n t e g e r ~ f l a g : b o o l e a n ;

Beg~n ( f i nd s u b s t r } m a t c h e d : - O; wens := O; s u b i n d e x : " l ; f l a g := l a l s e i e n d s u b a t r := 0; w h i l e ( m a t c h e d < s u b l e n ) a n d

( s t r ] w p o s ÷ s u b i e n ] <> ENDSTR) and ( ( u p o s ¢ s u b l e n ) < HAXSTRIN(;) do

i f l o w e r ( s t r [ w p o s + a u b i n d e × [ ) " l o w e r ( s u b s t r [ s u b z n d e x [ ) t h e e b e g i n m ~ t c h e d : - m a t c h e d ¢ l ; s u b i n d e x := s u b i n d e x mod s u b l e n + 1;

end vlb~. Dt~l l l

m a t c h e d := 0~ wpos : - wpus ¢ ; ,

e n d ; { i f } I I t a~ tched - su b l e f l t h e n b e g i n

f l a g :" t r u e ; r n d s n b s t r : - wpos + s u b l e n ;

~nd ~ l i n d s t l h s t r : - t la~x;

gi ld; { t l n d _ s u b s t t }

* * * * * * * * * * * * * * * * * * * * * * t : ,p I r v , , l p r o r s * * * * * * * * * * * * * * * * * * * * * * * * * *

{1 . . . . . . . . . . - . . . . g e n s y m t a b l , . . . . . . . . . ~ . . . . . . . . . ' PRC)CEI)I:R~ g e n s y m t a b ~ P , ~ g e n ( ' r a t v tL~' ~ y m b ~ ~,t.,~, (aD~t ' f

v a t ] : i n t e g e r ; p t : ~ n t e g r r ; { t a h l , , p , } l n t ~ r t ( 'h : CHARACTERs

*2 . . . . . . . . . . i n s t * l . . . . . . . . . . . ~ PROCEIXJRE I n s t a l ( s y m b o l : n a m e s [ i ) ;

{ I n n [ a l l • l y r i c a l tn t h e symbol s t a t e t a b l e ) v a t t r i t e , l a t t t t a t e , l : i n t e g e r ; * w a r a i u g : w i l l not work t a r tram[, b e i n g s u b s e t of a n o t h e r name I

~ e g i n { i u • t a l } ~ : " 1; l a s t s [ a t e := 1; s t a t e : " ~ y m L a b l e [ s y m b o l [ l } , l a s t s t a t e ~ i

while s t a t e >* 0 do b e g ~ n I : " x ~ 1; l a l t s t a t e : - s t a t e ; s i l t s :~ s y m t a b l e [ s y m b o l [ l ] , l a s t s t a t e ] ;

e n d ;

s y m t a b l e [ s y m b o l [ l [ . l l s t s t a t ~ ' l :~ p t ¢ l , w h i l e s y m b o l [ i ] <> ENDSTR do b e g i n

g y m [ a b l e [ s y m b o l [ i ] , p t : - p t ¢ l ; pt :~ pt ÷ I ~ ~ : = t e l ;

e n d ; s y m t a b i e [ s y m b o l [ i - l ~ . p t - I ~ ') ,

End ; { i n s t a l }

B e g i n { g e o a y m t a b l r } pt := I ;

152 Adv. Eng. Software, 1985, Vol. 7, No. 3

{ l n i t t a l ~ z e t h e symbol t a b l e t o minus I ) f o r j : - I t o SY~ABSIZE do

f o r ch : " o r d ( ' a ' ) to o r d ( ' z ' ) do s y m t a h l e [ c b , j ] : - - l ; { i n i t i a l t z e }

{ put k~y ~ords into tho table }

i n ~ t a l ( s r e a l ) ; i ~ t a l ( s ~ n ~ r ) ~ i n a t a l ( s c m p l x ) ~ i n ~ t a l ( s l g c l ) ; ~ n s t a l ( s b y t e ) ; i n ~ t a l ( s d b l e ) ; i n ~ t a l ( s c h a r ) ; ~ o ~ t a l ( ~ f o c t n ) ; i n s & a l ( s c o m m ) ; ~ n s t a l ( s n b ~ t n ) ;

~ n d ; * o f ~ e n s y s m b o l t a b l e )

( l . . . . . . . . . . . . g e t names . . . . . . . . " . . . . . . . . . . . } PROCEDURE i s * n a m e s ( c a r d : s t r i n g ; / , t r l l l~ t ,gcr J ~ { get~ t h v na~e~ o ~ the ~cl l ~ e a~c put~ the~ ~u ~h,. { a p p r o p s e a t e ] l E t , { INPUTS c a r d - - s t r ~ n g ,~t (~,rtran ~ourcv codv ( p t r p o s i t i o n a t enc a t d c l k e y w o r d

v a t c o u n t , I : i n t e g e r ; s a v e d : b o o l e a n ; name : n a m e s t r ; g p t r : i n t e g e r ; ( p o s i t i o n p o i n t e r ) p t b e g i n : i n t e g e r ; ( b e g i n ~ n g p o i n t of a v a t . name p t e n d : i n t e g e r ; ( e n d of v a r x b l e name }

( 2 . . . . - - . . . . . . . . . L i v e _ n a m e . . . . . . - . . . . . . . ~ . . . . . . ) PROCEDORE Dave_name(name : n a m e s * r ; l e n : z n t e g e r ; I L y p e : ~_ l i s t ) ; ( s a v e s a name i n t h e a p p r o p r i a t e l i s t ~f i t zs not a l r e a d y t h e r e } ( Uses a s e q u e n t i a l s e a r c h t h r u t h e l i s t tu ~znd t h e ~ame. } ( ~NPUT$ na~e -~ name tO be aa~ed. } { Inn -- length of name to be saved. } { itype -- Izat type. }

v a t u f l a g : b o o l e a n ;

Begin { Dave" nlme }

nflag :: (hms.underscore(name) and PR ~SCORE): if (Inn > stdsgze) or *uflag) then put. in. llst(uame,ltyp~.) else if (Itype " global) and module flag and

( not inlzst(name,vis_list,vzs..list _<t ) ) then p n t _ i n _ l i s t ( n a ~ e , g l o b a l )

e l s e i t ( ~ e n - s t d s i z e ) a n d no t u f l a g t h e n p u t _ i n _ l i a t ( n i m e . s z x l i s t ) ;

End; ( sa~e_~ame }

Beg~n { I S * n a m e s )

{ g p t r comes b a c k a s 0 or t h e p o s i t i o n of t h e end of t h e s u b s t r } i f f i n d a u b s t r ( c a r d , s f n c t n , 8 , g p t ~ ) t h e n b e g i n

l a a t w a s d c l : - f a l s e ; p t~ : - g p t r * 1; i t g e t v a r ( c a r d , p t r , n l m e , c o u n t ) >~ 0 ~h~n

s l v e . _ ~ a m e ( n a m e , c o u n t , g l o h a l ) ; e n d ( i f t h e ~ }

e l s e z! f i n d s u b s t r ( c a r d , s u b r t n , 1 0 , g p t r ~ t h , ' n ~,,.gln l a s t w a s d c l : - f a l s e ; p t r := g p t r ¢ 1; i f g e t v a r ( c a r d , p t r , n a m e , e o u n t ) - 0 t h e e

save name(t.ame,count,g!obal)~ e n d { e l s e If

e l s e begin coutlt : - C. pi t . rid : , pe t * p o s ~ t t o t : a l t e r , h t . ~ k . d ~ t

v h i l e p t r > O do b e g i n p t b e g l t ~ := p t e n d ; p t r : - g ~ t v a r ( c a r d , p t b e g l n , n a m e , c o u n t ) ~

xf p t r > 0 t h e n p t e n d :o p t r

c i t e F r e u d : - p t b e g g n * c o u n t ;

l i v e d :~ false; i e p e i ~

i f c l r d [ p t e D d ] - SLASN t h e n b e g i n ( c o ~ = o u b l o c k ~sme )

a a v e _ o a m e ( n a m e 0 c o u n t o g l o b a l ) ; s a v e d : - t r u e ;

e n d e l s e zf c a r d [ p t e n d ] - LPAREN ~hen b e g z n { a n a r r a y ie b e £ n g d e c l a r e d , o n l y need t h e namr }

s a v e _ n a m e ( n a m e , c o u n t . l o c a l ) ; s a v e d := t r u e ; j : - pten~;

repe~ j :'~.I;

until (card[j] = ENDSTR) or (card[j) - RPAREN) ~ (j >- ~XSTRING • ~)~

gg card[j] - RPAREN the~ ptend :-)

else if card(j] - ENDSTR [hen ptend :~ j "" I~

end;

p~eud :- p~end • ~; until (cmrdlptend} " Eh~STR) or

(car~Ip&e~d] in alpha) or (¢tend >- ~ING);

£~ not eared then aave_~ame(n~me,couu~,~ocal};

Page 12: VAX Fortran to Fortran 77 translator

end; { while } end; { if find_substr... }

End; { getnamee }

{I ....... - ............ output_defines . . . . . . . . . . . . . . . . . . } PROCEDURE output_defines;

generates a table of defines to be used with the macro processor t h e defines are written t~ standard output global names not in the visible list are mapped into sequential unique names using "gloh_.prefix". local nares are truncated. If truncation causes a conflict then a new name is generated using "loc~prefix". code is supplied for handleing underscores, but must be activated at compile time with the constant "PR_USCORE"

CONST MAXSUFCHAR - 36; { 0..9,A..Z }

TYPE sufix~cntr = record s|,s2 : integer; { counters for the last 2 chrs.

end; { record }

v a t i , j : i n t e g e r ; tname : uamestr; g v a r , l v a r : s u f i x _ c n t r ; c h _ c t r : CHARACTER; ( c h a r a c t e r c o u n t e r } s u f i x : a r ray[I . .HAXSUFC~AR] of CMARACTER; { used to g e t t he l a s t two c h a r a c t e r s o f the u n i q u e name }

{2 " = ' = " . . . . . " - = ' ' ' ' ' " t r u n c a t e - - - - - - - - - - - - - - - - - - - - - - - - - - } ~rocedure t r u n c a t e ( i n n a m e : n a m e s t r ; v a r outname : n a m e s t r ) ;

T r u n c a t e s a name to the STDSIZE and t a c k s a ENDSTR on t h e end . I f a name ha s u n d e r s c o r e s and t h ey a r e to be p r o c e s s e d they a r e removed and the result is truncated if it is still > STDSIZE BUG: does not check for conflict with names shorter than six

c h a r a c t e r s . C o n f l i c t c o u l d o c c u r i f r emoving t h e u n d e r s c o r e s g e n e r a t e s a name s h o r t e r t h a n s i x c h a r a c t e r s t h a t a l r e a d y e x i s t in t h e fortran s o u r c e c o d e .

INPUTS inname - - name to be t r u n c a t e d , can have u n d e r s c o r e s OUTPUTS outname - - t r u n c a t e d name e n d i n g w i t h a ENDSTR

v a t j,k : i n t e g e r ; b e g i n

if PR_USCORE then begin i f h a s _ u n d e r s c o r e ( i n n a m e ) t h en b e g i n

k :" 0; j := 0; r e p e a t

j : - j ÷ l ; if inname[j] <> UNDERLINE then begin

k :- k + 1; i n n a m e [ k ] := i n n a m e [ j ] ; { j >- k so use same v a r i a b l e }

end; { xf inname } u n t i l ( j = MAXVARLEN) or (inuame[k] - ENDSTR);

e n d , { if h a s _ u n d e r s c o r e } end; ( i f PR_USCOEE )

j :'0; r e p e a t

j : - j ÷ l ; o u t n n m e [ j ] : - i n n a m e [ j ] ;

until (j - STDSIZE) or (outname[j] - ENDSTR); if outname[j] <> ENDSTR then

outname[STDSlZE + I] := ENDSTR; en d ; { truncate }

{2 ................... write_new_name . . . . ~ .............. } PROCEDURE write new name(prefix : n a m e s t r ; v a t s u f c t r : sufix_cntr);

generates a unique name for a variable name using t h e user supplied prefix, o r the default prefix. INPUTS prefix -- first part of new name

sufctr -- counters for the last two characters of the new name.

OUTPUTS sufctr -- incremented by i

v a t j : i n t e g e r ; gegin ( ~rlte new ~me }

f o r j := l t o PREFIXLEN do p u t t ( p r e f i x [ j ] ) ; p u t c ( e u f i z [ e u f c t r . s l ] ) ;

p u t c ( ~ i z [ s u f c t r . e 2 ] ) ; • ufctr.~2 : " sufctr.s2 + l; i f s ~ f c t r , e 2 = ~AXSUFC~L~R+I t h en b e g i n

s u f c t r . s 2 :- O; s u f c t r . s l :- s u f c t r . s l + 1; if s u f c t r . s l > MAXSUFCHAR t h e n

m e s ~ a g e ( ' T o o many u n i q u e v a r i a b l e s r e q u i r e d ' ) ; end ; { i f e u f c t r . . . }

End; { write new name }

g e g i n { o u t p u t _ d e f i n e s } g v s r . s l := 1; g v a r . s 2 :~ 1; l v a r . e l := l ; I v a r . s 2 : " 1;

( i n i t i a l i z e sufix a r r a y } i : - 0; f o r c h ~ c t r : - ord('0") to ord('9") do begin

i : - i + I; s u f i x [ i ] : " c h _ c t r ;

end ; ( f o r ) f o r ch._ctr := o r d ( ' A ' ) to o r d ( ' Z ' ) do b e g i n

i :- i + 1; sufix[iJ : - c h _ c t r ;

end ; { f o r )

for i : - I to in war l i s t do b e g i n

j : " I ; r e p e a t

p u t c ( d e f s t r [ j ] ) ; j : - j + 1 ;

until ( d e f s t r { j / " ENDSTR) or ( j " b~XVARLEN); puCc(LPAREN);

j : - 1; repeat

putc(namelist[i].txt[j]); j : = j ÷ l ;

until ( j >- MAXVARLEN) or (namelist[il,txt[j] - ENDSTR ); putt(COMMA);

if (namelist[i].scope - GLOBAL) and (module_flag) then begin { names in the visible list were never saved in namelist }

write new name(glob_pref ix,gvar); end { if global }

else begin truncate(namelist[i].txt,tname); if inlist(tname,six char list,in_sixlist) then

write new name(loc~ref ix,lvar) else begin { put truncated name in the six char list }

in_sixlist :- in._sixlist * I; s i x char list[in sixlist] := tname;

( write out truncated name ) j : - 1 ; w h i l e ( t n a m e [ j ] <> ENDSTR) and ( j < HAXSTRING) do b e g i n

p u t c ( t n a m e [ j ] ) ; j :- j + I;

end; ( while }

end; { e l s e } end ; { e l s e }

putc(RPAREN); putc(NEWLINE);

end ; { f o r i :- I to in vat list } End; { output_defines }

{I ~ . . . . . . . . . . . . . . p r _ o p t i o n " .................. } PROCEDURE pr_option(card : string); war opt~os,lp,len : integer;

s o u r : aamestr;

B e g i n { p r _ o p t i o n ) o p t _ p o e : " 3 ; l p := g e t v a r ( c a r d , o p t _ _ p o s , s o u t , f e n ) ;

if s e q u a l ( s d e b u g , s o u t ) t h e n b e g i n i f g e t v a r ( c a r d , l p , e o u t , l e n ) >=0 t h e n b e g i n

i f sour[l] i n [ o r d ( ' t ' ) , o r d ( ' T ' ) ] the~ DEBUG :" t r u e

e l s e DEBUG := false; end ; ( if getvar... }

end ( if sequal }

e l e e if s e q u a l ( m o d u l e , s o u t ) t h e n b e g i n m o d u l e _ f l a g := t r u e ; i f g e t v a r ( c a r d , l p , e o u t , l e n ) >- 0 t h e n g l o b ~ p r e f i x : - s o u r ; i f DEBUG t h e n w r i t e l n ( ' P R _ O F T l O N : module c a r d f o u n d ' ) ;

end

e l s e if s e q u a l ( u u i q u e , s o u t ) t h e n b e g i n if getvar(card,lp,sout,len) >ffi 0 then Ioc~refix := sour; if DEBUG then writeln('PR_OPTlON: unique card found');

end

else if sequal(visible,sout)then b e g i n repeat

Ip :- getvar(card,lp,sout,len); if (Ip >= O) then

put_in_list(sout,VISIBLELlgT); until (Ip <" O) or (vis list ct >= MAXLIST); if DEBUG then writeln('PR_OPTlON: visible ca rd found');

end;

End; { p r _ o p t i o n )

( l .................. initialize .................... ) PRO~EI~ initialize; ( i n i t i a l i z e s e l l c o n s t a n t s } ~ e g i n

d e l i m i t e r s :- (BIA[~,COI~4A,LPAREN,Eh'DSTR,NE~LINE,SLASH,STAR,T&B|; alpha : " ~ o r d ( ' a ' ) . . o r d ( ' z ' ) , o r d ( ' A ' ) . . o r d ( ' Z ' ) J ; alphanumeric : - l o r d ( ' 0 " ) . . o r d ( ' 9 " ) ] + a l p h a ; i f PR._USCORE then a l p h a n u m e r i c := a l p h a n u m e r i c ÷ [UNDERLINE];

s t e a l [ I ] : , o r d ( ' r ' ) ; s r e a l [ 2 ] : - o r d ( ' e ' ) ; s r e a l [ 3 ] := o r d ( ' a ' ) ; s r e a l [ 4 ] := o r d ( ' l ' ) ; s r e a l [ 5 ] := ENDSTR;

s i n t g r [ l ] := o r d ( ' i ' ) ; s i n t g r [ 2 ] := o r d ( ' n ' ) ; s i u t g r [ 3 ] := o r d ( ' t ' ) ; s i n t g r [ 4 ] := o r d ( ' e ' ) ; s i n t g r [ b ] : " ord('g'); s i n t g r [ 6 ] := o r d ( ' e ' ) ; s i n t g r [ 7 ] := o r d ( ' r ' ) ; s i n t g r { 8 | : " EMDSTR;

• c m p l x [ l ] : - o r d ( ' c ' ) ; s c m p l x [ 2 ] := o r d ( ' o ' ) ; e cmp lx [3 ] :- ord('m'); s cmp lx [4 ] :- o r d ( ' p ' ) ; s cmp lx [5 ] : - o r d ( ' l ' ) ; s c m p l x [ 6 ] : = ord('e'); s c m p l x [ 7 ] : - o r d ( ' x ' ) ; s c m p l x [ 8 ] : " ENDSTR;

s l g c 1 [ l ] : " o r d ( ' 1 " ) ; s l g c l [ 2 ] :" o r d ( ' o ' ) ; slgcl[3] := ord('g'); s l g c l [ 4 ] : - o r d ( ' i ' ) ;

Adv. Eng. Software, 1985, Vol. 7, No. 3 153

Page 13: VAX Fortran to Fortran 77 translator

s l g c I [ 5 ] := o r d ( ' c ' ) ; s l g c l [ 6 ] := o r d ( ' a ' ) ; s l g c l [ 7 ] := o r d ( ' l ' ) ; slgcl[8] := ENDSTR;

sbyte[ll := ord(~b'); sbyte[2] := ord('y'); sbyte[3] := ord(~t~); sbyte[4] := ord('e');

sbyteI§] := ENDSTR;

sdble[II := ord('d') sdble[2] :- ord('o ~ ) sdhle[3] :~ ord(~u ") sdble[4] :- ord('b') sdble[5] :- ord('l')

sdble[6] :~ ord('e') sdble[7] := ord('p'); sdhleIS~ := ord(~r'); sdbleIg] := ord(~e'); sdble[10] :ffi ord('c'); sdble[ll] := ord('i'); sdble[12] := ord('s'); sable[13] := ord('i*); sdble[14l := ord('o'); sdble[15] :ffi ord('n'); sdble[16] := ENDSTR;

schar[ll := ord(*c~); schar[2] := ord('b~); schar[3] := ord('a'); schar[4] :ffi ord('r*); schar[5] := ord('a*); schar[6] := ord('c'); schar[7] := ord('t'); schar[8] := ord(*e'); schar[9] := ord('r'); schar[10] := ENDSTR;

subrtn[l] :- ord(*s'); subrtn[2] := ord('u'); subrtn[3] := ord('b'); subrtn[41 := ord('r'); subrtn[5} := ord('o'); subrtn[6] := ord('u'); subrtn[7] := ord(~t'); subrtn[8] := ord('i'); subrtn[91 := ord('n*); subrtn[lO[ := ord('e~); subrtn[ll[ := ENDSTR;

scomm[l] := ord('c'); sen=f2] := ord('o'); scoff31 := ord('m'); scomm[4] := ord('m'); scomm[5] := ord('o'); scomm[6] := o r d ( ' n ' ) ; s c o w l 7 ] := ENDSTR;

s f n c t n [ l } := o r d ( ' f ' ) ; s f n c t n [ 2 ] := o r d ( ' u ' ) ; s f n c t n [ 3 ] : - o r d ( ' n ' ) ; s f n c t n [ 4 ] := o r d ( ' c ' ) ; s f n c t n [ 5 ] := o r d ( ' t ' ) ; s f n c t n { 6 ] := o r d ( ' i ' ) ; s f n c t n [ 7 ] : - o r d ( * o ' ) ; sfnctn[8] :ffi o r d ( ' n ¢ ) ; sfnctn[9] := ENDSTR;

visible[l] := ord('v ~ ) visible[2] :ffi ord('i') visible[3] :ffi ord('s') visible[4] : - ord('i') visible[5] :- ord('b') visible[6] :- ord('l ~) visible[7] :ffi ord('e') visible[8] := ENDSTR;

module[if := ord('m*); module[2] := ord(*o'); m o d u l e [ 3 ] :ffi o r d ( ' d ' ) ; module[4] := ord('u'); module[5] := ord('l'); module[6] :~ ord('e'); module[7] := ENDSTR;

unique[If :- ord('u'); unique[2] :~ ord('n'); unique[3] := ord('i'); unique[4] := ord('q'); unique[5] :- ord('u'); unique[6] := ord('e'); unique[7] := ENDSTR;

sdebug[l] :ffi ord('d'); sdehug[2~ := ord('e~); sdebug[3] :- ord('b'); sdebug[4] := ord('u'); sdebug[5] := ord('g'); sdebug[6] := ENDSTR;

defstr[l] :- ord('d'); defstr[2] := ord('e'); defstr[3] := ord('f'); defstr[4] := ord('i¢); defstr[5] :~ ord('n¢); defstr[6] := ord('e¢); defstr[7] := ENDSTR;

{ default value of glob~refix for global names } gloh~refix[l] := ord('M'); glob~refix[2] := ord('O');

154 Adv. khg. Software, 1985, Vol. 7, No. 3

glob~refix[3] := ord('D'); glob~refix[4] := ord('U');

loc~refix[l] := ord('U'); loc ~refix[2] := ord('N'); loc~refix[3[ := ord('l'); loc~refix[4] := ord('O');

gensymtable; ( initialize symbol state table }

debug := false; lastwasd¢l :- false; { inltialize for continuation checking }

module_flag :~ false; in vat list :* O; ( initialize llst counters } in_sixlist :* O; vis__list_Ct := O;

End; { initialize )

{I ............. check dcl ................. } _

FUNCTION check_dcl(card : string; var end_dcl : integer) : boolean; checks to see if a card is a declaration card. Uses the symbol } state table to determine if the card has a reserved word on it )

input -- card, a line of fortran code } output -- end_dcl, positlon of first character after the }

end of the reserved word. } returns -- true if dcl card is found. }

var cptr : integer; { card pointer } state : integer; { used in symbol state table } dclflag : boolean; ch : CHARACTER;

Begin { check dcl } _

dcl_flag false; cptr := I; state := I;

while (state > O) and not(card[cptr] = ENDSTR) do begin cptr :- cptr + 1 ; ch := lower(card[cptr]);

if (ch in alpha) then state := symtable[ch,state]

else if not(ch in [BLANK,TAB]) then state := -1; { not a dcl }

if state = 0 then dcl_flag :- true; end; { while }

if dcl_flag then end dcl := cptr + 1 else end_dcl := 0; if debug then writeln('check dcl: ",dc[_flag); check_dcl := dcl_f]ag;

End; { check_dcl }

{I ............. continued ................. )

FUNCTION continued(card : string): boolean; { the first six columns are searched for a non blank character ( i f t h a t c h a r a c t e r i s a t a b t h e n t h e l i n e i s nn t c o t l t l n u e d { i f t h e f ~ r s t non b l a n k c h a r a c t e r i s in column s i s and not a { t a b o r 0 t h e n t h e l t n e t s c o n t i n u e d

vat cp : 0..MAXSTRING; { card position } cflag : boolean; { continued flag }

Begin { continued } ep := l; cflag := false;

while ( cp <= COL6) and (card[cp] = BLANK) do cp := cp + i; if (cp > COL6) or (card[cp] = TAB) then cflag := false else if cp ~ COL6 then begin

if card[cp] " ord('0") then cflag :- false else cflag :" true;

end; ( else if } continued := cflag;

End; { continued }

{ ******************** main procedure *************************

Begi~ {main}

initio; { initializes software tools constants,types and variables

initialize; { initializes all the variables, arrays and tables used in the main procedure }

while getline(card,STDIN,MAXSTR) do begin if (lower(card[l]) = LETC) and (card[2] = DOLLAR) then

pr_option(card) else if not (lower(card[If) in [LETC,STAR]) then if check_dcl(card,end_dcl) then begin

getnames(card,end_dcl); lastwasdcl := true;

end else if (lastwasdcl) and continued(card) then

{ if a line is continued the text has to start } { in at least column 7 } getnames(card,7)

else lastwasdcl := false; end; { while }

output~define s; End. ( longname }

DEFINE.SFT Processes the define statements

{ DEFINE PROGRAM (sft) (

~ FUNCTION -- define reads from standard input, looking for macro

Page 14: VAX Fortran to Fortran 77 translator

definitions of the form define([dent,string). } and writes tO standard output with each subsequent instance of the } the identifier ideal replaced by the sequence of characters string.} String must be he,lanced in parentheses. The text of each defini- tion proper results in no output of text. Each replacement string is rescanned for further possible replacements, permitting multi- level definitions.

NOTE this program may be modified to handle underscores by adding an underscore to the valid characters of the utility "isalphanm~"

EXAMPLE define(endfile,(-l)) define(done,endfile)

if (getit(line) = done) then putit(sumline);

<end of file>

if (getit(line) " ( - i ) ) then put it (s~line) ;

BUGS A recursive definition such as define(x,x) will cause an infinite loop when x is invoked

REFERENCE Kernighan &Plauger, "Software Tools in Pascal" 198l ~dison-Wesley Publishing Company, Reading, MA

wrapper (CU) -- this is the wrapper for all the software tools This next line inherits all the global definitions that go along

with the software t o o l s . [ inherit ('userl : [bllb.sof ttool .environ} globdefs ,env') ] program wrapper( input , o u t p u t ) ;

{ define -- simple string replacement macro processor } procedure define;

{ defcons -- coust declarations for define } c o a s t

BUFSIZE = 500; { size of pushback buffer } MAXCMARS - 5000; { size of uame-defn table } MAXDEF - MAXSTR; { max chars in a defn } MAXTOK = MAXSTR; { max chars in a token } HASRSIZE - 53; { size of hash table }

{ deftype - - type definitions for define } t ype

charpos = 1..MAXCHARS; charbuf - a r r a y [I..MAXCHARS] of c h a r a c t e r ; s t t y p e - (DEFTI~E, MACTYPE); { symbol t a b l e t ypes ) n d p t r = Andblock; ( p o i n t e r to a name-defn b lock ) ndblock =

record { name-defn block } name : cha rpos ; defn : cha rpoa ; k ind : sttype; n e x t p t r : ndp t r

end ;

{ d e f v a r - - v a t d e c l a r a t i o n s fo r d e f i n e ) v a t

hash i sh : a r r a y [I. .HASHSIZE] of n d p t r ; n d t a b l e : c h a r b u f ; n e x t t a b : c h a r p o s ; { first f r e e p o s i t i o n in n d t a b l e } bur : a r r a y [ I . .BUFSIZE] of c h a r a c t e r ; { fo r pushback } bp : 0. .BUFSIZE; { next a v a i l a b l e c h a r a c t e r ; init=0 } defn : s t r i n g ; t o k e n : s t r i n g ; t ok type : s t t y p e ; { t ype r e t u r n e d by lookup } defuame : string; { value is "define" } null : string; { value is "" }

{ d e f p r o c - - procedu re s needed by define }

{ c s c o p y - - copy c b [ i ] . . , to s t r i n g s } procedure cscopy ( v a t cb : c h a r b u f ; i : cha rpos ;

vat s : string); vat

j : integer; beg in

j : - 1 ; wh i l e ( c b [ i ] <> E~DSTR) do beg in

s[j] :- c b [ i ] ; i :- i+l; j :" j + I

end; s[j] :- ES~STR

end;

{ sccopy -~ copy string s to cb[i] . . . } procedure sccopy ( v a t s : s t r i n g ; v a t cb : c h a r b u f ;

i : c h a r p o s ) ; v a t

j : integer; begin

j : - I ; while (s[j[ <> ENDSTR) do begin

cbIi] := s[jl; j := j + I; i := i+ 1

end ; c b [ i ] : " ENDSTR

end;

( p u t b a c k - - push c h a r a c t e r back onto i npu t }

procedure p~tback (c : c h a r a c t e r ) ; begin

if (bp >- Bt~SIZE) then e r r o r ( ' t o o many c h a r a c t e r s pushed b a c k ' ) ;

bp : - bp + I ; b u f [ b p ] : - c

end;

( ge tpbc - - ge t a ( p o s s i b l y pushed back) c h a r a c t e r ) f u n c t i o n getpbc (va t c : c h a r a c t e r ) : c h a r a c t e r ; b e g i n

i f (bp > O) t h e n c := b u f [ b p ]

e l s e b e g i n bp : - i ; buf[bp} := g e t c ( c )

end; if (C <> ENDFILE) then

bp := bp - i; ge tpbc := c

end;

( p b s t r - - push s t r i n g back onto inpu t } procedure pbs t r (war s : s t r i n g ) ; v a t

i : integer; begin

for i :- length(s) downto I do p u t b a c k ( s [ i ] )

end;

{ gettok -- get token for define ) function gettok (vat token : string; toksize : integer)

: c h a r a c t e r ; v a t

i : integer; done : boolean;

beg in i := I ; done : - fa lse; while (not done) and (i ~ toksize) do

if (isalphanum(getpbc(token[i]))) then i:=i+l

else done : - t r u e ;

if (i >- toksize) then error('define: token too long');

if (i > 1) then begin { some alpha was seen } p u t b a c k ( t o k e n [ i ] ) ; i : " i - 1

end; { e l s e single non-a lphanumer ic ) token[i+l] := ENDSTR; gettok :- token[l}

end;

( g e t d e f - - g e t name and d e f i n i t i o n } procedure g e t d e f ( v a t token : s t r i n g ; t o k s i z e : i n t e g e r ;

v e t defu : s t r i n g ; d e f e i z e : i n t e g e r ) ; v a t

i , n l p a r : i n t e g e r ; c : c h a r a c t e r ;

beg in t o R n [ l } : - ENDSTR; { in case of bad input ) d e f n [ 1 ] : " ENDSTR; i f ( g e t p b c ( c ) <> LPAREN) then

m e s s a g e ( ' d e f l n e : missing l e f t p a t e n ' ) e l s e if (no t i s l e t t e r ( g e t t o k ( t o k e n , t o k s i z e ) ) ) t h e n

m e s s a g e ( ' d e f i n e : non-a lphanumer ic name*) e l s e if ( 8 e t p b c ( c ) <> COI~fA) t h e n

m e s s a g e ( ' d e f i n e : m i s s i n g cou~a in d e f i n e ' ) e l s e begin { got " ( n a m e , " s o f a r }

whi le ( g e t p b c ( c ) - BLANK) do ; ( sk ip l e a d i n g b lanks )

p u t b a c k ( c ) ; { went one tOO f a r } n l p a r :m O; i := I ; w h i l e ( n l p a r >= O) do b e g i n

if ( i >" d e f s l z e ) t hen e r r o r ( ' d e f l n e : d e f i n i t i o n too l o n g ' )

e l s e i f ( S e t p b c ( d e f n [ i ] ) = ENDFILE) then e r r o r ( ' d e f i u e : m i s s i n g r i g h t p a r e n ' )

e l s e i f ( d e f n [ i ] = LPA~EN) then n l p a r : " n l p a r + I

else if ( d e f n [ i ] " RPAR~N) then n l p a r : " n l p a r - 1;

{ e l s e normal c h a r a c t e r in defu[i] } i : ' i + l

e n d ; d e f n [ i - l ] : - ENDSTR

end e n d ;

{ i n i t h e s h - - i n i t i a l i z e hash t a b l e to n i l } procedure i n i t h a s h ; v a t

i : I . .HASHSIZE; begin

nexttab := l; { first free slot in table } for i : " I to HASHSXZE do

hashtab[i] :~ nil end;

( hash - - compute hash f u n c t i o n of a name ) f u n c t i o n hash ( v a t name : s t r i n g ) : i n t e g e r ; v a t

i, h : i n t e g e r ; b e g i n

h : - 0; fo r i : - I t o l e m ~ t b ( n a m e ) do

h : " ( 3 * h + n a m e [ i } ) ~ o d ~ASHSIZE; ba rb : - h + 1

end;

{ h a s h f i n d - - f l a d ~ m e i~ hash t a b l e } f u n c t i o n hashf ind ( v a t name : s t r i n g ) : n d p t r ; v a t

ad , Vo Z: oo

Page 15: VAX Fortran to Fortran 77 translator

p : ndptr; tempname : strlng; found : boo lean ;

begin found := ~alse; p :- hashtab[hash(name)]; while (not found) and (p <> nil) do begin

cscopy(ndtable, p'.name, tempname); if (equal(name, tempname)) then

found :~ true else

p :~ p'.nextptr end; hashfind :- p

end;

{ install -- add name, definition and type to table } procedure install (vat name, defn : string; t : sttype) vat

h, dlen, nlen : integer; p : ndptr;

begin ulen :- length(name) + i; { I for ENDSTR dlen :- length(defn) + I; if (nexttab + mien + dlen > HAX¢~ARS) then begin

put~tr(n&me, SYDERR); error(': too many definition~')

end else begin { put it at front of chain }

h :- hash(name); new(p); p^.nextptr :~ hashtab[h]; hashtab[h] :- p; p~.name :- nexttab; secopy(n&m~, ndtable, nexttab); nexttab :- nexttab + mien; p^.defn :" nexttab; se¢opy{de[n, ndtable, nexttab); nextt~b :~ nexttab + dlen; p*.kind :l t

end end;

{ lookup -- locate n~me, get defn ~nd ~ype from t&ble } function lookup (v~r u~me, defm : s~rimg; vlr t : sttype)

• boolean; va~

p : u d p t r ; ~,eK~n

p :- ha~hfznd(name): i~ (p - n i l ) then

lookup :~ f a l s e e l s e beg in

lookup := t ,ue~ c s c o p y ( n d t a b l v , p ' . d e f n , de fn ) ; t - p ' . k i n d

end end;

( i n i t d e f - - i n i t i a l i z e v a r i a b l e s for de f i ne ) procedure i n i t d e f ; begin

( s e t s t r i n g ( d e f n a m e , " d e f i n e r ) ; } de fname[ l ] := o r d ( ' d " ) ; defname[2] := o r d ( " e " ) ; defname[3] := o r d ( ' f ' ) ; defname[4] := o r d ( " i ~ ) ; defname[5] := o r d ( ' n ' ) ; de£name[6] := o r d ( ' e ' ) ; defname[7] : - ENDSTR;

bp : - 0 ; ( pushback b u f f e r p o i n t e r } i n i t h a s h

end; begin

null[l] :- E~DSTR; initdef; install(defname, null, DEFTYPE); while (gettok(token, MAXTOK) <> ENDFILE) do

if (not isletter(token[l])) then p u t s t r ( t o k e n , STIIOUT)

e l s e i f (not lookup( token , defn , t o k t y p e ) ) then p u t s t r ( t o k e n , STI~UT) ( undef ined )

e l s e i f ( t o k t y p e u DEF~YPE) then beg in { defn getdef(token, HAXTOK, defn, MAXDEF); install(token, defn, HACTYPE)

end else

pbstr(defn) ( push replacement onto end; begin { wrapper }

initio; { Call program here. For example: filter } define

end. { wrapper )

xnpu~ )

l~,q~, ~ H ~ I ~ ~ . ) ~ . ~ .,:~1~, Iz~ 7 , ~ . ~