Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Translate Fortran 77 to Fortran 95

2,408 views
Skip to first unread message

russ

unread,
Aug 20, 2015, 9:26:24 AM8/20/15
to
Can anyone recommend a reference for translating Fortran 77 idioms to
Fortran 95 idioms? This is more than just translating fixed form to free
form.

I've been tasked with making an estimate for converting old Fortran 77
code to Fortran 95 making some improvements, such as:
1)Make it compile with f95 compiler from the gfortran package.
2)Add IMPLICIT NONE ;
3)Use MODULES;
4)Eliminate GOTO;
5)Eliminate jumping out of loops;
6)Do something about COMMON blocks (mostly used as part of memory
management by linker script and to simulate a kind of C struct);
And more.

The code below illustrates the problem. It occurs lots in the old
program with only slight variations.

jascii = 1
10 continue
read(12,rec=jasc,err=1000,end=100) iascii, text
if( iascii .eq. -1 ) then ! EOD marker found
text = 'END OF DATABASE FILE'
write(16,'(i5,a)') iascii, text
stop
endif
do 20 j=76,1,-1 ! trim right spaces
if( text(j:j) .ne. ' ' ) then
ilen = j
go to 30
endif
20 continue
c Text is only spaces. Write out record number.
write(16,'(i5)') iascii
jascii = jascii + 1
go to 10
30 continue
!Code to parse text
write(16,'(i5,a)') iasc, text(1:ilen)
jascii = jascii + 1
go to 10
100 continue !EOF before EOD
text = 'EOF BEFORE END OF DATA'
write(16, '(a)') text
stop ' '


1000 print *,'read 12 error'
stop

Beliavsky

unread,
Aug 20, 2015, 10:26:49 AM8/20/15
to
On Thursday, August 20, 2015 at 9:26:24 AM UTC-4, russ wrote:
> Can anyone recommend a reference for translating Fortran 77 idioms to
> Fortran 95 idioms? This is more than just translating fixed form to free
> form.

A good book is "Upgrading to Fortran 90" by Cooper Redwine. Some free translation tools are to_f90 http://jblevins.org/mirror/amiller/to_f90.f90 and ezup http://amiller.nmsu.edu/ezup.html . There are commercial tools such as plusFORT http://www.adeptscience.co.uk/products/fortran-tools/plusfort-with-spag/spag-fortran-code-restructuring.html .

robin....@gmail.com

unread,
Aug 20, 2015, 10:31:14 AM8/20/15
to
Fortran 90 Handbook: Adams, Brainerd, Martin, Smith, Wegener

russ

unread,
Aug 20, 2015, 11:59:02 AM8/20/15
to
That is a good book, everyone should have a copy. But not what I was
looking for. I need more of a style guide that shows common tasks in
Fortran 66/77 and a recommends way to do the same thing in Fortran 90.
For example the code above between 10 and 30 is an idiom to read each
line in a file, processes it, and write it to an output file. Valid
Fortran 77, but not Fortran 90/95. So what would be a good Fortran 95
idiom to do the same thing?
Another example is the code should be re-written as a subroutine in a
module such that the comment "! Code to parse text" could be replaced
with a function call supplied as a parameter.

Paul van Delst

unread,
Aug 20, 2015, 12:15:20 PM8/20/15
to
Crikey! <shudders>

First off, I would say one's person's idioms is anothers sh*t code. Ha
ha. It's not clear to me that the Fortran community is cohesive enough
to declare what is and isn't idiomatic Fortran95/2003/2008.

Regarding the example you gave I can respond as to how I would redesign.
Basically:

1) Use NEWUNIT for opening files. No unit numbers!
2) Use IOSTAT and IOMSG in file I/O, not END/ERR
3) Label your loop constructs
4) Replace GOTO with BREAK and CYCLE
5) Make use of the great new intrinsics in Fortran90+

But, as always, YMMV...

! Open the files
open(newunit=input_fid,...other specifiers...) ! ** Use NEWUNIT
open(newunit=output_fid,...other specifiers...)

! Read the input file in an open loop
jascii = 0
read_loop: DO

! Read a record
jascii = jascii + 1
READ(input_fid,rec=jascii,iostat=io_stat,iomsg=io_msg) iascii, text

! Process io_stat /= 0
! ...Are we at EOF?
IF ( io_stat < 0 ) THEN
msg = 'EOF BEFORE END OF DATA'
CALL msg_display(msg,FAILURE)
STOP ! Really? You want to stop?
END IF
! ...Was there an error?
IF ( io_stat > 0 ) THEN
msg = 'ERROR READING FILE - '//TRIM(io_msg)
CALL msg_display(msg,FAILURE)
STOP
END IF

! Are we at the end of the database?
IF ( iascii == -1 ) BREAK read_loop

! Print out record number if the text is only spaces
IF ( LEN_TRIM(text) == 0 ) THEN
WRITE(output_fid,'(i5)') iascii
CYCLE read_loop
END OF

! Print out the text
WRITE(output_fid,'(i5,1x,a)') iascii, TRIM(text)

END DO read_loop
CLOSE(input_fid)


Other than that, my other personal choices would be:
- Rather than STOP, I would set an error flag and return that for
checking in the caller, e.g.
- Following on from that, I would have an internal procedure that deals
with error recovery (prints out message, closes files, deallocates
memory, etc).

So the code that looks like:

SUBROUTINE my_new_read_procedure(....)

...code...

! ...Was there an error?
IF ( io_stat > 0 ) THEN
msg = 'ERROR READING FILE - '//TRIM(io_msg)
CALL msg_display(msg,FAILURE)
STOP
END IF

...code...

END SUBROUTINE my_new_read_procedure


would change to something like


SUBROUTINE my_new_read_procedure(...., err_stat)

err_stat = SUCCESS

...code...

! ...Was there an error?
IF ( io_stat > 0 ) THEN
msg = 'ERROR READING FILE - '//TRIM(io_msg)
CALL Cleanup(); RETURN
END IF

...code...

CONTAINS

SUBROUTINE Cleanup()
err_stat = FAILURE
CLOSE(input_fid,IOSTAT=io_stat)
CLOSE(output_fid,IOSTAT=io_stat)
...anything else that would need doing...
CALL Msg_Display(msg,err_stat)
END SUBROUTINE Cleanup

END SUBROUTINE my_new_read_procedure

Paul van Delst

unread,
Aug 20, 2015, 12:20:00 PM8/20/15
to
On 08/20/15 12:15, Paul van Delst wrote:
> First off, I would say one's person's idioms ....

"one's person's" ???

I need to do a remedial writing course. Sigh.

Lynn McGuire

unread,
Aug 20, 2015, 1:12:24 PM8/20/15
to
I'm there too. I am fairly sure that all of my English teachers are spinning in their graves.

Lynn

Lynn McGuire

unread,
Aug 20, 2015, 1:17:37 PM8/20/15
to
Of all those admirable upgrades, the IMPLICIT NONE is the first most difficult to implement. Unless, you are lucky and all of the
variables were declared already. Usually though, they just used the old I-N rule that those variables are integer and everything
else is a real*4. We used a shell script on our code to create the declarations but I have no idea where it went over the years.

Good luck on the goto's. There used to be a product called FOR_STRUCT to restructure code and get rid of the gotos.
http://www.cobalt-blue.com/fs/fsmain.htm

Lynn

Lynn

FortranFan

unread,
Aug 20, 2015, 1:59:16 PM8/20/15
to
On Thursday, August 20, 2015 at 12:15:20 PM UTC-4, Paul van Delst wrote:

>
> 1) Use NEWUNIT for opening files. No unit numbers!
> 2) Use IOSTAT and IOMSG in file I/O, not END/ERR
> 3) Label your loop constructs
> 4) Replace GOTO with BREAK and CYCLE
> 5) Make use of the great new intrinsics in Fortran90+
>

Didn't OP say Fortran 95? NEWUNIT is not supported by that standard revision. Also, BREAK is not part of any Fortran standard, as far as I know. Did you mean EXIT?

Paul van Delst

unread,
Aug 20, 2015, 2:25:27 PM8/20/15
to


On 08/20/15 13:59, FortranFan wrote:
> On Thursday, August 20, 2015 at 12:15:20 PM UTC-4, Paul van Delst
> wrote:
>
>>
>> 1) Use NEWUNIT for opening files. No unit numbers! 2) Use IOSTAT
>> and IOMSG in file I/O, not END/ERR 3) Label your loop constructs 4)
>> Replace GOTO with BREAK and CYCLE 5) Make use of the great new
>> intrinsics in Fortran90+
>>
>
> Didn't OP say Fortran 95? NEWUNIT is not supported by that standard
> revision.

Good point. But, these days, I'm comfy suggesting people not start new
coding using a 20 year old standard. :o) And I include refactoring in
that definition of "new".

I would go with at least f2003, and as many "common" items of f2008 that
the majority of fortran compilers support.

<OT>
In my case, given the history of compiler vendors implementing a
complete standard before moving onto features of the next one, I've
given up resolutely requiring adherence to a particular Fortran standard
in code submissions (mine or contributors). If it builds on my test
systems using gfortran, ifort, and pgi, and all the regression and unit
tests pass, it's o.k.

So, for example, even though NEWUNIT is Fortran2008, I use it for all my
new (and newly refactored) code. Any stick-to-the-standard requirement I
come up with would also deny me the use of this extremely handy feature.
</OT>

> Also, BREAK is not part of any Fortran standard, as far as
> I know. Did you mean EXIT?

D'oh! Yes, I meant EXIT. Thank you! (OP take note!!!!)

I was just writing some IDL code doing sort-of similar stuff so my head
was full of CONTINUE and BREAK instead of CYCLE and EXIT. I'm assuming
since I recognise CONTINUE as a Fortran statement that's why I correctly
used CYCLE, but flubbed the BREAK/EXIT pair.

It's turning into one of those weeks....

Thanks again for catching my error.

cheers,

paulv

Beliavsky

unread,
Aug 20, 2015, 3:12:42 PM8/20/15
to
On Thursday, August 20, 2015 at 2:25:27 PM UTC-4, Paul van Delst wrote:
> On 08/20/15 13:59, FortranFan wrote:
> > On Thursday, August 20, 2015 at 12:15:20 PM UTC-4, Paul van Delst
> > wrote:
> >
> >>
> >> 1) Use NEWUNIT for opening files. No unit numbers! 2) Use IOSTAT
> >> and IOMSG in file I/O, not END/ERR 3) Label your loop constructs 4)
> >> Replace GOTO with BREAK and CYCLE 5) Make use of the great new
> >> intrinsics in Fortran90+
> >>
> >
> > Didn't OP say Fortran 95? NEWUNIT is not supported by that standard
> > revision.
>
> Good point. But, these days, I'm comfy suggesting people not start new
> coding using a 20 year old standard. :o) And I include refactoring in
> that definition of "new".
>
> I would go with at least f2003, and as many "common" items of f2008 that
> the majority of fortran compilers support.
>
> <OT>
> In my case, given the history of compiler vendors implementing a
> complete standard before moving onto features of the next one, I've
> given up resolutely requiring adherence to a particular Fortran standard
> in code submissions (mine or contributors).

I think you meant vendors NOT implementing a complete standard before moving onto features of the next one.

Paul van Delst

unread,
Aug 20, 2015, 3:36:35 PM8/20/15
to
> beforemoving onto features of the next one.

Yes, that is what I meant.

I figured the use of the word "history" would imply that but I guess
that path is a tortuous one.... and requires a "wink, wink" too.

cheers,

paulv

FortranFan

unread,
Aug 20, 2015, 3:57:04 PM8/20/15
to
On Thursday, August 20, 2015 at 2:25:27 PM UTC-4, Paul van Delst wrote:
> On 08/20/15 13:59, FortranFan wrote:
> > On Thursday, August 20, 2015 at 12:15:20 PM UTC-4, Paul van Delst
> > wrote:
> >
> >>
> >> 1) Use NEWUNIT for opening files. No unit numbers! 2) Use IOSTAT
> >> and IOMSG in file I/O, not END/ERR 3) Label your loop constructs 4)
> >> Replace GOTO with BREAK and CYCLE 5) Make use of the great new
> >> intrinsics in Fortran90+
> >>
> >
> > Didn't OP say Fortran 95? NEWUNIT is not supported by that standard
> > revision.
>
> Good point. But, these days, I'm comfy suggesting people not start new
> coding using a 20 year old standard. :o) And I include refactoring in
> that definition of "new".
>

