forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

gFortran and MAKE
Goto page Previous  1, 2, 3
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General
View previous topic :: View next topic  
Author Message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Fri Aug 30, 2019 8:26 am    Post subject: Reply with quote

It may be an error in the Standard, but isn't it a common extension supported for backward compatibility ?
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Fri Aug 30, 2019 8:54 am    Post subject: Reply with quote

If the variable were of type INTEGER, perhaps, but assigning a character constant to a REAL variable would almost guarantee incompatibility, since no mainframes that I know of had IEEE reals, and on PCs we have had IEEE compatibility from the time that the first IBM PC arrived. What the Apple II did, I do not know -- possibly, software emulation on the 6502, which did not have FP instructions.
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Fri Aug 30, 2019 10:34 am    Post subject: Reply with quote

I didn't have to look very far. CDC Fortran certainly allowed it, as did Pr1me.
The following is taken from a Pr1me implementation in 1980's.
FTN77 on Pr1me was my first experience of Salford Fortran.

The following was compiled with Pr1me FTN.
I think FTN77 also supported this.
Lines 2 and 3 were my changes for CDC > Pr1me

Code:
C
      IMPLICIT INTEGER*4 (I-N)
      IMPLICIT REAL*8 (A-H,O-Z)
C
C     DRAIN-2D      DYNAMIC RESPONSE ANALYSIS OF INELASTIC STRUCTURES
C
C     A.E.KANAAN AND G.H.POWELL        UNIV. OF CALIF., BERKELEY, 1972
C
      COMMON /CONTR/ NELGR,NEQ,MBAND,NPTH,NPTV,NSTO,JCOL
      COMMON /GENINF/KCONT(10),KELEM(10),NELEM(10),NINF(10),NDOF(10)
     1             ,FCONT(3)
      COMMON /DAMP/ ALPHA,BETA,DT,GAXCTE,CON1,CON2,CON3,CON4,CON5,
     1             C1,C2,C3,C4,C5,C6,C7,C8,C9,C10,C11,C12,BETAO,DELTA
      COMMON /PASS/ IGR,ISTEP,KVARY,NBLOK,KSTAT,KDDS,KM
      COMMON /STOR/ NAVST,NF1,NF2,NF3,NF4,NTST,KODST,KDATA
      COMMON /OUTN/ IPJ,IPE,KNTJ,KNTE,NHOUT,NVOUT,NROUT
      COMMON /WORK/ HED(18),KFORM(2),TITLE(9),W(1972)
      COMMON /INFEL/ IEL,KST,LM(1),DUM(199)
      COMMON /THIST/ITHOUT(10),THOUT(20),ITHP,ISAVE,NELTH,NSTH,NF7,ISE
      COMMON /THISTJ/ITHPJ,NF5,NSTHJ,ISJ
      COMMON /THISTR/ITHPR,NF6,NSTHR,NHR,NVR,LRH1(50),LRH2(50),LRV1(50),
     1       LRV2(50)
C
      DIMENSION A(1)
      DIMENSION CHEK(2),HDAT(3,3),HSTF(2,2),SLOD(2,2)
      DATA CHEK/5HSTART,5HSTOP /
      DATA HDAT/8HEXECUTE ,8H        ,8H        ,
     1          8HDATA CHE,8HCKING ON,8HLY      ,
     2          8HEXECUTE ,8HIF SINGL,8HE BLOCK /
      DATA HSTF/8HSTORED I,8HN CORE  ,
     1          8HSTORED O,8HN TAPE  /
      DATA SLOD/8HLOADS AP,8HPLIED   ,
     1          8HLOADS IG,8HNORED   /
C
C
C     START AND TITLE CARD
C
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Fri Aug 30, 2019 11:40 am    Post subject: Reply with quote

The code that you show is either Fortran IV or Fortran-66, which did not have LOGICAL or CHARACTER variables, and that is the reason for the appearance of those Hollerith constants in the code.

Allowing <non-character-type-variable> = <character-type-expression> would be an extension, used for allowing old, non-conforming code to continue to work. It is not allowed in standard Fortran 77. Microsoft Fortran 5.0, for example, has this on p.117 of the Fortran Reference Manual, showing the second sentence in blue to signify that it is not standard-conforming:

"Both variable and expression must have type CHARACTER. If the $NOTSTRICT metacommand (the default) is in effect, then a character expression can be assigned to a noncharacter variable...".
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Fri Aug 30, 2019 1:21 pm    Post subject: Reply with quote

Do not forget about the compiler stability to this bug/feature which made it to become crazy and spew the garbage. Reduce the text to 4 bytes
Code:
filename = 'zzzO'
and the bug either disappear or gets under the carpet. We need rock stable compiler
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Fri Aug 30, 2019 1:25 pm    Post subject: Reply with quote

