Using reserved words as variables

Greetings,

I am a member of the SciPy maintainer team and recently I have been translating PROPACK and ARPACK libraries. In the meantime, since it is causing a bit too much of trouble, I started touching slsqp fortran code located in https://github.com/scipy/scipy/blob/main/scipy/optimize/slsqp/slsqp_optmz.f

Here is the very preliminary code WIP:ENH:optimize:Replace SQP solver fortran code by ilayn · Pull Request #19121 · scipy/scipy · GitHub

I tend to think of myself as knowlegable on the topic due to my PhD but I am quite confused about this piece of code. Mostly because of the flatbuffer practice that is, w(i+1) is the start of one array but w(j+mq) is another and so on, that makes everything almost impossible to read. Still, I can find my way out in most cases however I stumbled upon something that is very surprising.

I am sure there is a reason that some machine in year 1964 AD ran out of punch cards or whatever, so they allowed this as valid code but I just want to make sure that this is not a secret gotcha

      IF = n*n+1       <----- What is this booby trap here? Is it allowed?
      DO 10 i=1,n3
         i1 = n1-i
         diag = SQRT (l(i2))
         w(i3) = ZERO
         CALL dcopy_ (i1  ,  w(i3), 0, w(i3), 1)
         CALL dcopy_ (i1-n2, l(i2), 1, w(i3), n)
         CALL dscal_sl (i1-n2,     diag, w(i3), n)
         w(i3) = diag
         w(IF-1+i) = (g(i) - ddot_sl (i-1, w(i4), 1, w(IF), 1))/diag  <---- IF is a variable now? 

Excuse my astonishment but does this mean that

       IF = 10
       THEN = 20
       ENDIF = 30
       GOTO = 40
       IF IF IF, THEN, ENDIF
C OK the following is just plain stupid but why not
10     GOTO GOTO
20     GOTO GOTO
30     GOTO GOTO
40     ...

should compile?

I checked the modernized version of this code in https://github.com/jacobwilliams/slsqp/blob/master/src/slsqp_core.f90#707 and this assignment is still there so I guess it is still “modern” practice?

While I’m here there is also this type of declarations in some code we already removed so has less of an effect but still equally perplexing for me.

These statements are

What are they trying to achieve here with such code?

Excuse my ignorance if these are common practices but I have no idea how to google these as I tried “cast function with equality”, “Fortran type agnostic variable”, “why Fortran why?” but no avail.

2 Likes

Ah now I discovered https://fortran-lang.discourse.group/t/no-reserved-keywords-why/

My apologies for not searching properly.

1 Like

See also Doctor Fortran in “No Reserve” - Doctor Fortran (stevelionel.com)

2 Likes

The other thing you are seeing are statement functions. These are one-line function definitions that are somewhere in between macros and full fledged functions.

FPOINT(I) = I

is a way to define a conversion from integer to real or double precision, depending on how FPOINT was declared. F77 and earlier did not have a generic function to do this, so it was common to see it done this portable way in codes. In modern fortran, this would now be done with the REAL() intrinsic, which now allows a KIND argument that specifies the output type+kind combination.

1 Like

Yes, usually it will, meaning many/most Fortran compilers try hard to serve legacy semantics by default!

These compilers need to be told via compilation options to override those settings and to follow the current Fortran standard that deletes ARITHMETIC IF, ASSIGN, assigned GO TO statements, etc.

      INTEGER GOTO, IF, THEN, ELSE, ENDIF
      ASSIGN 40 TO GOTO
      ASSIGN 1 TO THEN
      ASSIGN 20 TO ELSE
      ASSIGN 30 TO ENDIF
   1  CONTINUE
      PRINT *, "IF?"
      READ(*,*) IF 
      IF ( IF ) 10, 20, 30
  10  CONTINUE
      PRINT *, "GO THRU' 10" 
      GO TO ELSE ( 10, 20, 30, 40 ) 
  20  CONTINUE
      PRINT *, "GO THRU' 20" 
      GO TO ENDIF ( 10, 20, 30, 40 )
  30  CONTINUE
      PRINT *, "GO THRU' 30" 
      GO TO GOTO ( 10, 20, 30, 40 )
  40  CONTINUE
      PRINT *, "GO THRU' 40"
      IF (IF .NE. 42) GO TO THEN ( 1 ) 
      STOP
      END
Compiler response!
C:\temp>ifort p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.10.0 Build 20230609_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 IF?
1
 GO THRU' 30
 GO THRU' 40
 IF?
99
 GO THRU' 30
 GO THRU' 40
 IF?
2
 GO THRU' 30
 GO THRU' 40
 IF?