Isn't Fortran 95 is the latest standard revision that is supported by the largest number of compilers and that is what motivates OP to select Fortran 95 as the basis for their task at hand? It could have Fortran 2003, but compiler writers unfortunately seem to struggle with implementing the parameterized data types feature.

Paul van Delst

unread,
Aug 20, 2015, 4:17:09 PM8/20/15
to
Yeah, sure. But I qualify that with a "whatever". (ha ha)

You can make that argument (and I'm not saying it's not a valid one in
some circumstances). But if I can use a new feature that saves me time
and makes the code more robust, more flexible, more <insert positive
attribute here>, runs on all the operational systems I use, and the
*only* argument against it is that not every compiler out there supports
this new feature (and the remaining family of features), well, I'll just
nod politely. I deal with enough red tape without manufacturing my own.

:o)

cheers,

paulv








lyttlec

unread,
Aug 20, 2015, 4:24:36 PM8/20/15
to
On 08/20/2015 12:15 PM, Paul van Delst wrote:
>SNIP<
> Crikey! <shudders>
>
> First off, I would say one's person's idioms is anothers sh*t code. Ha
> ha. It's not clear to me that the Fortran community is cohesive enough
> to declare what is and isn't idiomatic Fortran95/2003/2008.
>
> So the code that looks like:
>SNIP<

> SUBROUTINE my_new_read_procedure(...., err_stat)
>
> err_stat = SUCCESS
>
> ...code...
>
> ! ...Was there an error?
> IF ( io_stat > 0 ) THEN
> msg = 'ERROR READING FILE - '//TRIM(io_msg)
> CALL Cleanup(); RETURN
> END IF
>
> ...code...
>
> CONTAINS
>
> SUBROUTINE Cleanup()
> err_stat = FAILURE
> CLOSE(input_fid,IOSTAT=io_stat)
> CLOSE(output_fid,IOSTAT=io_stat)
> ...anything else that would need doing...
> CALL Msg_Display(msg,err_stat)
> END SUBROUTINE Cleanup
>
> END SUBROUTINE my_new_read_procedure
This is the kind of thing needed. I agree that no matter what idiom is
selected, there will be lots of push-back by those who want to do it
differently. There are lots of Fortran idioms scattered about. I'm
hoping that out there somewhere are collections of idioms someone liked.

lyttlec

unread,
Aug 20, 2015, 4:36:13 PM8/20/15
to
On 08/20/2015 01:17 PM, Lynn McGuire wrote:
>SNIP<
> Of all those admirable upgrades, the IMPLICIT NONE is the first most
> difficult to implement. Unless, you are lucky and all of the variables
> were declared already. Usually though, they just used the old I-N rule
> that those variables are integer and everything else is a real*4. We
> used a shell script on our code to create the declarations but I have no
> idea where it went over the years.
>
> Good luck on the goto's. There used to be a product called FOR_STRUCT
> to restructure code and get rid of the gotos.
> http://www.cobalt-blue.com/fs/fsmain.htm
>
> Lynn
>
> Lynn
I already found how much work the IMPLICIT NONE is going to be if there
isn't automation. I've already have Fortran parsers, so it should be
possible to adapt one of these to do nothing but find identifiers and
emit declarations for them.

Thomas Koenig

unread,
Aug 20, 2015, 5:23:51 PM8/20/15
to
lyttlec <lyt...@removegmail.com> schrieb:

> I already found how much work the IMPLICIT NONE is going to be if there
> isn't automation. I've already have Fortran parsers, so it should be
> possible to adapt one of these to do nothing but find identifiers and
> emit declarations for them.

NAG Toolpack (can still be found ...) and ftncheck both can be used
for this. Toopack is also useful in restructuring some aspects of GOTO
forests.

Steve Kargl

unread,
Aug 20, 2015, 6:10:53 PM8/20/15
to
On 8/20/2015 8:58 AM, russ wrote:
> Valid Fortran 77, but not Fortran 90/95. So what would be a good Fortran 95
> idiom to do the same thing?

If it is valid Fortran 77, then it's valid Fortran 90/95.

--
steve

glen herrmannsfeldt

unread,
Aug 20, 2015, 6:41:59 PM8/20/15
to
Except for a very small list of features rarely used.
(REAL DO variables, for one.)

-- glen

dpb

unread,
Aug 20, 2015, 7:10:31 PM8/20/15
to
If it's all as well organized as this, personally I'd not worry much
about the GOTOs nor the breaks; you'll end up with CYCLE and the like
anyway from an automated converter and not necessarily any more and
perhaps far less) readable/maintainble than what you've got.

IMPLICIT NONE and some of the others I'm in agreement with...

--

Richard Maine

unread,
Aug 20, 2015, 9:08:37 PM8/20/15
to
From context, I find it fairly clear that he meant conversion to
idiomatic f95 style rather than just to conform to the f95 standard.
Others have made some suggestions relating to that, to which I don't
have a lot to add. I'll second the recommendation of Cooper Redwine's
book if you can find a copy.(It is long out of print). I don't think
you'll find a book that does a thorough job of covering the idiomatic
changes, as you'll find it hard for people to agree on the best idioms
in all cases.

I mostly posted to note one pet nit of mine about the old code. It
actually has an erroneous f77 idiom that I've seen several times. I
think it conforms to the standard, but it certainly doesn't make sense
according to the standard (and it might actually be in violation - not
handy for me to check at the moment from this hotel room).

The end= specifier makes no sense (and might even be invalid) in a
direct access read statement. The standard does not allow an EOF
condition in a direct access read.

--
Richard Maine
email: last name at domain . net
domain: summer-triangle

robin....@gmail.com

unread,
Aug 20, 2015, 9:15:45 PM8/20/15
to
On Friday, August 21, 2015 at 1:59:02 AM UTC+10, russ wrote:
FORTRAN 66 now?

> and a recommends way to do the same thing in Fortran 90.

The posted code is FORTRAN 77.
That's already valid F90+.

> For example the code above between 10 and 30 is an idiom to read each
> line in a file, processes it, and write it to an output file. Valid
> Fortran 77, but not Fortran 90/95.

Looks like valid F90+ to me.

> So what would be a good Fortran 95
> idiom to do the same thing?

There's some code to remove trailing blanks.
Use the TRIM function instead.
READ statements are still READ statements.
WRITE statements are still WRITE statements.

Steve Kargl

unread,
Aug 21, 2015, 12:24:04 AM8/21/15
to
I'm well aware of the delete features lists as I
am the person that gave gfortran the ability to
deal with REAL DO variables. I doubt that there
has ever been a Fortran 95 compiler that did not
support delete features.

--
steve


glen herrmannsfeldt

unread,
Aug 21, 2015, 2:25:04 AM8/21/15
to
Steve Kargl <sgkR...@troutmask.apl.washington.edu> wrote:
> On 8/20/2015 3:41 PM, glen herrmannsfeldt wrote:
>> Steve Kargl <sgkR...@troutmask.apl.washington.edu> wrote:

(snip)
>>> If it is valid Fortran 77, then it's valid Fortran 90/95.

>> Except for a very small list of features rarely used.
>> (REAL DO variables, for one.)

> I'm well aware of the delete features lists as I
> am the person that gave gfortran the ability to
> deal with REAL DO variables. I doubt that there
> has ever been a Fortran 95 compiler that did not
> support delete features.

I didn't doubt that you knew them, but wasn't sure that
the OP knew them.

Some (many) years ago, I did some translating of BASIC programs
to Fortran. With most versions of BASIC, all variables are
floating point, so REAL DO variables are convenient. Also,
allowing REAL variables as subscripts helps, too. Both features
rarely used, but when used are very convenient.

-- glen

glen herrmannsfeldt

unread,
Aug 21, 2015, 2:44:37 AM8/21/15
to
Richard Maine <nos...@see.signature> wrote:
> Steve Kargl <sgkR...@troutmask.apl.washington.edu> wrote:

>> On 8/20/2015 8:58 AM, russ wrote:
>> > Valid Fortran 77, but not Fortran 90/95. So what would be
>> > a good Fortran 95 idiom to do the same thing?

>> If it is valid Fortran 77, then it's valid Fortran 90/95.

> From context, I find it fairly clear that he meant conversion to
> idiomatic f95 style rather than just to conform to the f95 standard.

I wondered about this at the time. Going back, I now see why.

I read the statement:

"Valid Fortran 77, but not Fortran 90/95."

as short for:

"Valid Fortran 77, but not valid Fortran 90/95."

(That is, if it isn't valid Fortran 95 then it isn't Fortran 95.)

But now I see it can be read differently.

> Others have made some suggestions relating to that, to which I don't
> have a lot to add. I'll second the recommendation of Cooper Redwine's
> book if you can find a copy.(It is long out of print). I don't think
> you'll find a book that does a thorough job of covering the idiomatic
> changes, as you'll find it hard for people to agree on the best idioms
> in all cases.

My thought on first reading this was that the OP was looking for
an automated, or at least partly automated system.

It might be that not so many can be done, but if they are used
enough, and can be done reliably, it would be nice.

It would be interesting to have a program that would add

IMPLICIT NONE

and at the same time add declarations for previously implicit
declared variables. It would then be fairly easy to go down the
list and verify that they are right. Maybe also detect similar,
and possibly misspelled names.

> I mostly posted to note one pet nit of mine about the old code. It
> actually has an erroneous f77 idiom that I've seen several times. I
> think it conforms to the standard, but it certainly doesn't make sense
> according to the standard (and it might actually be in violation - not
> handy for me to check at the moment from this hotel room).

> The end= specifier makes no sense (and might even be invalid) in a
> direct access read statement. The standard does not allow an EOF
> condition in a direct access read.

I didn't notice that one.

-- glen




Arjen Markus

unread,
Aug 21, 2015, 5:31:23 AM8/21/15
to
Op vrijdag 21 augustus 2015 08:44:37 UTC+2 schreef glen herrmannsfeldt:

>
> It would be interesting to have a program that would add
>
> IMPLICIT NONE
>
> and at the same time add declarations for previously implicit
> declared variables. It would then be fairly easy to go down the
> list and verify that they are right. Maybe also detect similar,
> and possibly misspelled names.
>

I came across this problem last week and my idea was to insert the IMPLICIT NONE statement and have the compiler sort out which variables lack a proper declarations. By analysing the error messages you could then insert a declaration for these variables. Maybe not the most thorough way to do it, but at you can leave the hard part (identify the names of the variables) to a piece of software that already does that and is known to be tested for that sort of job.

Regards,

Arjen

Gordon Sande

unread,
Aug 21, 2015, 8:40:24 AM8/21/15
to
Several compilers that I use have error messages that give the subroutine name,
the line number and the undeclared varaible. A minor amount of work wth a
text editor gives a list of the required fixes. Some compilers are too happy to
complain so you get told for each usage which makes the unduplication feature
of the text editor very handy. The only bother is you need to insert
the "implicit
none" but that is easier with a search and paste that you quickly
develop muscle
memory for doing. The editors I have used all deal gracefully with
multiple files
so even the one routine per file is not really much extra fuss.




Beliavsky

unread,
Aug 21, 2015, 8:51:05 AM8/21/15
to
On Friday, August 21, 2015 at 5:31:23 AM UTC-4, Arjen Markus wrote:
> Op vrijdag 21 augustus 2015 08:44:37 UTC+2 schreef glen herrmannsfeldt:
>
> >
> > It would be interesting to have a program that would add
> >
> > IMPLICIT NONE
> >
> > and at the same time add declarations for previously implicit
> > declared variables. It would then be fairly easy to go down the
> > list and verify that they are right. Maybe also detect similar,
> > and possibly misspelled names.
> >
>
> I came across this problem last week and my idea was to insert the IMPLICIT NONE statement and have the compiler sort out which variables lack a proper declarations. By analysing the error messages you could then insert a declaration for these variables.

A difficulty of adding IMPLICIT NONE to a large code is that you must make many changes to make the code compile by adding lots of declarations, and if the revised code does not match the original, you need to identify which declaration was incorrect. An incremental way to declare variables is to use an implicit none compiler option, for example -fimplicit-none in gfortran, fix the first few undeclared variables, compile without the implicit none option, check that the results are the same as the original code, and iterate.

