fpt and WinFPT Reference Manual - Command-line Commands

| SimCon Home | Ref Manual Home |

Modernising Fortran

Hunting the Wumpus - an example

wumpus.f is a slightly extended FORTRAN 77 implementation of "Hunt the Wumpus". To my surprise, it compiles and runs under gfortran and the game is playable. The code needs modernisation. For example, the code which sets up the cave system where the Wumpus lives begins:

SUBROUTINE PASSAG INCLUDE 'ints.inc' INTEGER DEST,IPASS(3,20) DO 230 I = 1,20 DO 220 J = 1,3 IPASS(J,I) = 0 220 CONTINUE 230 CONTINUE DO 300 I = 1,3 N = 20 J = 0 DO 280 WHILE (N .GT. 0) J = J+1 IF (IPASS(I,J) .EQ. 0) THEN 240 CONTINUE M = N*RAND() IF ((M .EQ. 0) .OR. (M .EQ. N)) GOTO 240 K = 0 DEST = J DO 260 WHILE (K .LT. M) DEST = DEST+1 IF (IPASS(I,DEST) .EQ. 0) K = K+1 260 CONTINUE DO 270 L = 1,I-1 IF (DEST .EQ.IPASS(L,J)) GOTO 240 270 CONTINUE IPASS(I,J) = DEST IPASS(I,DEST) = J N = N-2 ENDIF 280 CONTINUE 300 CONTINUE C WRITE(6,310)(J,(IPASS(I,J),I = 1,3),J=1,20) 310 FORMAT(4I5) C END

There is no indentation, implicit typing, the DO loop control constructs are DO <label> - <label> CONTINUE, variables are passed between routines in a COMMON block and there are labels everywhere.

fpt runs on this code with the script modernise_fortran.fsp to produce:

SUBROUTINE passag ! ! ! **************************************************************************** ! ! USE fpt_module_kinds ! USE module_ints IMPLICIT NONE ! ! **************************************************************************** ! INCLUDE 'ints.i90' ! INTEGER(KIND=ki4)dest,ipass(3,20) INTEGER(KIND=ki4) :: i INTEGER(KIND=ki4) :: j INTEGER(KIND=ki4) :: k INTEGER(KIND=ki4) :: l INTEGER(KIND=ki4) :: m INTEGER(KIND=ki4) :: n REAL(KIND=kr4) :: rand ! DO i=1,20 DO j=1,3 ipass(j,i)=0 ENDDO ENDDO DO i=1,3 n=20 j=0 DO WHILE (n>0) j=j+1 IF (ipass(i,j)==0) THEN 240 CONTINUE m=n*rand() IF ((m==0) .OR. (m==n)) THEN GOTO 240 ENDIF k=0 dest=j DO WHILE (k<m) dest=dest+1 IF (ipass(i,dest)==0) THEN k=k+1 ENDIF ENDDO DO l=1,i-1 IF (dest==ipass(l,j)) THEN GOTO 240 ENDIF ENDDO ipass(i,j)=dest ipass(i,dest)=j n=n-2 ENDIF ENDDO ENDDO ! DO i=1,20 DO j=1,3 passage(j,cave_alias(i))=cave_alias(ipass(j,i)) ENDDO ENDDO ! WRITE(6,310)(j,(pass(i,j),i = 1,3),j=1,20) ! END

The text of the script modernise_fortran.fsp is:

! modernise_fortran.fsp 20-May-24 John Collins ! Please edit this file to customise the changes for your system ! File handling ! ============= ! We assume that the top-level directory structure is: ! ! project_base_directory ! ! original_source ! ! ! directories containing the code ! ! modified_source ! ! ! empty directories matching original_source ! ! fpt_output ! ! ! empty directories matching original_source ! ! If your directory structure is different (and it may be) comment-out the following ! Set a default for new files (if any) % output directory "../fpt_output" % keep directories % edit output file names: replace "original_source" by "fpt_output" % edit output file names: replace "modified_source" by "fpt_output" ! Note - specify the input file name extensions in the list of input files % primary output file name extension: ".f90" % include output file name extension: ".i90" % overwrite changed files ! modified_source contains files changed by hand. Look in modified source for changed files % check modified source ! Code changes ! ============ % specify implicit none % specify numeric kinds % change do continue to do enddo % change if to if-then % remove labels from enddo statements % remove labels from executable statements % change relational operators to symbolic form ! Choose a number (or comment-out) % remove format statements used fewer than 3 times % change common to module % make makefile ! Suppress the diagnostics which mark these changes % suppress diagnostic 2255 4243 4495 ! Code formatting ! =============== % free format % no column format ! Choose numbers appropriate for your system % output code line length: 130 % page width: 132 % write continuation character in column 88 ! Choose between: !!! % lower case keywords % upper case keywords !!! % lower case intrinsics % upper case intrinsics % lower case symbols !!! % upper case symbols !!! % lower case parameters !!! % upper case parameters % default case parameters % lower case kind tags !!! % upper case kind tags !!! % default case kind tags !!! % lower case exponent characters % upper case exponent characters ! Optionally: % space before "::" % space after "::" % space before "=" % space after "=" ! End of modernise_fortran.fsp