0
 GO THRU' 20
 GO THRU' 30
 GO THRU' 40
 IF?
-5
 GO THRU' 10
 GO THRU' 20
 GO THRU' 30
 GO THRU' 40
 IF?
42
 GO THRU' 30
 GO THRU' 40

C:\temp>
1 Like

Very strange but OK. Thanks everyone for the help.

1 Like

Have fun looking at https://stevelionel.com/drfortran/wp-content/uploads/2021/05/CrazyFortran.for , though some of this is extensions.

1 Like

@ilayn welcome! Looks like you got your questions resolved. Yes, some of these old constructs are new to me as well, for example I had to learn the mechanics of the “assigned goto” statements above, what is allowed, what is not, when figuring out how to implement it about a year ago in LFortran. And yes, SciPy uses some very old “techniques” indeed.

You’ll be happy to know LFortran can now fully compile specfun.f and SciPy tests pass. We are now finishing some final touches on it. We do test it at our CI for every commit now. Our C and C++ backends will be useful to you, if you would prefer those languages. The most useful I think might be a Python/NumPy backend which we plan to write, and it would compile with LPython to get the same performance. That might be the best solution for SciPy long term. Many possibilities will open up once we can reliably compile SciPy via our default LLVM backend.

1 Like

That’s indeed great news. It probably won’t make too much difference for SciPy but for Fortran audience wonderful progress.

We started to overhaul our Fortran codebase META: FORTRAN Code inventory · Issue #18566 · scipy/scipy · GitHub and I am slowly replacing all fortran code with something we know how to maintain and hopefully have less bugs in them.

I have the “privilege” to read most of our F77 code in the last 3 months due to never ending bug reports and I am happy to report that most of those fortran code are at best naive at worst nearly broken. That’s expected since none of them have been maintained since 90s. It is a bit sad that some python package maintainer is going through them out of desperation after 3 decades instead of the fortran community who love to praise fortran at every occasion.

And after reading the spaghetti for a few months I know why and you know why; it’s an unreadable mess. Even fortran coders can’t read it. If anyone disagrees I kindly invite them to read it and prove my ignorance with a flattened code :sweat_smile:

In the meantime, I’m done with Propack almost ready with Arpack and now need to finish up slsqp. Then we will get to specfun. So long story short please don’t waste your time on such old code semantics. Your time is way more valuable to be spent in the future instead of the incompetent past. There is not much to salvage among all that historical wart. And half of ehat we have is repeated blas-like code in every other file in the name of “standalone library”

Since I’m in the dragons den, I dare to repeat my proposal;

Grab what makes Fortran fast, get rid of the silly syntax, make it 0-indexed row major memory ordered, call it Fivetran and move on. Keep it a niche numerical language and I guarantee you everone will be using it as the lowlevel infra if it has a decent compiler on all platforms. That’s how rust and python won the popularity contest. Not with mingw64 not with cygwin but cargo or pip on all platforms.

3 Likes

I don’t know what are precisely the “never ending bug reports” you are mentioning. Just, I’m using on a regular basis some decades old Fortran codes, and most of time they just work ok. Sure, I don’t really want to dig into these codes to correct bugs, but the point is that I don’t really have to: old codes are generally robust and have been largely debugged, and bugs are extremely rare according to my experience. So I would definitely not call them “broken”, nor “naive”, if they are used the way they are supposed to be used (for instance old codes should not be assumed to be thread safe in general).

What I’m describing here is quite common in the industry.

I assume you are just trolling…

No doubt Python is very popular. And indeed some people in my company have been developing some pieces of software in Python, instead of the traditional Fortran/C/C++ we are using (this is mostly an internal software, not commercial). And what we observe is that reliably distributing the Python pieces in a controlled industrial environment is just a mess.

2 Likes

I’ll throw out there I don’t think he’s trolling. As another “young kid that doesn’t know anything,” it can be very confusing looking at code much older than myself and be left wondering why on earth things were done a certain way.

It’s a bit hyperbole to say the past is incompetent. At least, the past authors were not. But people have to remember (the historians here too), that computer science and programming computers is a field not even 100 years old. It’s younger than flight. Look at what “modern” airplanes are compared to the first.

Lots of practices from a language as old as Fortran are indeed outdated. It is OK to recognize that humans have indeed learned BETTER ways since the 1950s. Making Fortran row major and indexed starting from 0 isn’t going to magically do anything other than break all the legacy code that exists.

Is legacy code that exists and “has been running for decades” bug free? Absolutely not. Anyone that has actually worked on said codes would attest the same.

All that said, Fortran could indeed have some updates to modernize and hopefully regain some popularity. At the moment, it’s too high level to write the most performant code, but lacks too many modern features to be a common first choice for new projects.