lyttlec

unread,
Aug 21, 2015, 12:43:22 PM8/21/15
to
Not necessarily. In this case the read( ) doesn't compile.
Fortran 77 lets it have the "end=100", Fortran 95 does not.

Steve Kargl

unread,
Aug 21, 2015, 12:45:44 PM8/21/15
to
On 8/20/2015 6:08 PM, Richard Maine wrote:
> Steve Kargl <sgkR...@troutmask.apl.washington.edu> wrote:
>
>> On 8/20/2015 8:58 AM, russ wrote:
>>> Valid Fortran 77, but not Fortran 90/95. So what would be a good Fortran 95
>>> idiom to do the same thing?
>>
>> If it is valid Fortran 77, then it's valid Fortran 90/95.
>
> From context, I find it fairly clear that he meant conversion to
> idiomatic f95 style rather than just to conform to the f95 standard.

There in lies the rub. Define idiomatic.

>
> I mostly posted to note one pet nit of mine about the old code. It
> actually has an erroneous f77 idiom that I've seen several times. I
> think it conforms to the standard, but it certainly doesn't make sense
> according to the standard (and it might actually be in violation - not
> handy for me to check at the moment from this hotel room).
>
> The end= specifier makes no sense (and might even be invalid) in a
> direct access read statement. The standard does not allow an EOF
> condition in a direct access read.

The code isn't valid Fortran 77. From page 12-15:

A control information list must not contain both a record
specifier and an end-of-file specifier.

--
steve




Ron Shepard

unread,
Aug 21, 2015, 12:51:47 PM8/21/15
to
On 8/21/15 1:44 AM, glen herrmannsfeldt wrote:
> It would be interesting to have a program that would add
>
> IMPLICIT NONE
>
> and at the same time add declarations for previously implicit
> declared variables. It would then be fairly easy to go down the
> list and verify that they are right. Maybe also detect similar,
> and possibly misspelled names.

I think it would be useful as a first step to have this kind of tool.
But most programs have their own conventions for how variables are
declared, and it might be difficult for a general tool to conform to
these conventions, so some manual effort might be required in the end in
any case.

For example, I *never* use DIMENSION statements in my code, and I
especially dislike seeing them used to declare multiple arrays of
different types or kinds in a single statement. For a general tool to
handle these types of declarations and to convert them to the way I like
would require some substantial code rearrangements.

$.02 -Ron Shepard

lyttlec

unread,
Aug 21, 2015, 12:52:41 PM8/21/15
to
The original was in Fortran 66 reading tapes. The EOF indicated an
attempt to read past the end of the tape. Not real direct access, but
some tapes could back-up to previous records without completely
re-winding. It was later re-worked into Fortran 77. f2c thinks the code
is ok, probably trying to be backward compatible with someone's idea of
a Fortran 66 compiler.

Tim Prince

unread,
Aug 21, 2015, 12:53:17 PM8/21/15
to
It's already been pointed out by at least one expert that combining rec=
with end= was never valid. One thing which changed in Fortran 90 was
that options began to be required to diagnose some syntax errors, but
whether this is one of those, I don't know. It doesn't look like a case
of a meaningful extension to f77 nor one which f77 compilers were
forbidden from diagnosing.

lyttlec

unread,
Aug 21, 2015, 1:37:01 PM8/21/15
to
On 08/20/2015 09:15 PM, robin....@gmail.com wrote:
> On Friday, August 21, 2015 at 1:59:02 AM UTC+10, russ wrote:

>> That is a good book, everyone should have a copy. But not what I was
>> looking for. I need more of a style guide that shows common tasks in
>> Fortran 66/77
>
> FORTRAN 66 now?
>
Some of the code is actually not valid Fortran 77, but is Fortran 66
that was accepted by f2c. It passed as valid back in the 1980s.

>> and a recommends way to do the same thing in Fortran 90.
>
> The posted code is FORTRAN 77.
> That's already valid F90+.
>
Not the read statement. Elsewhere some of the write statements need to
be re-worked.
>> For example the code above between 10 and 30 is an idiom to read each
>> line in a file, processes it, and write it to an output file. Valid
>> Fortran 77, but not Fortran 90/95.
>
> Looks like valid F90+ to me.
>
>> So what would be a good Fortran 95
>> idiom to do the same thing?
>
> There's some code to remove trailing blanks.
> Use the TRIM function instead.
> READ statements are still READ statements.
> WRITE statements are still WRITE statements.
>
One problem to solve is that copies of the code exist throughout the
program with different functionality where the example is simply
removing trailing blanks. Two different processes : Read a record (from
somewhere), process the record, write new record(s) somewhere.

lyttlec

unread,
Aug 21, 2015, 1:40:11 PM8/21/15
to
So far I haven't seen that on this project. But there are some very
creative integers.

lyttlec

unread,
Aug 21, 2015, 1:43:38 PM8/21/15
to
The customer has been burnt by supposedly compliant Fortran 2003
compilers. Fortran 95 seems to be the last version with compilers that
have proven themselves in applications similar to my project.

lyttlec

unread,
Aug 21, 2015, 2:01:37 PM8/21/15
to
ftnchek -declare helps with IMPLICIT NONE. I had the NAG Toolpack in the
past, but not now. Looks like someone thinks it should be locked up to
keep it away from terrorist.

lyttlec

unread,
Aug 21, 2015, 2:05:52 PM8/21/15
to
On 08/20/2015 07:10 PM, dpb wrote:
> On 08/20/2015 8:26 AM, russ wrote:
>> >SNIP<
>
> If it's all as well organized as this, personally I'd not worry much
> about the GOTOs nor the breaks; you'll end up with CYCLE and the like
> anyway from an automated converter and not necessarily any more and
> perhaps far less) readable/maintainble than what you've got.
>
> IMPLICIT NONE and some of the others I'm in agreement with...
>
> --
>
On the whole, the old code is of excellent quality, which is one reason
no one wants to change. But it is getting more and more difficult to
maintain.

glen herrmannsfeldt

unread,
Aug 21, 2015, 2:24:45 PM8/21/15
to
Beliavsky <beli...@aol.com> wrote:

(snip, I wrote)

>> > It would be interesting to have a program that would add

>> > IMPLICIT NONE

>> > and at the same time add declarations for previously implicit
>> > declared variables. It would then be fairly easy to go down the
>> > list and verify that they are right. Maybe also detect similar,
>> > and possibly misspelled names.

(snip)

> A difficulty of adding IMPLICIT NONE to a large code is that
> you must make many changes to make the code compile by adding
> lots of declarations, and if the revised code does not match the
> original, you need to identify which declaration was incorrect.

Yes, that is the part that I thought could be automated.

> An incremental way to declare variables is to use an implicit
> none compiler option, for example -fimplicit-none in gfortran,
> fix the first few undeclared variables, compile without the
> implicit none option, check that the results are the same as
> the original code, and iterate.

That is the not so automated way.

-- glen


dpb

unread,
Aug 21, 2015, 2:42:37 PM8/21/15
to
On 08/21/2015 1:05 PM, lyttlec wrote:
> On 08/20/2015 07:10 PM, dpb wrote:
>> On 08/20/2015 8:26 AM, russ wrote:
>>> >SNIP<
>>
>> If it's all as well organized as this, personally I'd not worry much
>> about the GOTOs nor the breaks; you'll end up with CYCLE and the like
>> anyway from an automated converter and not necessarily any more and
>> perhaps far less) readable/maintainble than what you've got.
>>
>> IMPLICIT NONE and some of the others I'm in agreement with...
>>
...

> On the whole, the old code is of excellent quality, which is one reason
> no one wants to change. But it is getting more and more difficult to
> maintain.

In what way? Unless one spends the time to really rewrite and refactor
manually similarly as to what Paul did above I'd have a hard time
thinking an automated conversion routine would provide anything an
easier to maintain than the above. I will apply a caveat that I've not
actually done that using such a tool so mayhaps they're better than I
expect.

The code I've maintained for nearly 30 year now that we moved from
VAX/VMS to OS/2 to NT looks very much like the above with a few
enhancements that the original developer did enforce declarations even
though IMPLICIT NONE wasn't used and found no cases where it wasn't
honored but otoh, it's still ALLCAPS and 7-character max names, etc.

The heritage shows however in that it has clear Digital traces in using
extensions such as the STRUCTURE/RECORD version of UDTs, etc. It is a
(slow, but) real time performance monitoring system and makes extensive
use of system interactions for sempahores, shared memory and the like,
but was set up where these are very well segregated into higher-level
user functions and the actual system-dependent stuff is down to only a
few dozen lines at most.

All in all, just to say that sometimes there really isn't much to be
gained in some forms of changes; I agree with some of the memory
management like COMMON and the like but then again, if COMMON is handled
in a set of INCLUDEs such that it's not difficult to keep in one place
the definitions and any modifications, what are module variables other
than common by another name? The above app, of course, as was
essentially mandatory for the time :) used type punning in the database
but that was all done with C routines that simply move memory and while
in some ways ugly, it's well hidden in the bowels of the code, works,
and is essentially totally transparent at the programming level of the
application and so hasn't been touched since the day it was first
completed. Why one would one waste time and energy to do something with
it just because it isn't the latest version of the Standard is beyond my
ken...

--

Richard Maine

unread,
Aug 21, 2015, 7:15:51 PM8/21/15
to
Well, f66 didn't have direct access at all. Nor did it have end=. So it
seems unlikely to me that allowing end= with direct access would have
much to do with f66 compatibility. I'd more guess it was just a
restriction that didn't get diagnosed. Recall that the f77 standard
didn't require compilers to be able to diagnose *ANY* errors.

On a direct access file, reading a record that doesn't exist (such as a
record past the last one of the file) would plausibly cause an error
condition, but not an end-of-file one. The error condition isn't
guaranteed (pretty much nothing about I/O errors is guaranteed), but it
is reasonably plausible at least for a record after the end of the file.

Richard Maine

unread,
Aug 21, 2015, 7:20:47 PM8/21/15
to
No. A specific f77 compiler apparently failed to diagnose the error.
That doesn't mean that the code was valid f77. Steve cited the specific
prohibition against this in the f77 standard. As I noted elsewhere, the
f77 standard does not require compilers to diagnose any errors at all.
That doesn't mean that code never has any errors.

glen herrmannsfeldt

unread,
Aug 21, 2015, 8:00:28 PM8/21/15
to
Richard Maine <nos...@see.signature> wrote:
> lyttlec <lyt...@removegmail.com> wrote:

(snip)

>> The original was in Fortran 66 reading tapes. The EOF indicated an
>> attempt to read past the end of the tape. Not real direct access, but
>> some tapes could back-up to previous records without completely
>> re-winding. It was later re-worked into Fortran 77. f2c thinks the code
>> is ok, probably trying to be backward compatible with someone's idea of
>> a Fortran 66 compiler.

> Well, f66 didn't have direct access at all. Nor did it have end=. So it
> seems unlikely to me that allowing end= with direct access would have
> much to do with f66 compatibility. I'd more guess it was just a
> restriction that didn't get diagnosed. Recall that the f77 standard
> didn't require compilers to be able to diagnose *ANY* errors.

OS/360 Fortran IV has both direct access and END=. As far as I know,
you aren't supposed to use them together, but I never tried.

But you would use BACKSPACE to position tapes, not direct
access I/O.

DECtapes allow direct access, as they have blocks formatted
like disk blocks. There might be machines with DECtape, Direct access,
and END=.

> On a direct access file, reading a record that doesn't exist (such as a
> record past the last one of the file) would plausibly cause an error
> condition, but not an end-of-file one. The error condition isn't
> guaranteed (pretty much nothing about I/O errors is guaranteed), but it
> is reasonably plausible at least for a record after the end of the file.

Sounds right to me.

-- glen

James Van Buskirk

unread,
Aug 21, 2015, 11:40:34 PM8/21/15
to
"lyttlec" wrote in message news:mr7p1s$ojk$1...@speranza.aioe.org...
Fixing IMPLICIT declarations in the general case is quite challenging
in my opinion because that implies being able to evaluate all
initialization expressions and that is a task that seems to be beyond
the capabilities of most compilers.

Not to mention that there are some cases where the FUNCTION
result variable is implicitly typed which the standard leaves a
bit murky.

Of course for normal F77 code I would imagine that these ugly
cases would be vanishingly rare.

Thomas Koenig