Most of the commands are self-explanatory. They are documented here. The incremental steps by which wumpus was modernised are shown below.

Checking for Errors

We put wumpus under fpt control. We create a new top-level directory for the project and within it a directory named fpt for the fpt control files. We cd to the fpt directory and run project_directory_setup.sh, which is in the main fpt directory and therefore in the path. We use the tree command to see what has been created.

john@gemsbok:~/projects/WinFPT/fpt/fpttest$ mkdir wumpus_project john@gemsbok:~/projects/WinFPT/fpt/fpttest$ cd wumpus_project john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project$ mkdir fpt john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project$ cd fpt john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt$ project_directory_setup.sh Please enter the base directory of your files: ../../wumpus john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt$ cd .. john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project$ tree .  fpt  fpt_output     wumpus  modified_source     wumpus  original_source  wumpus  cavnum.f  inipos.f  input.f  intro.f  ints.inc  move.f  passag.f  play.f  shoot.f  wumpus.f 7 directories, 10 files

In the fpt directory we create a simple fsp file for the project. We make as few changes as possible to the original code - we first simply want to analyse it. wumpus.fsp is:

! wumpus.fsp 25-Oct-23 John Collins % input directory: ../original_source/wumpus % infer input code layout from file name extension % output directory ../fpt_output/wumpus % keep layouts % keep file name extensions % overwrite changed files cavnum.f inipos.f input.f intro.f move.f passag.f play.f shoot.f wumpus.f ! End of wumpus.fsp

We run fpt interactively to check the code

john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt$ fpt wumpus.fsp %i ------------------------------------------------------------------------------- NOTE Number 1273 Severity 0 (Worst 0) Count 1 Fortran auxiliary keyword(s) used as identifier(s). See Listing File or FORTRAN output for occurrences. ------------------------------------------------------------------------------- ------------------------------------------------------------------------------- NOTE Number 2241 Severity 0 (Worst 0) Count 2 References are made to sub-programs which have not been read. ------------------------------------------------------------------------------- FPT>

We check the keywords used for symbols:

FPT> show keywords used for symbols Check of Usage of Keywords and Intrinsic Names ============================================== FORTRAN Auxiliary Keywords used for identifiers ----------------------------------------------- Name Scope Use/COMMON Address Type Size Value/Bounds ---- ----- ---------- ------- ---- ---- ------------ PASS WUMPUS,SHOOT,PLAY,PASSAG,MOVE,INIPOS,CAVNUM /INTS/ 92 INTEGER *4 df (1:3,1:20) FORTRAN Intrinsic names used for identifiers -------------------------------------------- Name Scope Use/COMMON Address Type Size Value/Bounds ---- ----- ---------- ------- ---- ---- ------------ TIME Global FUNCTION REAL *4 df Page> FPT>

There is a COMMON block, which we check for misalignment

FPT> check names in common Name Usage Consistency Check ============================ No inconsistent name uses detected FPT>

We check symbol usage

FPT> check usage Symbol Usage Check ================== No objects are read but never written to. Objects which are written to but never read ------------------------------------------- Name Scope Use/COMMON Address Type Size Value/Bounds ---- ----- ---------- ------- ---- ---- ------------ I WUMPUS LOCAL INTEGER *4 df ------------------------------------------------------------------------------- !!! Symbol Usage Check !!! !!! Total number of objects written to but never read (Warnings): 1 ------------------------------------------------------------------------------- No objects are declared but unused. Check of Protected Variables ============================ No PROTECTED variables found FPT>

Other checks also reveal nothing particularly untoward.

Building from the fpt output