For the file I part listed, FTN95 with /-IMP compiled many routines with only a few warnings. It did not report an error until line 771.

I think Dan should be prepared to look more extensively for the coding error, then try using SDBG once he gets to creating a .exe.

The following is extracted from drain.lis
Using character constants in real*8 is accepted.
( I have not looked at this code in 30 years)
Code:
Compiler options in effect:
    ERROR_NUMBERS;INTL;LIST;LOGL;

   0737         SUBROUTINE INAXL (KFORM,TH,GH,TV,GV,GAXH,GAXV,NSTEPS,DT,FACAXH,FAC
   0738        1TMH,FACAXV,FACTMV,IEQFM)
   0739   C
   0740         IMPLICIT INTEGER*4 (I-N)
   0741         IMPLICIT REAL*8 (A-H,O-Z)
   0742   C
   0743   C     SET UP EARTHQUAKE RECORDS
   0744   C
   0745         COMMON /CONTR/ NELGR,NEQ,MBAND,NPTH,NPTV,NSTO,JCOL
   0746   C
   0747         DIMENSION KFORM(1),TH(1),GH(1),TV(1),GV(1),GAXH(1),GAXV(1),
   0748        1          IEQFM(1)
   0749   C
   0750         DATA XPR, YPR /3H X , 3H Y /
   0751   C
COMMENT - 1000: The CHARACTER(LEN=3) constant " X " is shorter than the REAL(KIND=2) variable XPR, so will be space-extended
COMMENT - 1000: The CHARACTER(LEN=3) constant " Y " is shorter than the REAL(KIND=2) variable YPR, so will be space-extended
   0752         IF (NPTH.NE.0) GO TO 20
   0753         DO 10 I=1,NEQ
   0754         IF (IEQFM(I).EQ.2) IEQFM(I)=4
   0755      10 CONTINUE
   0756         GO TO 80
   0757      20 READ (5,30) (TH(I),GH(I),I=1,NPTH)
   0758      30 FORMAT(12F6.0)
   0759         IF (KFORM(1).NE.0) WRITE (6,40) XPR,(TH(I),GH(I),I=1,NPTH)
   0760      40 FORMAT (24H1GROUND ACCELERATIONS IN, A3, 19HDIRECTION, AS INPUT///
   0761        1        5(4X, 4HTIME, 7X, 5HACCEL, 3X)  //
   0762        2        (5(F 8.3, F12.4, 3X)))
   0763   C
   0764         DO 50 I=1,NPTH
   0765         GH(I)=GH(I)*FACAXH
   0766      50 TH(I)=TH(I)*FACTMH
   0767   C
   0768         IF (NSTEPS.LE.0) GO TO 80
   0769         CALL INTPOL (TH,GH,GAXH,DT,NSTEPS)
   0770   C
   0771         IF (KFORM(2).NE.0) WRITE (6,60) XPR,(N,GAXH(N),N=1,NSTEPS)
*** Error 817: Array subscript for first rank of KFORM, 2, is greater than the declared upper bound, 1
   0772      60 FORMAT (24H1GROUND ACCELERATIONS IN, A3,
   0773        1        37HDIRECTION, AS SCALED AND INTERPOLATED  ///
   0774        2        5(5H STEP, 7X, 5HACCEL, 5X)  //
   0775        3        (5(I5, F12.3, 5X)))
   0776   C
   0777         GA=0.
   0778         DO 70 I=1,NSTEPS
   0779         GAXH(I)=GAXH(I)-GA
   0780      70 GA=GAXH(I)+GA
   0781   C
   0782      80 IF (NPTV.NE.0) GO TO 100
   0783         DO 90 I=1,NEQ
   0784         IF (IEQFM(I).EQ.3) IEQFM(I)=4
   0785      90 CONTINUE
   0786         GO TO 130
   0787     100 READ (5,30) (TV(I),GV(I),I=1,NPTV)
   0788         IF (KFORM(1).NE.0) WRITE (6,40) YPR,(TV(N),GV(N),N=1,NPTV)
   0789   C
   0790         DO 110 I=1,NPTV
   0791         GV(I)=GV(I)*FACAXV
   0792     110 TV(I)=TV(I)*FACTMV
   0793   C
   0794         IF (NSTEPS.LE.0) GO TO 130
   0795         CALL INTPOL (TV,GV,GAXV,DT,NSTEPS)
   0796   C
   0797         IF (KFORM(2).NE.0) WRITE (6,60) YPR,(N,GAXV(N),N=1,NSTEPS)
   0798   C