unread,
Aug 22, 2015, 5:15:52 AM8/22/15
to
lyttlec <lyt...@removegmail.com> schrieb:

> I had the NAG Toolpack in the
> past, but not now. Looks like someone thinks it should be locked up to
> keep it away from terrorist.

You can find it at

http://www.ibiblio.org/pub/Linux/devel/lang/fortran/!INDEX.short.html

I did a port to Linux around 20 years or so ago, and rechecked
it half a year go.

The Fortran parts still compile nicely. You have to add some
#include statements to get the C parts to work.

Toopack is VERY picky about Fortran 77 compliance (' vs. " as
string delimiter, ...). The main problem is that it does not
support INCLUDE, but it is quite nice otherwise.

lyttlec

unread,
Aug 22, 2015, 7:08:53 AM8/22/15
to
The basic issue is what exists, not what the language specified. IIRC,
back in the good-ol-days every vendor had extensions to promote some
hardware they were pushing. Printers, tape drives, terminals,
track-balls (yeah, track-balls in the 60s). Which, from my perspective,
seems to be how the next specification gets written. Some extension to
the previous standard is widely used and gets adopted.

lyttlec

unread,
Aug 22, 2015, 7:32:27 AM8/22/15
to
On 08/21/2015 02:42 PM, dpb wrote:
> On 08/21/2015 1:05 PM, lyttlec wrote:
>> On 08/20/2015 07:10 PM, dpb wrote:
>>> On 08/20/2015 8:26 AM, russ wrote:
>>>> >SNIP<
>>>
>>> If it's all as well organized as this, personally I'd not worry much
>>> about the GOTOs nor the breaks; you'll end up with CYCLE and the like
>>> anyway from an automated converter and not necessarily any more and
>>> perhaps far less) readable/maintainble than what you've got.
>>>
>>> IMPLICIT NONE and some of the others I'm in agreement with...
>>>
> ...
>
>> On the whole, the old code is of excellent quality, which is one reason
>> no one wants to change. But it is getting more and more difficult to
>> maintain.
>
>SNIP<
> All in all, just to say that sometimes there really isn't much to be
> gained in some forms of changes; I agree with some of the memory
> management like COMMON and the like but then again, if COMMON is handled
> in a set of INCLUDEs such that it's not difficult to keep in one place
> the definitions and any modifications, what are module variables other
> than common by another name? The above app, of course, as was
> essentially mandatory for the time :) used type punning in the database
> but that was all done with C routines that simply move memory and while
> in some ways ugly, it's well hidden in the bowels of the code, works,
> and is essentially totally transparent at the programming level of the
> application and so hasn't been touched since the day it was first
> completed. Why one would one waste time and energy to do something with
> it just because it isn't the latest version of the Standard is beyond my
> ken...
>
> --
In this case, change is driven by hardware. . One day soon the last
PDP-8, IBM Peanut, and TRS-80 are going to die. And, yes, they are still
in use. 8" floppies and IOmega zip disks are getting hard to find. News
story yesterday about NASA cannibalizing museum displays to get parts
for the space station. And I'm working on 35 year old code. *sigh*

Richard Maine

unread,
Aug 22, 2015, 9:30:16 AM8/22/15
to
lyttlec <lyt...@removegmail.com> wrote:

> On 08/21/2015 07:15 PM, Richard Maine wrote:
> > lyttlec <lyt...@removegmail.com> wrote:
> >
> >> On 08/20/2015 09:08 PM, Richard Maine wrote:
> >
> >>> The end= specifier makes no sense (and might even be invalid) in a
> >>> direct access read statement. The standard does not allow an EOF
> >>> condition in a direct access read.
> >>>
> >> The original was in Fortran 66 reading tapes. The EOF indicated an
> >> attempt to read past the end of the tape. Not real direct access, but
> >> some tapes could back-up to previous records without completely
> >> re-winding. It was later re-worked into Fortran 77. f2c thinks the code
> >> is ok, probably trying to be backward compatible with someone's idea of
> >> a Fortran 66 compiler.
> >
> > Well, f66 didn't have direct access at all. Nor did it have end=. So it
> > seems unlikely to me that allowing end= with direct access would have
> > much to do with f66 compatibility. I'd more guess it was just a
> > restriction that didn't get diagnosed. Recall that the f77 standard
> > didn't require compilers to be able to diagnose *ANY* errors.
> >
> > On a direct access file, reading a record that doesn't exist (such as a
> > record past the last one of the file) would plausibly cause an error
> > condition, but not an end-of-file one. The error condition isn't
> > guaranteed (pretty much nothing about I/O errors is guaranteed), but it
> > is reasonably plausible at least for a record after the end of the file.
> >
> The basic issue is what exists, not what the language specified.

That's certainly important. But then so is precision in exposition. The
features mentioned are not "Fortran 66". (Just like the code mentioned
in another recent thread was not "Fortran 77"). The features mentioned
also were not even particularly widespread extensions to Fortran 66.

lyttlec

unread,
Aug 22, 2015, 10:25:55 AM8/22/15
to
Well, the read() form was acceptable for IBM, Microsoft, DEC, MIPS(they
sold a few computers), and now, Linux "compliant" Fortran 77 compilers.
I don't know if it worked on WATFOR, as there doesn't seem to be an IBM
360/370 available to test it. All I can do is name the compiler that
compiled the code which passed the test. The real question is how to
make the code that compiles, runs, and passes tests using "f2c (Fortran
to C Translator) version 20100827" compile, run, and pass tests using
"f95 Using built-in specs.
COLLECT_GCC=f95
COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.8/lto-wrapper
Target: x86_64-linux-gnu
Configured with: ../src/configure -v --with-pkgversion='Ubuntu
4.8.4-2ubuntu1~14.04'
--with-bugurl=file:///usr/share/doc/gcc-4.8/README.Bugs
--enable-languages=c,c++,java,go,d,fortran,objc,obj-c++ --prefix=/usr
--program-suffix=-4.8 --enable-shared --enable-linker-build-id
--libexecdir=/usr/lib --without-included-gettext --enable-threads=posix
--with-gxx-include-dir=/usr/include/c++/4.8 --libdir=/usr/lib
--enable-nls --with-sysroot=/ --enable-clocale=gnu
--enable-libstdcxx-debug --enable-libstdcxx-time=yes
--enable-gnu-unique-object --disable-libmudflap --enable-plugin
--with-system-zlib --disable-browser-plugin --enable-java-awt=gtk
--enable-gtk-cairo
--with-java-home=/usr/lib/jvm/java-1.5.0-gcj-4.8-amd64/jre
--enable-java-home
--with-jvm-root-dir=/usr/lib/jvm/java-1.5.0-gcj-4.8-amd64
--with-jvm-jar-dir=/usr/lib/jvm-exports/java-1.5.0-gcj-4.8-amd64
--with-arch-directory=amd64
--with-ecj-jar=/usr/share/java/eclipse-ecj.jar --enable-objc-gc
--enable-multiarch --disable-werror --with-arch-32=i686 --with-abi=m64
--with-multilib-list=m32,m64,mx32 --with-tune=generic
--enable-checking=release --build=x86_64-linux-gnu
--host=x86_64-linux-gnu --target=x86_64-linux-gnu
Thread model: posix
gcc version 4.8.4 (Ubuntu 4.8.4-2ubuntu1~14.04) "

dpb

unread,
Aug 22, 2015, 10:40:30 AM8/22/15
to
On 08/22/2015 6:32 AM, lyttlec wrote:
...

> In this case, change is driven by hardware. . One day soon the last
> PDP-8, IBM Peanut, and TRS-80 are going to die. And, yes, they are still
> in use. 8" floppies and IOmega zip disks are getting hard to find. News
> story yesterday about NASA cannibalizing museum displays to get parts
> for the space station. And I'm working on 35 year old code. *sigh*

But the code posted as a "problem" isn't hardware dependent at all; I'm
simply saying that it would seem prudent to really evaluate what it is
your changing and why...change simply for change's sake seems futile.

Fix (and refactor if need be to make it more contained as the code I was
describing above) what is machine-dependent, sure, and even
(selectively) rewrite in a modern idiom going forward those modified
pieces, but it would appear that routines such as the one posted would
have no need for anything to be modified other than perhaps as Paul
noted to return an error code instead of the somewhat brutal STOP (but,
then again, if it only does that once every 20 years, have you really
gained anything useful for the investment?).

The described code base above is 35 yr old, too. The characters in the
source files are the same now as then...they haven't aged! :)

While somewhat dated by today's sensibilities of lowercase, freeform
source, etc., etc., and I'd not begrudge one converting the form from
fixed to free it wouldn't really add anything to 99% of the code as the
way it is structured to add new functionality for a new plant one adds a
module almost always rather than making extensive changes within a
currently-existing one. If, otoh, your code is such that changes are
being made within a whole lot of existing routines, then it does make
more sense.

Again, the point here is to consider the "why" and what's really to be
gained and perhaps end up with more focus on "what" is important and has
real payback.

--

Richard Maine

unread,
Aug 23, 2015, 1:56:06 AM8/23/15
to
Oh. Slight confusion in talking about 2 different versions here. I
specifically mentioned Fortran 66 when I said that direct access and
end= were not "widespread extensions to Fortran 66." That was in reply
to a suggestion that allowing the two together was done for
compatibility with Fortran 66; I seriously doubt that was the reason.

F77 is another matter. Both direct access and end= are standard in f77
and all full language f77 compilers support them. However, having both
of them in the same READ statement is just plain a bug. Allowing that
bug does not constitute a meaningful extension; it is just a quality of
implementation shortcomming in the compiler. I might note that depending
on such compiler bugs quite often bites people when a subsequent release
of even the same vendor's compiler fixes the bug.

> The real question is how to
> make the code that compiles, runs, and passes tests using "f2c (Fortran
> to C Translator) version 20100827" compile, run, and pass tests using
> "f95 Using built-in specs.

Afraid I can't be of much help in that. I also admit to some slight
confusion here as that does not appear to have been the subject of this
particular thread. This thread was specifically about changing code to a
more modern style. Note the subject line. I recall that you were asking
questions about that, but that was a different thread. Are you
conflating two different threads?

FortranFan

unread,
Aug 23, 2015, 9:41:18 PM8/23/15
to
On Thursday, August 20, 2015 at 11:59:02 AM UTC-4, russ wrote:

>..
> >
> > Fortran 90 Handbook: Adams, Brainerd, Martin, Smith, Wegener
> >
> That is a good book, everyone should have a copy. But not what I was
> looking for. I need more of a style guide that shows common tasks in
> Fortran 66/77 and a recommends way to do the same thing in Fortran 90.
> For example the code above between 10 and 30 is an idiom to read each
> line in a file, processes it, and write it to an output file. Valid
> Fortran 77, but not Fortran 90/95. So what would be a good Fortran 95
> idiom to do the same thing?
> Another example is the code should be re-written as a subroutine in a
> module such that the comment "! Code to parse text" could be replaced
> with a function call supplied as a parameter.

You should also take a close look at the following book which I think comes closest to the reference you're looking for:

Modern Fortran: Style and Usage
Norman S. Clerman and Walter Spector
Cambridge University Press, New York, NY, 2012.
DATE PUBLISHED: December 2011
ISBN 978-0-521-73052-5. 334 pp. USD 45.00 (P).
http://www.cambridge.org/us/knowledge/isbn/item6577536

Ultimately you yourself have to develop the style and idioms that work best for you and those who work with you..

lyttlec

unread,
Aug 23, 2015, 10:31:00 PM8/23/15
to
On 08/23/2015 09:41 PM, FortranFan wrote:
> SNIP< You should also take a close look at the following book which
> I think comes closest to the reference you're looking for:
>
> Modern Fortran: Style and Usage Norman S. Clerman and Walter
> Spector Cambridge University Press, New York, NY, 2012. DATE
> PUBLISHED: December 2011 ISBN 978-0-521-73052-5. 334 pp. USD 45.00
> (P). http://www.cambridge.org/us/knowledge/isbn/item6577536
>
> Ultimately you yourself have to develop the style and idioms that
> work best for you and those who work with you..
>
I've met Walter Spector years ago. I'll order a copy asap.

FortranFan

unread,
Aug 24, 2015, 12:23:41 PM8/24/15
to
On Saturday, August 22, 2015 at 10:40:30 AM UTC-4, dpb wrote:

> ..
>
> But the code posted as a "problem" isn't hardware dependent at all; I'm
> simply saying that it would seem prudent to really evaluate what it is
> your changing and why...change simply for change's sake seems futile.
>
> Fix (and refactor if need be to make it more contained as the code I was
> describing above) what is machine-dependent, sure, and even
> (selectively) rewrite in a modern idiom going forward those modified
> pieces, but it would appear that routines such as the one posted would
> have no need for anything to be modified other than perhaps as Paul
> noted to return an error code instead of the somewhat brutal STOP (but,
> then again, if it only does that once every 20 years, have you really
> gained anything useful for the investment?).
>
> The described code base above is 35 yr old, too. The characters in the
> source files are the same now as then...they haven't aged! :)
>
> While somewhat dated by today's sensibilities of lowercase, freeform
> source, etc., etc., and I'd not begrudge one converting the form from
> fixed to free it wouldn't really add anything to 99% of the code as the
> way it is structured to add new functionality for a new plant one adds a
> module almost always rather than making extensive changes within a
> currently-existing one. If, otoh, your code is such that changes are
> being made within a whole lot of existing routines, then it does make
> more sense.
>
> Again, the point here is to consider the "why" and what's really to be
> gained and perhaps end up with more focus on "what" is important and has
> real payback.
>

All of these arguments are only relevant if the folks in charge of some code simply who do not have the essential resources - time/money - and are themselves hesitant to convert code to modern Fortran and are looking for "manager" type of reasons to convince themselves why they shouldn't embark on any change.

Per OP, the context of this particular thread seems to be one where a specific task request has come in to "upgrade" some existing code and in that case, my position will be to embrace it and not ponder any further on "whether" and "why" i.e., learn the best ways to "modernize", as the OP is trying to do here, and initiate the effort.

The faster a whole lot of "legacy" Fortran code can transform from F77 and prior forms to modern approaches and style, the better it will be for the Fortran world. Of course such transformations do have a real cost to them, but if there are institutions willing to bear such costs (which might be the case here), then go for such modernization.

I have personally taken upon myself to do this for several legacy libraries and already seeing two big benefits:

1) "passing the baton" to younger generations in terms of code responsibility is so much easier: we have a few 20-somethings working on these libraries and the only complaint they have about Fortran are the somewhat poorer developer resources e.g., compared to what C++ and C# coders have with "Intellisense" in Microsoft's Visual Studio. These bright minds would have little interest in working with F77-like code. No matter what one may say that young engineers in computational fields should be open to working on any technical code even if it were in legacy forms, younger folks are not "buying" the arguments and this is a real problem in industry and many managers are very concerned about it. Eventually many organizations decide to move away from legacy F77-like code to C++ or whatever; instead, I think it is better to upgrade to modern Fortran.

2) move away from statically allocated and global variables (think COMMONs and EQUIVALENCEs) to dynamically allocated and "local" memory (e.g., instance-specific to an OOP class object) has opened up the world of threading and parallelization in a clearer manner.

Wolfgang Kilian

unread,
Aug 25, 2015, 2:19:39 AM8/25/15
to
While all these arguments are perfectly valid, don't overestimate the
burden of F77 style vs. 'modern' style. That is only a small fraction
of the problems with legacy code.

F77 code that is well structured and well documented (procedure
interfaces, in particular) is often easier to maintain than idiomatic
F90 or F08 code. There are many new pitfalls in genuine F90+ that F77
did not have. For instance, pointer-target relations have to be
managed, and the compiler won't be of much help in that area.

It goes without saying that F77 in new code makes no sense:
allocatables, strings, derived types, abstract design patters, parallel
execution.

In old code: if there is something to change, I also would convert. If
not, or not yet, time is invested better in automatizing, extending and
improving the test suite. F90 compilers provide a huge improvement in
terms of consistency checks, but they can deal only with a small
fraction of error sources. Only the programmer and the user know what
the program is actually supposed to do.

Moreover, in the last decades I found myself converting code already
three times, once from F77 to F90, then to F95+ (pointer arrays to
allocatables!), then to F03 OO style. I wouldn't have believed it a
decade ago, the latter conversion buys as much in terms of clarity and
maintenance as the former conversions, namely if complex patterns of
dynamic data have to be structured and shuffled around.

Yes, F77 style is ugly and old-fashioned, but ... implicit typing? In
Javascript, all typing is implicit. Semantics of fixed-form
indentation? Python. UPPER case? CamelCAse. COMMON? Global state in
web code. Apparently, contemporary programmers are not afraid of ugly
syntax and awful programming language design. Or you could say that the
same mistakes are repeated again with each new generation.

-- Wolfgang



--
E-mail: firstnameini...@domain.de
Domain: yahoo

robin....@gmail.com

unread,
Aug 25, 2015, 11:42:10 AM8/25/15
to
On Tuesday, August 25, 2015 at 2:23:41 AM UTC+10, FortranFan wrote:

> All of these arguments are only relevant if the folks in charge of some code simply who do not have the essential resources - time/money - and are themselves hesitant to convert code to modern Fortran and are looking for "manager" type of reasons to convince themselves why they shouldn't embark on any change.
>
> Per OP, the context of this particular thread seems to be one where a specific task request has come in to "upgrade" some existing code and in that case, my position will be to embrace it and not ponder any further on "whether" and "why" i.e., learn the best ways to "modernize", as the OP is trying to do here, and initiate the effort.
>
> The faster a whole lot of "legacy" Fortran code can transform from F77 and prior forms to modern approaches and style, the better it will be for the Fortran world. Of course such transformations do have a real cost to them, but if there are institutions willing to bear such costs (which might be the case here), then go for such modernization.

The old saying "If it works don't fix it" is apt.
But the older a program gets, the less likely
it will be that it will continue to work.
Inevitably, changes are needed such as new output formats,
and new data.

lyttlec

unread,
Aug 25, 2015, 8:20:11 PM8/25/15
to
The general tenor of the last few posters summarizes the problem
exactly. Older Fortran dialects seemed clunky, but they supported
writing safe programs. That is, if you wrote a program to control and
aircraft, you wouldn't mind going on the first test flight. Fortran
90/95 introduced some things to help with making good programs and
somethings that make it easier to write unsafe programs (e.g. some
pointer semantics, as you pointed out).
The joke, popular with old Fortran programmers, is that C gives you
enough rope to hang yourself. C++ throws the rope over the yardarm,
puts the noose around your neck, puts a gun in your hand, cocks it,
puts your finger on the trigger, and points it at your foot. The
point being that bad Fortran 66 and Fortran 77 was pretty obviously
bad. Post Fortran 95 isn't anywhere as near as dangerous as C++, but a
good style guide is required.



Gary Scott

unread,
Aug 25, 2015, 9:22:09 PM8/25/15
to
A good style guide has always been required, especially for multi-person
developments...mish mash of styles is deadly.

FortranFan

unread,
Aug 25, 2015, 11:06:47 PM8/25/15
to
On Tuesday, August 25, 2015 at 8:20:11 PM UTC-4, lyttlec wrote:

> .. The
> point being that bad Fortran 66 and Fortran 77 was pretty obviously
> bad. Post Fortran 95 isn't anywhere as near as dangerous as C++, but a
> good style guide is required.

To reiterate what I suggested earlier, whoever is looking for a style guide must take a close look at:

Modern Fortran: Style and Usage
Norman S. Clerman and Walter Spector
Cambridge University Press, New York, NY, 2012.
DATE PUBLISHED: December 2011
ISBN 978-0-521-73052-5. 334 pp. USD 45.00 (P).
http://www.cambridge.org/us/knowledge/isbn/item6577536

If a good chunk of, if not all, the recommendations in this book are followed, the resultant code should be fairly alright.

Ron Shepard

unread,
Aug 26, 2015, 12:43:09 AM8/26/15
to
On 8/25/15 7:20 PM, lyttlec wrote:
> The general tenor of the last few posters summarizes the problem
> exactly. Older Fortran dialects seemed clunky, but they supported
> writing safe programs. That is, if you wrote a program to control and
> aircraft, you wouldn't mind going on the first test flight. Fortran
> 90/95 introduced some things to help with making good programs and
> somethings that make it easier to write unsafe programs (e.g. some
> pointer semantics, as you pointed out).

My experience is almost the opposite of these conclusions. With modern
fortran, I often find that once I get the code to compile, my debugging
is often over. By that time the compiler has checked interfaces, checked
undeclared variables, and so on. With f77, getting it to compile was
just the first step of many more to go. There are MANY ways to shoot
yourself in the foot with f77, ways in which the compiler cannot and
does not help.

It is true that I avoid pointers in favor of allocatables when
applicable, and I have not yet adopted the newer OO oriented features,
but I do make extensive use of modules, elemental procedures, and user
defined types.

$.02 -Ron Shepard

Richard Maine

unread,
Aug 26, 2015, 1:10:06 AM8/26/15
to
My experience matches Ron's, at least in broad direction. I won't go so
far as to claim that my debugging was almost done when my f90+ codes
compiled, but they sure were a *LOT* closer to debugged than my f77
codes were when they first compiled. It is perhaps hard to tell how much
of that relates to the language and how much of it relates to my greater
maturity as a programmer, but it seemed to me that the two factors went
together. Certainly since f90+ included (essentially) all of f77 plus
new features, it included all of f77's ways to go wrong plus new ones.
But it also provided facilities help a careful programmer to avoid many
errors. Specifics not worth going into here (and that would get
unreasonably long).

I'm afraid I never made much use of allocatables in real code because
one could not count on most compilers having sufficiently robust support
for allocatables in the time frame that my last serious codes were
designed. But I was disciplined in my use of pointers to the extent that
I rarely ran into trouble with them. (See, for example, my regular
comments recommending against ever using functions that return
pointers). For similar reasons of timing, I never did much with the OO
stuff, though I did see ways it would have fit very well in some of my
apps if it had been available at the time.

robin....@gmail.com

unread,
Aug 26, 2015, 3:08:40 AM8/26/15
to
But IF fixed source form is avoided entirely,
many of those error vanish.
So F90+ helps avoid most of the errors inherent in old codes.
To get the most out of F90+, one needs IMPLICIT NONE and explicit
interfaces.

> But it also provided facilities help a careful programmer to avoid many
> errors. Specifics not worth going into here (and that would get
> unreasonably long).

Perhaps, but IMPLICIT NONE and explicit interfaces go a long way
to avoiding errors that were a fact of life with FORTRAN 77 and earlier.

Ian Harvey

unread,
Aug 26, 2015, 3:10:55 AM8/26/15
to
On 2015-08-26 10:20 AM, lyttlec wrote:
...
> The general tenor of the last few posters summarizes the problem
> exactly. Older Fortran dialects seemed clunky, but they supported
> writing safe programs.

"Supported"?? In what way? The level of support that Fortran 77
*standard language* offered for writing "safe" programs was essentially
zero - no diagnostics were required from a conforming processor.

The philosophy that I've seen with lots of the Fortran 77 code that I
have maintained appears to have been "It compiles and runs without
errors and appears to give the right result, therefore the code must be
right". I detect elements of that in some of the recent threads here
around getting an old code to work with f2c. Plenty of opportunity for
latent bugs.

> That is, if you wrote a program to control and
> aircraft, you wouldn't mind going on the first test flight. Fortran
> 90/95 introduced some things to help with making good programs and
> somethings that make it easier to write unsafe programs (e.g. some
> pointer semantics, as you pointed out).

Prior to Fortran 90, people still needed things that tended towards the
semantics of a Fortran 90 pointer. So they fudged something equivalent
together, often using language extensions or tricks that happened to
work (but were not necessarily designed to work) on their particular
platform. That fudged solution then exposed their programs to very
similar programming error/safety issues that might arise with the use of
pointers in Fortran 90.

But somehow they were better off with this fudged solution? I don't
think so.

Modern Fortran is far from perfect in regard to code safety aspects, but
at least code safety has been considered in its evolution. To pretend
that Fortran 77 is somehow better from a code safety point of is
ludicrous - many of the code safety issues in Fortran 90 only exist
because of a desire to maintain backwards compatibility with Fortran 77!