We generate output from the fpt run, build from the fpt output files and play a few games to check that nothing has changed. fpt will reformat the output, but apart from indentation and changes in upper and lower case text, fpt should not change the code unless instructed to do so.

The default reformatting does help to make the code more readable. The fragment at the start of passag.f:

DO 230 I = 1,20 DO 220 J = 1,3 IPASS(J,I) = 0 220 CONTINUE 230 CONTINUE

now becomes:

DO 230 I=1,20 DO 220 J=1,3 IPASS(J,I)=0 220 CONTINUE 230 CONTINUE

We build it

john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt_output/wumpus$ gfortran -c *.f john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt_output/wumpus$ gfortran -o wumpus.exe *.o john@gemsbok:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt_output/wumpus$ ./wumpus.exe

We run a few games - it works!

A Regression test

We are going to make changes to the code. We need a regression test to prove that we haven't broken anything. This is an interactive program. We can't write down a set of instructions and run the regression test by hand because wumpus will run with different random numbers on different runs. This is because the random number is seeded from the time of day. But if we comment-out the seed statement in wumpus.f the intrinsic rand will always generate the same set of numbers and we can then make a reproducible test.

The alternative is to use the record/replay facility in fpt, but this makes a number of changes to the code and in this case it is better to avoid that.

We don't modify the original_source file wumpus.f. The whole point of having original_source is that it doesn't change and we can see what we have done. Instead, we copy wumpus.f to the corresponding modified_source directory and change it there. We add the command

% check modified source

to wumpus.fsp so that fpt looks in modified_source for each file before searching original_source.

wumpus.fsp is now:

! wumpus.fsp 25-Oct-23 John Collins % input directory: ../original_source/wumpus % infer input code layout from file name extension % output directory ../fpt_output/wumpus % keep layouts % keep file name extensions % overwrite changed files % check modified source cavnum.f inipos.f input.f intro.f move.f passag.f play.f shoot.f wumpus.f ! End of wumpus.fsp

We run fpt, build the code in fpt_output and make a run, recording the interactive commands.

Statement Labels and IF Sub-statements

The code is now indented, but there is a maze of statement labels. The DO loop control construct is DO <label> - <label> CONTINUE. We can change that. The fpt command is

% change do continue to do enddo.

We remove the labels from the ENDDO statements with the command

% remove labels from enddo statements

Also, there are labels attached to executable statements. We can move them to CONTINUE statements with the command

% remove labels from executable statements

There are IF statements with sub-statements. The code will be clearer if they are changed to IF THEN constructs with the conditional statement indented. The command is

% change if to of then

We add these commands to wumpus.fsp

! wumpus.fsp 25-Oct-23 John Collins % input directory: ../original_source/wumpus % infer input code layout from file name extension % output directory ../fpt_output/wumpus % keep layouts % keep file name extensions % overwrite changed files % check modified source % change do continue to do enddo % remove labels from enddo statements % remove labels from executable statements % change if to if-then cavnum.f inipos.f input.f intro.f move.f passag.f play.f shoot.f wumpus.f ! End of wumpus.fsp

The code of passag.f, which sets up the passages between caves, mow looks almost civilised:

! ***************************************************************************** ! passag.f90 17-May-86 John Christopherson ! ***************************************************************************** C SUBROUTINE PASSAG C INCLUDE 'ints.inc' C INTEGER DEST,IPASS(3,20) C DO I=1,20 DO J=1,3 IPASS(J,I)=0 ENDDO ENDDO DO I=1,3 N=20 J=0 DO WHILE (N .GT. 0) J=J+1 IF (IPASS(I,J) .EQ. 0) THEN 240 CONTINUE M=N*RAND() IF ((M .EQ. 0) .OR. (M .EQ. N)) THEN GOTO 240 ENDIF K=0 DEST=J DO WHILE (K .LT. M) DEST=DEST+1 IF (IPASS(I,DEST) .EQ. 0) THEN K=K+1 ENDIF ENDDO DO L=1,I-1 IF (DEST .EQ. IPASS(L,J)) THEN GOTO 240 ENDIF ENDDO IPASS(I,J)=DEST IPASS(I,DEST)=J N=N-2 ENDIF ENDDO ENDDO C WRITE(6,310)(J,(IPASS(I,J),I = 1,3),J=1,20) 310 FORMAT (4I5) C DO I=1,20 DO J=1,3 PASS(J,CAVEN(I))=CAVEN(IPASS(J,I)) ENDDO ENDDO C WRITE(6,410) 410 FORMAT (/,'Final passages') C WRITE(6,310)(j,(pass(i,j),i = 1,3),j=1,20) C END