Last edited by JohnCampbell on Fri Aug 30, 2019 1:30 pm; edited 1 time in total
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Fri Aug 30, 2019 1:29 pm    Post subject: Reply with quote

..ctd
Code:
   0789   C
   0790         DO 110 I=1,NPTV
   0791         GV(I)=GV(I)*FACAXV
   0792     110 TV(I)=TV(I)*FACTMV
   0793   C
   0794         IF (NSTEPS.LE.0) GO TO 130
   0795         CALL INTPOL (TV,GV,GAXV,DT,NSTEPS)
   0796   C
   0797         IF (KFORM(2).NE.0) WRITE (6,60) YPR,(N,GAXV(N),N=1,NSTEPS)
   0798   C
*** Error 817: Array subscript for first rank of KFORM, 2, is greater than the declared upper bound, 1
   0799         GA=0.
   0800         DO 120 I=1,NSTEPS
   0801         GAXV(I)=GAXV(I)-GA
   0802     120 GA=GAXV(I)+GA
   0803   C
   0804     130 RETURN
   0805         END


/OLD will fix this problem.
For default options, real = character is accepted.
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Fri Aug 30, 2019 3:32 pm    Post subject: Reply with quote

For John's Drain-2D program (terminate the fragment he gave with a line containing END), using the /ISO option gives

Code:
0026)       DATA CHEK/5HSTART,5HSTOP /
*** You cannot use the CHARACTER(LEN=5) constant "START" to initialise the REAL(KIND=2) variable CHEK


and similar messages for the other instances of initialising REAL variables with Hollerith constants in DATA statements.

Dan may consider trying /ISO, but also be prepared for lots of warnings for minor deviations from standard Fortran.
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Sat Aug 31, 2019 4:34 am    Post subject: Re: Reply with quote

mecej4 wrote:
Dan may consider trying /ISO, but also be prepared for lots of warnings for minor deviations from standard Fortran.
Well or not but /ISO found no problems with my demo above
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Sat Aug 31, 2019 10:19 am    Post subject: Reply with quote

You are correct. However, when there are multiple errors in adjacent lines of source, many compilers are able to detect only a subset of all the errors in those lines.

Likewise, a compiler may not even scan the rest of the source code of a program unit after finding a severe error.

I have found that when I compile a number of source files with a single command and one the files contains a major error the compiler will terminate the compilation immediately, not even looking at the remaining source files (named in the command line, or implicitly using *.f90), and I have to list the directory to see which files were not compiled.
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Sat Aug 31, 2019 4:33 pm    Post subject: Re: Reply with quote

mecej4 wrote:
Likewise, a compiler may not even scan the rest of the source code of a program unit after finding a severe error.
Looks like compiler did not consider this as severe error or as an error at all.

Great would be if cryptic diagnostics messages with "unwritable" wording substituted with the clear and exact ones other compilers demonstrated above
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Sun Sep 01, 2019 5:32 am    Post subject: Reply with quote

Dan,

I think I understand your problem with interpreting "Non-writable" could also have included "to parameter".
I find that using PLATO and having access to both FTN95 and gFortran does help for interpreting error messages, by easily switching between (three) compilers.

FTN95 message is:
C:\temp\forum\dan\dan2.F90(8) : error 304 - Non-writable expression in READ statement
C:\temp\forum\dan\dan2.F90(8) : error 52 - Compilation abandoned

gFortran message is:
C:\temp\forum\dan\dan2.f90(8) : error - Named constant 'iz' in variable definition context (item in READ) at column 1
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Sun Sep 01, 2019 6:10 am    Post subject: Reply with quote

Yes, in this case gfortran which may miss many errors compared to FTN95 wins hands down in clarity, you know this comparison here

https://www.fortran.uk/fortran-compiler-comparisons/win32-fortran-compiler-comparisons-diagnostic-capabilities/

- and since years ago this table was made the FTN95 added many more features and diagnostic capabilities (catch trimmed variables at the 72/132 boundary, for example, double declaration of variables in common etcetc. Not listed are mismatch of size of common blocks and many many other errors. And if add useful non-standard and graphics and opengl supporting features this green list of FTN95 will be 100x longer, you perfectly know that, i just mention this for the newbies).

Still to my South Antarctic taste this gfortran error message above could be improved further
Code:
*** "It is forbidden to change PARAMETER iz illegaly used in READ statement on line XXX"

From day one i'm using FTN77-95 i like it finds more errors than any other compiler and many more than i can find myself but hate its error diagnostics language. It is simply unacceptable if the company ever wanted its compiler to be adopted by general public.
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> General All times are GMT + 1 Hour
Goto page Previous  1, 2, 3
Page 3 of 3

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group