> The joke, popular with old Fortran programmers, is that C gives you
> enough rope to hang yourself. C++ throws the rope over the yardarm,
> puts the noose around your neck, puts a gun in your hand, cocks it,
> puts your finger on the trigger, and points it at your foot. The
> point being that bad Fortran 66 and Fortran 77 was pretty obviously
> bad. Post Fortran 95 isn't anywhere as near as dangerous as C++, but a
> good style guide is required.

A good starting point for a style guide for Fortran 95 is "don't write
Fortran 77".

glen herrmannsfeldt

unread,
Aug 26, 2015, 4:09:52 AM8/26/15
to
Richard Maine <nos...@see.signature> wrote:
> Ron Shepard <nos...@nowhere.org> wrote:
>> On 8/25/15 7:20 PM, lyttlec wrote:
>> > The general tenor of the last few posters summarizes the problem
>> > exactly. Older Fortran dialects seemed clunky, but they supported
>> > writing safe programs.

(snip)
>> My experience is almost the opposite of these conclusions. With modern
>> fortran, I often find that once I get the code to compile, my debugging
>> is often over. By that time the compiler has checked interfaces, checked
>> undeclared variables, and so on. With f77, getting it to compile was
>> just the first step of many more to go. There are MANY ways to shoot
>> yourself in the foot with f77, ways in which the compiler cannot and
>> does not help.

I probably agree, but maybe not completely.

It isn't so hard to learn all the features, and non-features, of
Fortran 66 or Fortran 77.

Newer Fortran versions, up to 2003 or 2008, have many more features,
that is, many more ways to go wrong.

If someone has been writing Fortran 77 programs for 30 years, and
Fortran 2008 programs for one, and actually try using many of the
new features, I certainly would not be surprised to see more
mistakes using the new features than the old ones.

That might depend on the person. I do remember in my early years
of programming that I was unusually good at finding bugs in compilers.

I would try using features just to use them, if that seemed a good
way to do something, even if I understood another way better.

(snip)

> My experience matches Ron's, at least in broad direction. I won't go so
> far as to claim that my debugging was almost done when my f90+ codes
> compiled, but they sure were a *LOT* closer to debugged than my f77
> codes were when they first compiled. It is perhaps hard to tell how much
> of that relates to the language and how much of it relates to my greater
> maturity as a programmer, but it seemed to me that the two factors went
> together. Certainly since f90+ included (essentially) all of f77 plus
> new features, it included all of f77's ways to go wrong plus new ones.
> But it also provided facilities help a careful programmer to avoid many
> errors. Specifics not worth going into here (and that would get
> unreasonably long).

Yes, those new ways to go wrong. After not so many years, I knew
very well some of those ways for Fortran 66. I do remember in those
years being around people learning Fortran 66 (before 1977) and
often knowing the problem with only a small hint.

-- glen

Wolfgang Kilian

unread,
Aug 26, 2015, 4:41:26 AM8/26/15
to
On 26.08.2015 09:10, Ian Harvey wrote:
> On 2015-08-26 10:20 AM, lyttlec wrote:
> ...
>> The general tenor of the last few posters summarizes the problem
>> exactly. Older Fortran dialects seemed clunky, but they supported
>> writing safe programs.
>
> "Supported"?? In what way? The level of support that Fortran 77
> *standard language* offered for writing "safe" programs was essentially
> zero - no diagnostics were required from a conforming processor.
>
> The philosophy that I've seen with lots of the Fortran 77 code that I
> have maintained appears to have been "It compiles and runs without
> errors and appears to give the right result, therefore the code must be
> right". I detect elements of that in some of the recent threads here
> around getting an old code to work with f2c. Plenty of opportunity for
> latent bugs.

For me, writing F77 code, when I still had to do this, implied 'compile
with g77 and check with ftnchek'. That appeared to be reasonably safe.
Fortunately, I could use important extensions such as lower case and
long variable names. When I switched to F90, I was astonished that I
could drop ftnchek altogether since its tasks were already done by the
F90 compiler.

My more recent experience is that an exhaustive automatic test suite
(test-driven development!) goes far beyond the capabilities of compiler
checks. In my field (academia), nobody wrote test suites in the 80s.

>
>> That is, if you wrote a program to control and
>> aircraft, you wouldn't mind going on the first test flight. Fortran
>> 90/95 introduced some things to help with making good programs and
>> somethings that make it easier to write unsafe programs (e.g. some
>> pointer semantics, as you pointed out).
>
> Prior to Fortran 90, people still needed things that tended towards the
> semantics of a Fortran 90 pointer. So they fudged something equivalent
> together, often using language extensions or tricks that happened to
> work (but were not necessarily designed to work) on their particular
> platform. That fudged solution then exposed their programs to very
> similar programming error/safety issues that might arise with the use of
> pointers in Fortran 90.
>
> But somehow they were better off with this fudged solution? I don't
> think so.
>
> Modern Fortran is far from perfect in regard to code safety aspects, but
> at least code safety has been considered in its evolution. To pretend
> that Fortran 77 is somehow better from a code safety point of is
> ludicrous - many of the code safety issues in Fortran 90 only exist
> because of a desire to maintain backwards compatibility with Fortran 77!

Completely agree. Rewriting a pure F77 program using modern-Fortran
terms consistently and switching on bounds checking, essentially
produces a safe program. However, (looking back) pointers for
allocating arrays in F90 opened a can of worms that was not there
before. This is fixed now by allocatables, but the language continues
to be unsafe in the area of lists, trees, etc., where pointers are
inevitable. Using such data structures in Fortran (natural for any
programmer who is educated in modern languages) requires either
allocating anonymous targets which can get lost, or spilling required
TARGET attributes at far-from-obvious places. No compiler that I know
of detects all of the resulting errors at runtime. Avoiding pointers is
not an option.

Now, coarrays appear to introduce another source of problems, but at
least there is a chance that they will offer a more practical solution
to multi-processing issues than other programming languages.

>> The joke, popular with old Fortran programmers, is that C gives you
>> enough rope to hang yourself. C++ throws the rope over the yardarm,
>> puts the noose around your neck, puts a gun in your hand, cocks it,
>> puts your finger on the trigger, and points it at your foot. The
>> point being that bad Fortran 66 and Fortran 77 was pretty obviously
>> bad. Post Fortran 95 isn't anywhere as near as dangerous as C++, but a
>> good style guide is required.
>
> A good starting point for a style guide for Fortran 95 is "don't write
> Fortran 77".

Fortran 77 is like Latin. No reason to speak or write, but one should
be able to read it.

lyttlec

unread,
Aug 26, 2015, 6:25:18 AM8/26/15
to
On 08/25/2015 09:22 PM, Gary Scott wrote:
> SNIP<
>>
> A good style guide has always been required, especially for multi-person
> developments...mish mash of styles is deadly.



Absolutely. Which is why I posted another thread asking for about idioms
for Fortran 95.

lyttlec

unread,
Aug 26, 2015, 6:26:57 AM8/26/15
to
Got a copy on order.

lyttlec

unread,
Aug 26, 2015, 6:37:21 AM8/26/15
to
As I said, newer Fortran has introduced things that help. You seem to
have adopted all the good things and avoided some of the more
problematic features. Things like pointers and OO are also helpful,
but need careful management.

lyttlec

unread,
Aug 26, 2015, 6:52:28 AM8/26/15
to
On 08/26/2015 04:41 AM, Wolfgang Kilian wrote:
> SNIP< a style guide for Fortran 95 is "don't write
>> Fortran 77".
>
> Fortran 77 is like Latin. No reason to speak or write, but one should
> be able to read it.
>
> -- Wolfgang
>
Do we all agree that upgrading from Fortran 77 to Fortran 90/95 is a
good thing? Like learning Latin, Fortran 77 teaches why things are done
a certain way.

Wolfgang Kilian

unread,
Aug 26, 2015, 7:41:56 AM8/26/15
to
Yes. Were done in a certain way, in an environment with tight
constraints.

Many of the computing limits of the 80s don't exist anymore, but
sometimes efficiency issues are the same on a different scale.

If any change is to be made -- convert first. Introducing free form,
lower case, explicit interfaces and explicit declarations are reasonably
simple, can be done incrementally, and can only improve the code. The
most delicate task is elimination of non-standard F77 extensions. Any
further steps would depend on time and money, so probably stop there.

Eliminating COMMON and EQUIVALENCE and declaring INTENT would be high on
my list, but might be tedious. Next would be derived types for
collecting data (where OO thinking creeps in), but at this point the
code has essentially been rewritten from scratch ... if code is actually
rewritten, I would bypass F95 style and rather write idiomatic F08,
including coarrays if parallel execution is an option.

Gary Scott

unread,
Aug 26, 2015, 8:58:18 AM8/26/15
to
I generally agree, however my code is very heavily GUIed! up. So just
because it compiles doesn't mean I've got the button in the right
position or I've highlighted the correct accelerator key or the callback
response does the right thing.

test test test test test

FortranFan

unread,
Aug 26, 2015, 8:58:38 AM8/26/15
to
On Wednesday, August 26, 2015 at 6:25:18 AM UTC-4, lyttlec wrote:

> ..
> Absolutely. Which is why I posted another thread asking for about idioms
> for Fortran 95.

The other thread comes across on my webbrowser under a nom de plume of "russ" where here you are "lyttlec", so I didn't make the connection it was the same person even though some of your later posts implied as much.

Richard Maine

unread,
Aug 26, 2015, 10:52:34 AM8/26/15
to
Ian Harvey <ian_h...@bigpond.com> wrote:

> The philosophy that I've seen with lots of the Fortran 77 code that I
> have maintained appears to have been "It compiles and runs without
> errors and appears to give the right result, therefore the code must be
> right".

In our office, we used to use the term
"name-withheld-to-protect-the-guilty check case" for getting a program
to compile and run. The qualification of "appears to give the right
result" was not needed. The guilty party in question was a student who
had been given a training task of writing code to find the roots of a
3rd-order polynomial with real coefficients. On one test case, his code
came up with 2 real roots and one complex one. He refused to believe
that his code could have given an incorrect answer. All that theory
stuff about how you had to have an even number of complex roots was
obviously wrong, as his code conclusively proved by showing a
counter-example.

FortranFan

unread,
Aug 26, 2015, 12:39:25 PM8/26/15
to
On Tuesday, August 25, 2015 at 8:20:11 PM UTC-4, lyttlec wrote:

> ..
> The general tenor of the last few posters summarizes the problem
> exactly. Older Fortran dialects seemed clunky, but they supported
> writing safe programs. ..

I can't help hammer in the point enough that the above statement "Older Fortran .. supported writing safe programs" is sheer myth. We've all heard the stories and it is mostly B.S.

The reality is often similar to what we've experienced in manufacturing industry where there are these FORTRAN codes and libraries touted as "robust" and supposedly running "fine" with "no changes required" for years and years but which actually have quite a few bugs including those causing aborted runs or giving wrong answers and so forth. We would often find the users simply "working around" such issues with a lot of pre-processing and post-processing of program data due to lack of alternatives i.e., the users had to adapt to the code rather than the code doing what the users needed! And whenever a young engineer was allowed to make any code change at all, the whole thing would come crashing down like a house of cards; often it was due to some strange interaction with COMMONs and EQUIVALENCEs and/or any of the memory mapping tricks that were done or actual/dummy argument mismatch and so forth. It was nearly impossible to teach anyone all those details because each case was unique. And only an old-timer "expert" or two would know how to navigate the code and get it to work.

Fast forward to today and while the facilities in current Fortran standard for pointers, OO, and so on are far from perfect, they allow some measure of "conforming" programming practices across languages i.e., good coding practices and styles learnt in one area can be applied in Fortran without having to jump through hoops. And vice versa! That is, some of the constructs from modern Fortran can be brought in as disciplined coding in other languages.

The other point is the younger engineers we come across with interest in computational science and engineering already have a great grasp of the concepts behind many of the newer features in Fortran 2003/2008/2015, having used them in C, C++, or Java (often in their early teens!). They are quite aware of pitfalls with pointers or the scaffolding that goes behind OO or impact of global data on parallel execution. They know such burdens are part and parcel of the programming paradigm itself and have little to do with the language [other than, say, some restrictions in Fortran for aliasing (e.g., pointer-target relationship)]. These young engineers are smart and brave and ambitious who say "do not stop me" from doing something simply because it was viewed as dangerous or too complex at something point in the past (say with pointers and/or OO), especially when the technical program requirements often forced previous developers to do the same in alternate (and now obsolescent) ways such as with memory tricks using EQUIVALENCEs and rigid programming edicts (to achieve some semblance of modular and OO-style structure) and so forth; instead, they want to follow some accepted programming styles (say a factory pattern from GoF for OO for an ODE solver implementation) and they want to use good analysis tools (e.g., valgrind) to prove to you the code is not only delivering what it should for the user while also having no ill-effects (such as memory leaks, data race conditions, etc.). All those old jokes about ropes and C and C++, which are actually about pointers, OO, etc., are only utterly old and worn out now..