We build and test again. It still works!

Free Format

The command to convert the code to free format is (surprisingly)

% free format

There are other formatting details which we might want to change. We can set the code line length with the command

% output code line length <integer>

and the page width (i.e. the width for code and comments) with the command

% page width <integer>

We choose a default column for the Fortran 90 continuation character with the command

% write continuation character in column <integer>

When the code is changed to free format we should change the primary file name extension to .f90. We also change the include file name extension to .i90. The commands are

% primary output file name extension: ".f90" % include output file name extension: ".i90'

When we do this, fpt needs to know the input extensions, because any input extension which differs from the default will otherwise be appended to the file base name. The commands are

% primary input file extension: ".f" % include input file extension ".inc"

As a last formatting detail we set the user-defined symbols to lower case with the command

% lower case symbols

Some users prefer the keywords in lower case and the symbols or at least the Fortran parameters in upper case. These, and options for changing code indentation are all available.

wumpus.fsp is now:

! wumpus.fsp 25-Oct-23 John Collins % input directory: ../original_source/wumpus % infer input code layout from file name extension % output directory ../fpt_output/wumpus !!! % keep layouts !!! % keep file name extensions % primary input file name extension: '.f' % include input file name extension: '.inc' % primary output file name extension: '.f90' % include output file name extension: '.i90' % overwrite changed files % check modified source % change do continue to do enddo % remove labels from enddo statements % remove labels from executable statements % change if to if-then % free format % output code line length: 132 % page width: 140 % write continuation character in column 88 % lower case symbols cavnum.f inipos.f input.f intro.f move.f passag.f play.f shoot.f wumpus.f ! End of wumpus.fsp

This generates:

!H!**************************************************************************** !H! File: ../fpt_output/wumpus/passag.f90 !H! Output by fpt 4.2-h Intel-Linux On 31:Dec:50 At 00:00:00 Input files: !H! Main: /home/john/projects/WinFPT/fpt/fpttest/wumpus_project/fpt/wumpus.fsp !H! Current: ...s/WinFPT/fpt/fpttest/wumpus_project/original_source/wumpus/passag.f !H! Licensee: SimCon: Development version. !H!**************************************************************************** ! ***************************************************************************** ! passag.f90 17-May-86 John Christopherson ! ***************************************************************************** ! SUBROUTINE passag ! INCLUDE 'ints.i90' ! INTEGER dest,ipass(3,20) ! DO i=1,20 DO j=1,3 ipass(j,i)=0 ENDDO ENDDO DO i=1,3 n=20 j=0 DO WHILE (n .GT. 0) j=j+1 IF (ipass(i,j) .EQ. 0) THEN 240 CONTINUE m=n*rand() IF ((m .EQ. 0) .OR. (m .EQ. n)) THEN GOTO 240 ENDIF k=0 dest=j DO WHILE (k .LT. m) dest=dest+1 IF (ipass(i,dest) .EQ. 0) THEN k=k+1 ENDIF ENDDO DO l=1,i-1 IF (dest .EQ. ipass(l,j)) THEN GOTO 240 ENDIF ENDDO ipass(i,j)=dest ipass(i,dest)=j n=n-2 ENDIF ENDDO ENDDO ! WRITE(6,310)(J,(IPASS(I,J),I = 1,3),J=1,20) 310 FORMAT (4I5) ! DO i=1,20 DO j=1,3 pass(j,caven(i))=caven(ipass(j,i)) ENDDO ENDDO ! WRITE(6,410) 410 FORMAT (/,'Final passages') ! WRITE(6,310)(j,(pass(i,j),i = 1,3),j=1,20) ! END

IMPLICIT Typing and Declarations

wumpus uses implicit typing. Also there are no kind specifications, though the typing is very simple and there are no precision implications so perhaps we don't need them. We will add them to demonstrate what can be done.

To add declarations for everything and to insert IMPLICIT NONE statements the command is

% specify implicit none

To add kind specifications the command is

% specify numeric kinds

We add these to wumpus.fsp and run fpt again.

Whenever fpt makes a significant change to the user's code it inserts a diagnostic to show what it has done. For example:

! IMPLICIT NONE !---------------^--------------------------------------------------------------------------------------------------------------------------- !!! FPT - 2255 Declaration statement modified or inserted !-------------------------------------------------------------------------------------------------------------------------------------------

and

INTEGER(KIND=ki4)dest,ipass(3,20) !------------------------^------------------------------------------------------------------------------------------------------------------ !!! FPT - 2255 Declaration statement modified or inserted !-------------------------------------------------------------------------------------------------------------------------------------------

If something goes wrong these messages can be useful. Usually they are a nuisance and can be suppressed by the command

% suppress diagnostic <integer>

We do that here.

With these commands, passag.f90 (Note the new file name extension) begins:

SUBROUTINE passag ! ! ! **************************************************************************** ! ! USE fpt_module_kinds ! IMPLICIT NONE ! ! **************************************************************************** ! INCLUDE 'ints.i90' ! INTEGER(KIND=ki4) :: dest,ipass(3,20) INTEGER(KIND=ki4) :: i INTEGER(KIND=ki4) :: j INTEGER(KIND=ki4) :: k INTEGER(KIND=ki4) :: l INTEGER(KIND=ki4) :: m INTEGER(KIND=ki4) :: n REAL(KIND=kr4) :: rand

Note the new IMPLICIT statement and the USE statement for fpt_module_kinds. The module fpt_module_kinds is written in the main output directory and is:

!H!**************************************************************************** !H! File: ../fpt_output/wumpus/fpt_module_kinds.f90 !H! Output by fpt 4.2-h Intel-Linux On 31:Dec:50 At 00:00:00 Input files: !H! Main: /home/john/projects/WinFPT/fpt/fpttest/wumpus_project/fpt/wumpus.fsp !H! Licensee: SimCon: Development version. !H!**************************************************************************** ! **************************************************************************** MODULE fpt_module_kinds ! IMPLICIT NONE ! ! ! **************************************************************************** ! INTEGER,PARAMETER :: kl1=1 INTEGER,PARAMETER :: kl2=2 INTEGER,PARAMETER :: kl4=4 INTEGER,PARAMETER :: kl8=8 INTEGER,PARAMETER :: ki1=SELECTED_INT_KIND(2) INTEGER,PARAMETER :: ki2=SELECTED_INT_KIND(4) INTEGER,PARAMETER :: ki4=SELECTED_INT_KIND(9) INTEGER,PARAMETER :: ki8=SELECTED_INT_KIND(18) INTEGER,PARAMETER :: kr4=SELECTED_REAL_KIND(6,37) INTEGER,PARAMETER :: kr8=SELECTED_REAL_KIND(15,307) INTEGER,PARAMETER :: kr16=SELECTED_REAL_KIND(33,4931) ! ! **************************************************************************** ! END MODULE fpt_module_kinds

(There are commands to change the kind names)

Dot-delimited Relational Operators

Enough of .EQ., .GT. and other nineteenth century nonsence. To change them to symbolic form the command is:

% change relational operators to symbolic form

Variable Names

Fortran 77 variable names tended to be short and sometimes cryptic. Some compilers still required names to be no longer than 6 characters. We change the names of the main variables in wumpus to be more meaningful. This step is program-specific and has to be done by hand. The commands:

% rename wump wumpus_cave % rename cave your_cave % rename arrw arrow % rename caven cave_alias % rename pass passage % rename seq arrow_path % rename bats bat_cave % rename pits pit_cave % rename acave arrow_cave

are added to wumpus.fsp. Renaming pass, which is an auxiliary Fortran keyword (Used in setting up type bound procedures) is a good idea anyway.

FORMAT Statements

FORMAT statements may be useful when the same format is used repeatedly, or when the same format is to be used for read and write. But FORMAT statements have labels (beloved of modern Fortran users) and can clutter the code. We can remove them selectively with the command:

% remove format statements used fewer than <integer> times

We do this for wumpus. They all disappear.

COMMON Blocks

There are (believe it or not) important cases where COMMON blocks should be used in modern Fortran. The use in wumpus is definitely not one of them. The appropriate way to share material between routines is in a Fortran module.

wumpus has one COMMON block named /ints/. We would like to move the variables to a module. The command

% change common to module

converts all COMMON blocks to modules. This is very simple in this case, but there are possible complexities which are described in: http://simconglobal.com/fpt_ref_change_common_to_module.html.

A Makefile

