F77 Bug list

Acorn Fortran77 release 2

Note:This compiler does not reliably support the Acorn debugger !DDT, it uses the application ASD, ( Acorn Symbolic Debugger), for debugging, details in the paper version of the Fortran77 manual.

Bug List and Example Code

last updated 16 Feb 98

Please send news of any other bugs you come across to us.
This page is Copyright 'Fortran Friends'.

no Date        Source
1  Mar91       Archive  vol 6 no.4 page 8
               Raymond Wright reported that DACOS(-1.) gives the wrong answer
               but    X=-1.
                      Y=DACOS(X)
               the right one.   see PRM page 1706
               This problem applies when any of the 'immediate operands'
               which are (0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 0.5, 10.0)  are
               used in negative form as arguments to fortran functions.
               e.g. the result of this code  below is 1.0
               PRINT *, ' the square root of -1 is ', SQRT(-1.)
               END
--------------------------------------------------------------------------
      PROGRAM BUG1
      PRINT *,' SQRT(-1.0) =',SQRT (-1.0)
      S = -1.0
C        but this one really does fail!
      PRINT *,' SQRT(S) =',SQRT(S)
      END

--------------------------------------------------------------------------
2  13 Jul 91   J.P.Davey  reported a problem passing functions as arguments
               the following code will not compile, it stops with an error
               Fatal Error (Code 930): Internal Error
               SUBROUTINE TEST(F1,X)
               EXTERNAL F1
               F(Z)=F1(X,Z)
               A=F(2.0-1.0)
               RETURN
               END
--------------------------------------------------------------------------
      SUBROUTINE TEST(F1,X)
      EXTERNAL F1
      F(Z)=F1(X,Z)
      B=F(2.0-1.0)
      RETURN
      END

--------------------------------------------------------------------------

3  30 Sep 91
Kate Crennell  Error in concatenating a character variable with itself,
               and no warnings given.
               This is not allowed in standard Fortran 77 although some
               compilers translate it correctly, others give compilation
               errors. Acorn Archimedes Fortran gives no compilation error
               or warning, and gives the wrong answer.
--------------------------------------------------------------------------
      PROGRAM Bug3
      CHARACTER *40 A
      DATA A/'<123>'/
      WRITE(*,*)' A=*',A,'*'
      A='X'//A   
      WRITE(*,*)' A=*',A,'*'
      STOP
      END

--------------------------------------------------------------------------

4  03 Nov 91
Kate Crennell  OPEN file names are truncated to 30 characters. 
               You can get round this by defining an Alias e.g 
               for the directory path and using that instead of the full
               path name in the Fortran.
--------------------------------------------------------------------------
      PROGRAM OPENBUG
      CHARACTER*40 NAMEO,INAME
      DATA NAMEO/'SCSI::HD4.$.MATHS.KMCPoly.NOGOODFILE'/
      OPEN(10,FILE=NAMEO,STATUS='NEW',FORM='FORMATTED')
      INQUIRE(UNIT=10,NAME=INAME)
      WRITE(*,*)' INQUIRE thought name was ',INAME
      WRITE(10,100)NAMEO,NAMEO(1:30)
  100 FORMAT(' this is just a little test file'/
     +' it ought to be written to a file with name'/1X,A/
     +' but actually it will be written to'/1X,A)
      CLOSE(10)              
      END

--------------------------------------------------------------------------
 5  21 Feb 92 
 Andrew Ray  Despite the statement on page 32 of the Release2 Fortran77
             manual, files cannot be accessed with STATUS='SCRATCH' in the
             OPEN statement. You get round this by putting STATUS='DELETE'
             in the CLOSE statement
  5a 21 Apr 94  Although you can use STATUS='SCRATCH' as shown below, you
             cannot REWIND the file, and then try to read it back, because
             REWIND does a CLOSE, and then subsequent attempts to read
             from that file cause the computer to hang
--------------------------------------------------------------------------- 
      PROGRAM sratchy
      INTEGER IWORD(200)
      DO 10 I=1,200
   10 IWORD(I)=I
      NOUT=2
C                 STATUS='SCRATCH' is not accepted at Run Time
C                 but STATUS='DELETE' in the CLOSE statement works
      OPEN(UNIT=NOUT,FILE='Kate',FORM='FORMATTED',STATUS='SCRATCH')
      WRITE(NOUT,101)(IWORD(I),I=1,200)
  101 FORMAT( 10I6)
      CLOSE(NOUT)
C      replace the line above with the line below to delete the file
C      CLOSE(NOUT,STATUS='DELETE')
      STOP 'OK'
      END 
----------------------------------------------------------------------------
6 17 June 93
  Eugène R Dahmen found many linker problems when using RISC OS 3 with
        ADFS buffers NOT set to 0, watch this after a 'factory reset'
----------------------------------------------------------------------------
7  4 Nov 93  
 K.M.Crennell  Compilation fails on very large BLOCK DATA statement with the
               message "insufficient store for code generation". Changing
               the slot size available makes no difference; you just have to
               rewrite the code.
----------------------------------------------------------------------------
8 27 Apr 96
 D.J.Crennell
      PROGRAM Bug8
      CHARACTER TEXT1*3,TEXT2*4
C          Character comparison ignores last character in first string
C          when the first string is longer than the second.
      TEXT1='ABC'
      TEXT2='ABCD'
      IF(TEXT2.EQ.TEXT1) PRINT *,'Bug 8 in Fortran: ',TEXT2,'.EQ.',TEXT1
      IF(TEXT1.NE.TEXT2) PRINT *,'but ',TEXT1,'.NE.',TEXT2 
      END
 prints:
 Bug 8 in Fortran: ABCD.EQ.ABC
 but ABC.NE.ABCD
----------------------------------------------------------------------------
9 16 Feb 98
 K.M. Crennell
      PROGRAM BUG9
      A = 15.0
      B = A**-0.5
      PRINT *,B
      END
 compiler fails with:
 Topexpress FORTRAN 77 front end version 1.19
     3         B = A**-0.5
 L    3---------------?
 Error (code 631): expecting name or constant

 work around: put the '-0.5' in parentheses so:
      B = A**(-0.5)
 compiles correctly
----------------------------------------------------------------------------
10 04 Mar 03
 D.J. Crennell
 compiler does not understand:
      IMPLICIT IDINT
 while it does understand:
      IMPLICIT IDNINT
----------------------------------------------------------------------------

Page last updated 02 May 2005
Click here to return to Fortran Friends Top page