FortranFan

unread,
Aug 26, 2015, 1:02:00 PM8/26/15
to
On Wednesday, August 26, 2015 at 4:09:52 AM UTC-4, glen herrmannsfeldt wrote:

> ..
>
> I probably agree, but maybe not completely.
>
> It isn't so hard to learn all the features, and non-features, of
> Fortran 66 or Fortran 77.
>
> Newer .., have many more features,
> that is, many more ways to go wrong.
>
> ..
>
> Yes, those new ways to go wrong. After not so many years, I knew
> very well some of those ways ...
>
> -- glen


Computing with an abacus or one's fingers has even fewer ways of going wrong..

Paul van Delst

unread,
Aug 26, 2015, 1:59:54 PM8/26/15
to
On 08/26/15 06:37, lyttlec wrote:
> As I said, newer Fortran has introduced things that help. You seem to
> have adopted all the good things and avoided some of the more
> problematic features. Things like pointers and OO are also helpful,
> but need careful management.

A sig on one of my email accounts:

"Complexity has to be very carefully managed or it becomes chaos." --
Chip Kidd

True across many different types of design.

cheers,

paulv


Paul van Delst

unread,
Aug 26, 2015, 2:11:38 PM8/26/15
to
Mostly OT....

Reminds me of one of my undergrad physics lecturers who pointed out an
error in the course textbook when we got to that topic.

Some of my fellow students argued with him about how the text could not
be wrong because, well, it was printed in the text.

What should've been a trivial remark in a lecture turned into a very
important lesson.

cheers,

paulv

glen herrmannsfeldt

unread,
Aug 26, 2015, 3:09:31 PM8/26/15
to
Richard Maine <nos...@see.signature> wrote:

(snip)
> In our office, we used to use the term
> "name-withheld-to-protect-the-guilty check case" for getting a program
> to compile and run. The qualification of "appears to give the right
> result" was not needed. The guilty party in question was a student who
> had been given a training task of writing code to find the roots of a
> 3rd-order polynomial with real coefficients. On one test case, his code
> came up with 2 real roots and one complex one. He refused to believe
> that his code could have given an incorrect answer. All that theory
> stuff about how you had to have an even number of complex roots was
> obviously wrong, as his code conclusively proved by showing a
> counter-example.

Reminds me when I tried to fit an N degree polynomial to N data points.
(My first try at polynomial fitting.)

-- glen

Thomas Koenig

unread,
Aug 26, 2015, 3:11:58 PM8/26/15
to
Wolfgang Kilian <kil...@invalid.com> schrieb:

> If any change is to be made -- convert first. Introducing free form,
> lower case, explicit interfaces and explicit declarations are reasonably
> simple, can be done incrementally, and can only improve the code.

Agreed.

The next big step, for me, would be introduction of assumed-shape
arrays instead of the old, loooooooooong argument lists which were
a constant source of error, at least in my earlier codes.

Being able to rid of workspace arrays is also a big bonus.

> The
> most delicate task is elimination of non-standard F77 extensions. Any
> further steps would depend on time and money, so probably stop there.
>
> Eliminating COMMON and EQUIVALENCE and declaring INTENT would be high on
> my list, but might be tedious.

If the documentation of the interface is good, then adding intent could be
done whenever you touch a procedure.

Dick Hendrickson

unread,
Aug 26, 2015, 6:15:14 PM8/26/15
to
Maybe not. If you ask an American to hold up 3 fingers he'll hold up
his index, naughty, and ring fingers. A European will hold up his
thumb, index, and naughty fingers. Cultural differences are pretty
basic and it's confusing.

Dick Hendrickson

Paul van Delst

unread,
Aug 26, 2015, 6:30:32 PM8/26/15
to
Huh. I hold up my pinky, ring, and middle.

Growing up in Australia will do that to a person....

:o)

Richard Maine

unread,
Aug 26, 2015, 9:17:13 PM8/26/15
to
Thomas Koenig <tko...@netcologne.de> wrote:

> If the documentation of the interface is good, then adding intent could be
> done whenever you touch a procedure.

By the time f90 came around, I had gotten in the habit of having a
comment for each argument about whether in was used for input, output,
or both. I was pleased to find that I could essentially change those
comments into compilable code; the syntax was different, but the message
was the same.

--
Richard Maine
email: last name at domain . net
dimnain: summer-triangle

Wolfgang Kilian

unread,
Aug 27, 2015, 3:30:19 AM8/27/15
to
On 27.08.2015 03:17, Richard Maine wrote:
> Thomas Koenig <tko...@netcologne.de> wrote:
>
>> If the documentation of the interface is good, then adding intent could be
>> done whenever you touch a procedure.
>
> By the time f90 came around, I had gotten in the habit of having a
> comment for each argument about whether in was used for input, output,
> or both. I was pleased to find that I could essentially change those
> comments into compilable code; the syntax was different, but the message
> was the same.
>

I suppose that you had always been smart enough to avoid dummy arguments
with context-dependent intent :-)

Wolfgang Kilian

unread,
Aug 27, 2015, 3:40:17 AM8/27/15
to
GoF patterns are seamlessly coded in Fortran, the committee did a great
job in that area. But those C++-educated engineers will severely miss
the STL functionality.

The ropes are shipped now with Python where every 'variable' is actually
a pointer. And off-by-one addressing errors are an all-time classic.

FortranFan

unread,
Aug 27, 2015, 9:16:05 AM8/27/15
to
On Thursday, August 27, 2015 at 3:40:17 AM UTC-4, Wolfgang Kilian wrote:

> ..
> GoF patterns are seamlessly coded in Fortran, the committee did a great
> job in that area. But those C++-educated engineers will severely miss
> the STL functionality.
>
> ..

Yes, C++ STL-type functionality is currently being missed mainly for the kind of technical code we develop where we need container "classes" - lists, collections, stacks, hashsets, queues, etc.. That's why I've been bringing this up in other discussions with the hope those lead Fortran standards (committee members, etc.) might see them and may decide to bring more capability into Fortran in a future revision:

https://groups.google.com/forum/#!searchin/comp.lang.fortran/FortranFan$20container/comp.lang.fortran/IPz-b_k3TJI/lB5M-zwk-ykJ

Re: C++ STL, my view currently is it will be great if Fortran were to introduce "intrinsic" derived types with type-bound procedures, perhaps even extensible, as part of some existing/new "intrinsic" modules! Why not a new intrinsic module, ISO_FORTRAN_STL that includes derived types similar to those in C++?!?

Wolfgang Kilian

unread,
Aug 27, 2015, 9:29:18 AM8/27/15
to
Well, STL means derived types parameterized on (derived or intrinsic)
types. That can't be put in a module, not even an intrinsic one. It
requires an extension of Fortran.

Beliavsky

unread,
Aug 27, 2015, 9:49:51 AM8/27/15
to
Error messages from using the C++ STL are often long and inscrutable, and if the Fortran analog had the same problem, I wonder if it would be worth adding. Are obscure error messages a necessary price to pay for generic programming?

Wolfgang Kilian

unread,
Aug 27, 2015, 10:01:08 AM8/27/15
to
Isn't that a quality of implementation issue, even for C++?

Part of the problem, I guess, is the explicit (de)referencing of
pointers in C++, which exposes implementation and thus the macro-like
internals of the template facility. Inscrutable errors are a typical
symptom of macro processing.

Fortran hides internal pointer structure, so the situation might be much
better from start. And there are loads of other languages that implement
generic programming, C++ is likely among the worst realizations of the idea.

Richard Maine