If further development work is to be carried out we will need a Makefile. This is generated by the command:

% make makefile

The makefile references the include file compiler.make to find the Fortran compiler in use. This may be copied from compiler.make.gfortran or compiler.make.ifx in the main fpt installation directory. Please see: http://www.simconglobal.com/fpt_ref_make_makefile.html

The final fsp file

! wumpus.fsp 25-Oct-23 John Collins ! File handline % input directory: ../original_source/wumpus % infer input code layout from file name extension % output directory ../fpt_output/wumpus !!! % keep layouts !!! % keep file name extensions % primary input file name extension: ".f" % include input file name extension: ".inc" % primary output file name extension: .f90 % include output file name extension: .i90 % overwrite changed files ! Look in modified source for changed files % check modified source ! Code changes % change do continue to do enddo % remove labels from enddo statements % remove labels from executable statements % change if to if-then % specify implicit none % specify numeric kinds % change relational operators to symbolic form % remove format statements used fewer than 3 times % change common to module % make makefile ! Suppress the diagnostics which mark the changes % suppress diagnostic 2255 4243 4495 ! Code formatting % free format % no column format % output code line length: 132 % page width: 140 % write continuation character in column 88 % lower case symbols % space before "::" % space after "::" ! More meaningful names % rename wump wumpus_cave % rename cave your_cave % rename arrw arrow % rename caven cave_alias % rename pass passage % rename seq arrow_path % rename bats bat_cave % rename pits pit_cave % rename acave arrow_cave ! The wumpus primary source files cavnum.f inipos.f input.f intro.f move.f passag.f play.f shoot.f wumpus.f ! End of wumpus.fsp

The Result

We run fpt, build the output and run it:

john@impala:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt$ fpt wumpus.fsp john@impala:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt$ cd ../fpt_output/wumpus john@impala:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt_output/wumpus$ gfortran -c fpt_module_kinds.f90 john@impala:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt_output/wumpus$ gfortran -o wumpus.exe *.f90 john@impala:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt_output/wumpus$ ls cavnum.f90 fpt_module_kinds.mod inipos.f90 intro.f90 move.f90 play.f90 wumpus.exe fpt_module_kinds.f90 fpt_module_kinds.o input.f90 ints.i90 passag.f90 shoot.f90 wumpus.f90 john@impala:~/projects/WinFPT/fpt/fpttest/wumpus_project/fpt_output/wumpus$ ./wumpus.exe HUNT THE WUMPUS =============== The Wumpus lives in a system of 20 caves. Each cave is connected by passages to 3 other caves. Some of the caves contain BOTTOMLESS PITS. Some of the caves have SUPERBATS which will pick you up and drop you at random, where you may fall into the jaws of the waiting WUMPUS !!! The WUMPUS is too big for the bats to pick up and has sucker feet so it won't fall down a BOTTOMLESS PIT. You have 3 magic arrows which will turn corners through the passages. You just tell them which caves to go through. If there is no passage they will go at random and may come back and hit you. If you are next to a cave with a BOTTOMLESS PIT you can feel a draught If you are next to a cave with SUPERBATS you can hear them. If you are within 2 caves of the WUMPUS you can smell it. You must find and SLAY the WUMPUS !!! GOOD LUCK You are in cave 1 There are passages to caves 9, 16 and 7 What would you like to do [Move/Shoot]:

And off we go. Don't forget to remove wumpus.f from modified_source, otherwise the cave system will always be the same.

Have fun!

modernise_fortran.fsp

The modernisation commands described above are collected into a single fsp file in the distributions of fpt versions 4.2-k and later. The file, named modernise_fortran.fsp is shown in the intriduction above.

We can invoke this fsp file from wumpus.fsp and the script then becomes:

! wumpus2.fsp 19-Nov-23 John Collins FPTMAIN:modernise_fortran.fsp ! The wumpus primary source files % primary input file name extension: ".f" % include input file name extension: ".inc" % input directory "../original_source/wumpus" cavnum.f inipos.f input.f intro.f move.f passag.f play.f shoot.f wumpus.f ! More meaningful names % rename wump wumpus_cave % rename cave your_cave % rename arrw arrow % rename caven cave_alias % rename pass passage % rename seq arrow_path % rename bats bat_cave % rename pits pit_cave % rename acave arrow_cave ! End of wumpus2.fsp

Copyright ©1995 to 2024 Software Validation Ltd. All rights reserved.