The coding practices of yesteryear are exactly the reason I have been working on this document: https://github.com/arjenmarkus/old-programming-idioms/blob/main/doc/old_programming_idioms.pdf.
For the record: I am slightly younger than the Fortran language itself and have been using it for roughly 40 years. Over that period of time I have seen several generations of computers and programming languages. And it is not always easy to justify the code we use in the way it is to younger colleagues.

Which is even worse if he really believes it.

And nobody is seriously denying that. Let’s not use the strawman fallacy…

I do work with some old codes like that. And I don’t think I’m different from “anyone”…

I was a “younger colleague” some long time ago. I was very confident in my “more modern practices” and started to rewrite these old routines with static work arrays passed as arguments. Such an old and outdated practice, now we have dynamic allocation, let’s allocate locally everything we need in the routines! At the end my modern routines were significantly slower than the outdated routines, because of the repeated allocations/deallocations.

1 Like

I don’t think there’s any strawman to say that opening up a file to discover arithmetic if and computed go to would throw someone less familiar with Fortran for quite the loop. That’s exactly what happened in this thread.

Maybe I was too broad. I also work with these legacy codes circa early 1980s, some newer some older. There are lots of bugs. “Just use it like it was intended” is not a valid response when the code is largely undocumented, difficult to understand for anyone not intimately familiar with all the possible ways to write Fortran through decades, and the original authors are nowhere to be seen (can’t ask them).

Fortran has a serious image problem. Bickering here about how bad practice or not lots of legacy (sometimes including deleted) “features” (today called footguns) are to use is not going to do anything helpful. Community efforts like stdlib, fpm, gfortran, lfortran, and flang are. So is this forum, when people asking honest questions and offering their outsider opinion can come here and be met with helpful answers. Simply writing them off as trolling for being displeased with coding practices from 40+ years ago does nothing to improve the situation.

1 Like

Sorry, strawman again: I did not cry troll because of being displeased with arithmetic if or assigned goto (that, I can understand), but because of the “incompetent past” charge (not to mention the fact that Fortran should now be Fivetran with row major ordering and zero indexing).

1 Like

R, Matlab/Octave, and Julia also use 1-based indexing, since it’s a reasonable choice for scientific computing.

Besides, the name Fivetran has already been taken by a company :slight_smile: providing an “automatic data movement platform”:

And then we’ll close with one softball, hopefully. “So why Fivetran and not a TenTran or ThreeTran?”

Fivetran actually is a pun on Fortran, which the software engineers in the audience will appreciate. Fortran was a programming language a long time ago, still is, not used much anymore, but it was one of the first big programming languages. And Fivetran is just a pun on that. Doesn’t really mean anything in particular, other than that. But just a pun on that. And I will say that I am very happy with it as a name all these years later. It’s easy enough to spell. It’s relatively easy to remember. It doesn’t really mean anything. And nobody used that term really before us, except for oddly enough, a band in England in the 2000s was named Fivetran.

1 Like

Ah I forgot the sensitive fortran users always fun

Then probably you should start asking about it before the tirade :blush: Also I already gave you plenty examples to click instead I get an insult. It’sOK though I don’t get triggered on this subject. I have been on and off with fortran since 1994 and amazingly hearing the same old sentences. Not a milimeter progress. But it’s ok I still love you and pure TeX evangelists against LaTeX usage. Both are wonderful crowd to engage with.

Anyways just want to mention that strawman is not what you think it is. Just saying.

Thanks again for the answers all and truly wishing all the success Ondrej,

It takes an immense lack of maturity, wisdom, and experience to call the past and the past generation incompetent just because the past did not have the tools and technology the future has.

I can’t see the “plenty of examples to click” in this discussion. I have followed this link you gave META: FORTRAN Code inventory · Issue #18566 · scipy/scipy · GitHub , which does not mention “plenty of bugs” either.

From there I followed this link to a bug in QUADPACK: BUG: wrong weights of the 7-point gauss rule in QUADPACK: dqk15w.f · Issue #14807 · scipy/scipy · GitHub . The de facto maintainer of QUADPACK on netlib was in the discussion and stated “I do not expect a lots of edits on the package. It feels like a bug here and there.”… Another contributor stated “For instance, ODRPACK seems stable and without open issues”. Still no plenty of bugs.

Then I browsed the issues of scipy: 9 of them are currently opened with the “fortran” tag out of 1405 opened issues, plus 30 closed issues with the “fortran” tag out of 7940 closed issues. So, are these 39 issues (0.4% of the total) “plenty of issues”?

QED: trolling

1 Like