unread,
Aug 27, 2015, 10:41:29 AM8/27/15
to
Yukk. Hate that! :-(

I don't recall doing such a thing in my own code - at least not by the
time f90 came around; I won't vouch for some of the things done by my
younger self.

I occasionally had to deal with such things in 3rd party libraries that
I was using. Along with messes like arguments whose type depended on
other arguments. :-( I recall an old case of that in some versions of
the old CalComp plotter library. I think it was the SYMBOL subroutine.
Part of the problem there was a holdover from f66 Hollerith days. And
part was that SYMBOL could do either of 2 largely unrelated things; I'm
not quite sure why they were mashed together into a single subroutine.
In more recent days, some C libraries use a flag argument to determine
the type that a subsequent argument gets cast to.

Ian Harvey

unread,
Aug 27, 2015, 11:28:03 AM8/27/15
to
I don't think pointers come into it.

The issue is as you then allude to - C++ template processing sits barely
above the level of a macro pre-processor. A template usually will have
requirements on a type that it is to be used with, which, with C++03 at
least, are difficult to describe to the compiler - i.e. it is at heart a
language issue. When a user then inadvertently uses a type that isn't
appropriate the compiler can only report to the user the immediate issue
that it encounters when it attempts to instantiate the template. This
immediate issue will occur in the source code of the template, remote
from the actual user's code.

Throw in aspects like nested and multiple template parameterisation,
partial specialisations of templates, implicit deduction, implicit
conversions and a much more involved process around template and
overload resolution, and it can often be bewildering to a user as to why
the compiler is even instantiating a particular piece of generic code,
let alone what it is about their code that they need to fix.

Facilities provided with later revisions of that language combined with
defensively written generic code can help to a certain extent, I don't
think things are anywhere close to being satisfactorily resolved.
There's a proposal for "concepts", which I think is still experimental,
that might make a meaningful difference.

I think a generic programming feature for Fortran would do well to avoid
these issues, even if that results in a loss in capability that the
language might otherwise have (there are trade-offs here). Hence I am
very much not in favour of generic programming approaches that are
macro-like, though that sort of approach is probably far easier to
specify and implement.

I've just reread the thread linked to by FortranFan - I'm starting to
repeat myself (and I haven't progressed the implementation any of my own
ideas since that thread :( ). But you can certainly have generic
programming and (hence) STL-like utility without long and inscrutable
errors.


glen herrmannsfeldt

unread,
Aug 27, 2015, 2:34:49 PM8/27/15
to
Richard Maine <nos...@see.signature> wrote:

(snip on arguments and INTENT)

> I occasionally had to deal with such things in 3rd party libraries that
> I was using. Along with messes like arguments whose type depended on
> other arguments. :-( I recall an old case of that in some versions of
> the old CalComp plotter library. I think it was the SYMBOL subroutine.
> Part of the problem there was a holdover from f66 Hollerith days. And
> part was that SYMBOL could do either of 2 largely unrelated things; I'm
> not quite sure why they were mashed together into a single subroutine.
> In more recent days, some C libraries use a flag argument to determine
> the type that a subsequent argument gets cast to.

In the Fortran 66 days, I figured out that SYMBOL called LINE to
actually draw, (with both SYMBOL and LINE assembler programs).

I wanted to plot on a different device, without rewriting everything,
so wrote a replacement for LINE in Fortran that SYMBOL could call.

It worked fine for me (with Fortran G), but it seems not for others
(with Fortran H). I found out later that it depends on the value
of register 0 not changing during the call to LINE.

Anyway, yes, SYMBOL can either draw a whole string, (using
Fortran 66 style characters in INTEGER array form) or a single
character (as an INTEGER value).

Seems to me like another side effect of argument passing and
characters in usual Fortran 66 systems. Since the dummy argument
looks like an INTEGER array, and SYMBOL knows which one you are
using, it works fine either way.

Not quite the same with Fortran 77 CHARACTER.

-- glen

FortranFan

unread,
Aug 27, 2015, 4:26:35 PM8/27/15
to
On Thursday, August 27, 2015 at 9:29:18 AM UTC-4, Wolfgang Kilian wrote:
> FortranFan wrote:
> >
> > Yes, C++ STL-type functionality is currently being missed mainly for the kind of technical code we develop where we need container "classes" - lists, collections, stacks, hashsets, queues, etc.. That's why I've been bringing this up in other discussions with the hope those lead Fortran standards (committee members, etc.) might see them and may decide to bring more capability into Fortran in a future revision:
> >
> > https://groups.google.com/forum/#!searchin/comp.lang.fortran/FortranFan$20container/comp.lang.fortran/IPz-b_k3TJI/lB5M-zwk-ykJ
> >
> > Re: C++ STL, my view currently is it will be great if Fortran were to introduce "intrinsic" derived types with type-bound procedures, perhaps even extensible, as part of some existing/new "intrinsic" modules! Why not a new intrinsic module, ISO_FORTRAN_STL that includes derived types similar to those in C++?!?
> >
>
> Well, STL means derived types parameterized on (derived or intrinsic)
> types. That can't be put in a module, not even an intrinsic one. It
> requires an extension of Fortran.
>

I'll clarify: at this point, our interest is mainly in the functionality of container classes. I brought up C++ STL only as an example since it has established a certain stature in technical computing. I could have instead brought up Java util namespace and Collections therein. So again, I'm not advocating Fortran doesn't need to offer something exactly like C++ STL. Instead, some container class utilities is what we seek so we don't have to "roll our own".

A simple example would be to consider the book, "Modern Fortran Explained" by Metcalf et al. and the "any list" example in their appendix. There they show a "any list" module with some derived types for "any item", "any list", etc. and procedures to operate on them. The consumers of such a class can "use" the module to create lists to hold data of any type. This is a rudimentary illustration of a list "class" to hold objects of any type.

https://groups.google.com/forum/#!searchin/comp.lang.fortran/FortranFan$20%22modern$20fortran$20explained%22/comp.lang.fortran/aRz3HMpblTs/3oWfF_aARIYJ

Along these lines, one can use concepts to create one's own classes (derived types) for common containers such as trees, queues, lists, stacks, etc. Instead, what if the language itself offered some standard capabilities that the consumers can use and perhaps extend too. And just like the "any_list" module in Metcalf et al., these can be packaged in "standard intrinsic" modules that come along with the compiler implementation. And these intrinsic modules, similar to ISO_C_BINDING with C_PTR, can include derived types using which coders can creates their own container objects; and these derived types can include type-bound procedures so coders can invoke e.g., if there were a derived type to create a hashtable or a dictionary, there may be a TBP named Add to insert a <key, value> pair:
!.. Pseudo code
..
use, instrinsic :: iso_fortran_container, only : dict_t
!.. i.e., dict_t is an intrinsic derived type in a new intrinsic module!!
..
type(dict_t), allocatable :: mydict
..
allocate( mydict.. )
..
call mydict%add( "foo", 1)
call mydict%add( "bar", 2)
..
i = mydict%GetVal( "foo" ) !.. returns 1
str = mydict%GetKey( 2 ) !.. returns "bar"
..
if ( mydict%Contains( "foobar" ) then
print *, " My dictionary does not contain foobar. "
end if
..

The above is just for illustration; the ideas for such containers are well-developed in computer science and many other languages have had good implementations for them for ages. It is up to Fortran standard bearers and thinkers to decide whether to offer such things to coders; my vote would be yes. And in my thinking, these truly come alive in the OO parlance and hence the use of derived types and TBPs such as dict_t and methods such as Add, Contains, GetVal, etc. "Intrinsic modules" can therefore play a vital role to package such types.

Ian Harvey

unread,
Aug 27, 2015, 6:42:30 PM8/27/15
to
Accepting that the above is supposed to be just pseudo-code, I think
Wolfgang's point is that today you would actually need to access a type
called `dict_key_of_default_character_value_of_default_integer_t`, and
if you wanted to use your own types as the key or value, you would have
to ring up your compiler vendor and get them to quickly issue an update
to the intrinsic module just for you.

That's the gap in the language right now - there is no ..."non-hacky"...
method of parameterising source code on the basis of type (and perhaps
other characteristics), that would otherwise be generic.

Once you have that capability, you can then consider whether it is
appropriate to standardise the interface to a particular library of
generic code.

Having a collectively agreed library interface is certainly useful in
terms of programmer efficiency, but it is very much secondary to the
language actually having the basic capability to support such interfaces
in the first place. Collective agreement on interface can also occur
outside of the standardisation process for the core language - consider
the current situation with the numerical libraries such as BLAS and
LAPACK - and in many respects I think a separate approach would be
better. After all, once the core language supports generic programming
in a effective manner, a library that supports a particular container
could just be written in portable source code.

lyttlec

unread,
Aug 27, 2015, 8:17:56 PM8/27/15
to
IIRC, the first Fortran compiler was a 10 pass compiler. C/C++
compilers are single pass. This meant that Fortran compiler could do a
lot of checking at compile time that C could do only at run time. C++
now has templates as part of the pre-processor which does a lot at
compile time. Perhaps the next Fortran standard should specify
handling Fortran-STL in a fist-pass/pre-processor? Check out C++
Template Meta Programming.

lyttlec

unread,
Aug 27, 2015, 8:22:12 PM8/27/15
to
Thus my comment to Wolfgang about handling that as a sort of
pre-processing as C++ does. The first pass resolves all the templates
and derived types, and the rest of the compiler sees them as if they
were an intrinsic part of the language.

lyttlec

unread,
Aug 27, 2015, 8:35:01 PM8/27/15
to
On 08/27/2015 04:26 PM, FortranFan wrote:
> SNIP <
>
> The above is just for illustration; the ideas for such containers are
> well-developed in computer science and many other languages have had
> good implementations for them for ages. It is up to Fortran standard
> bearers and thinkers to decide whether to offer such things to
> coders; my vote would be yes. And in my thinking, these truly come
> alive in the OO parlance and hence the use of derived types and TBPs
> such as dict_t and methods such as Add, Contains, GetVal, etc.
> "Intrinsic modules" can therefore play a vital role to package such
> types.
>
I think I mixed up names in my previous reply. Sorry.
My point is that to do what you describe implies something like C++
templates and/or Ada generics. Fortran has a chance to do it right, but
the standard will have to lay requirements on the compiling process, not
just language syntax.

William Clodius

unread,
Aug 27, 2015, 11:21:46 PM8/27/15
to
I don't know how many passes the original Fortran compiler used, but
Bernard Hodson ("Computers Without Machine Code") claimed to have
written a single pass compiler. Typically the claimed difference between
Fortran and C/C++, was not that iFortran could do more checking at
compile time, but the languages assumptions, i.e., no modifiable
aliasing, meant that it did not have to do as much compile time (or run
time) checking if it could assume valid Fortran code.

The amount of runtime vs compile time checking has little if anything to
do with the number of passes. For early Fortran it would have had to do
more with the limited capabilities of the machine than the runttime vs
compile time checking. The limited memory of those mahines made it
necessary to meant that the analysis had use as little memory as
possible, which in turn dictated doing the analysis as a sequence of
well defined simple stages. Generally the simpler a language is the
easier it is to focus on error checking.

I don't know how of any C compiler that used a single pass, though
perhaps LCC comes close. It is just conceptually simpler to factor the
analysis into a few well defined stages. Conisde Richard O'Keefe's
discussion of the analysis of C9x (17 Oct. 1998, in comp.compilers)


"""
Frankly, I _wouldn't_ describe C9x/C++/Java identifiers using a
regular expression. Remember, there are EIGHT "translation phases" in
C9x:


1. Map source multibyte characters to the source character set.
This includes converting end of record to newline, and it
SPECIFICALLY INCLUDES CONVERTING non-basic characters to
UCNs. So you are allowed to have an <e-acute> character
in your source code, and it may even be represented in the
source file by a single 16#E9# byte, but subsequent phases
of translation will 'see' \u00E9 or possibly even
\u0065\u0301 <e,floating acute> instead.


The main consequence of this for your regular expression is
that if you want to recognise identifiers in SOURCE files,
you need to handle the full range of local multibyte codes
AS WELL AS universal character names. If your regular
expression processor is 8-bit-clean, you might be able to
get away with
letter = [a-zA-Z_] | [\0x80-\0xFF]+ | \u[0-9a-fA-Z]{4} | ...
ident = letter (letter | digit)*


1a. After this, trigraphs are replaced. (Yes, that means C9x
really has nine phases, not 8.)


2. \<newline> is spliced out.


3. the input is tokenized as a sequence of pp-tokens and white space


4. preprocessing is done, directives, macros, &c.
THIS PHASE MAY GENERATE NEW IDENTIIFERS, so foo(x)(y) may
actually _be_ an identifier even though it doesn't _look_
like one. (No, you can't generate new UCNs here.)


5. Characters are now converted from the source character set
to the execution character set.


6. Strings are pasted (narrow strings with narrow strings, wide
strings with wide strings). The effect of "x" L"y" and
L"x" "y" is not defined, which is a pity, because that was
a very nasty problem that they should have fixed.


7. Now pp-tokens are converted to tokens, and of course some
pp-tokens that look like identifiers are actually keywords.
White space including comments is finally discarded.


7a. The program is parsed. (Yes, that means there are really
ten phases, not 8.)


8. External references are resolved and everything is put into an
"image" suitable for execution in the target environment.


What this means is that if you want a tool to do something useful with
identifiers in C source files, you would have to be very very silly
not to do it by taking a freely available preprocessor (such as the
GNU one) and bolting your tool on the end.

"""

Wolfgang Kilian

unread,
Aug 28, 2015, 2:33:45 AM8/28/15
to
Yes, maybe without C-style pointer resolution the issues would still be
the same. A good implementation of generics should not remind the user
that a preprocessor is at work. Apparently, the C++ standard doesn't
allow such an implementation.

I can imagine that, in Fortran terms, the type argument(s) of a
container type must always be completely declared, including all
requirements on the operations that they have to support. This is
analogous to the interface of a deferred procedure, which must be
explicit in Fortran. Then, all checks can be done before instantiating
the generic. Errors would be obvious.

On the user's side, writing Fortran generic might become somewhat
tedious with all those declarations explicit, but it's more important
that using generics is foolproof.

> Throw in aspects like nested and multiple template parameterisation,
> partial specialisations of templates, implicit deduction, implicit
> conversions and a much more involved process around template and
> overload resolution, and it can often be bewildering to a user as to why
> the compiler is even instantiating a particular piece of generic code,
> let alone what it is about their code that they need to fix.

IIRC, the C++ template facility is a Turing-complete language on its
own. Well ...

> Facilities provided with later revisions of that language combined with
> defensively written generic code can help to a certain extent, I don't
> think things are anywhere close to being satisfactorily resolved.
> There's a proposal for "concepts", which I think is still experimental,
> that might make a meaningful difference.
>
> I think a generic programming feature for Fortran would do well to avoid
> these issues, even if that results in a loss in capability that the
> language might otherwise have (there are trade-offs here). Hence I am
> very much not in favour of generic programming approaches that are
> macro-like, though that sort of approach is probably far easier to
> specify and implement.

Whether the approach is macro-like internally doesn't matter. On the
user's side, using generics should be opaque regarding the
implementation, but straightforward to use, type-safe, and involve only
minimal syntax additions. I hope that the existing PDT facility can be
extended, so it becomes useful eventually.

> I've just reread the thread linked to by FortranFan - I'm starting to
> repeat myself (and I haven't progressed the implementation any of my own
> ideas since that thread :( ). But you can certainly have generic
> programming and (hence) STL-like utility without long and inscrutable
> errors.

Sorry, I'm also repeating myself :-)

lyttlec

unread,
Aug 28, 2015, 6:30:43 PM8/28/15
to
On 08/28/2015 02:33 AM, Wolfgang Kilian wrote:
> SNIP < IIRC, the C++ template facility is a Turing-complete
> language on its own. Well ... SNIP<

> -- Wolfgang
>
>
Yes, but it was an accident discovered by Erwin Unruh. If Fortran
adopts something similar, it should be deliberate and, if possible,
follow closely the main body of the requirements.

lyttlec

unread,
Aug 28, 2015, 7:09:39 PM8/28/15
to
On 08/27/2015 11:21 PM, William Clodius wrote:
> SNIP <
>
> What this means is that if you want a tool to do something useful with
> identifiers in C source files, you would have to be very very silly
> not to do it by taking a freely available preprocessor (such as the
> GNU one) and bolting your tool on the end.
>
C++ throws in Templates as part of the preprocessor, which makes
preprocessing Turing Complete.
Fortran could adopt something similar as part of the language, not an
accidental addon.
It is loading more messages.
0 new messages