Eliminate implicit mapping

Please see this:

Issue #90 proposes to eliminate implicit typing in Fortran. There is strong resistance to this, there being a major concern that to “eliminate implicit typing”, if pursued with any seriousness, will require a deletion of the IMPLICIT statement from the language. There is great worry some existing code would break as a result.

Can the Fortran community then coalesce to a somewhat simpler proposal, to eliminate implicit mapping instead?

The main aspect of such a proposal is to primarily change one sentence in the section on IMPLICIT statement to introduce the following:
If a mapping is not specified for a letter, the default for a program unit or an interface body shall be NULL, and the default for a BLOCK construct, internal subprogram, or module subprogram is the mapping in the host scoping unit

Note the current Fortran standard (document 18-007r1) instead states in section 8.7 IMPLICIT STATEMENT page 114, paragraph 3, lines 32-34, “If a mapping is not specified for a letter, the default for a program unit or an interface body is default integer if the letter is I, J, ..., or N and default real otherwise, and the default for a BLOCK construct, internal subprogram, or module subprogram is the mapping in the host scoping unit.

This one sentence effectively ends up achieving backward compatibility with code written from the days of FORTRAN I where “ICARUS was an integer unless specified as REAL”, to paraphrase a long-standing joke with FORTRAN! The proposal is to modify this sentence as indicated in bold above

But now almost all the code written from the days of FORTRAN 77 then has tried to avoid the fate of the legend and not drown while trying to only take flight via the explicit use of the IMPLICIT statement, IMPLICIT NONE overwhelmingly but IMPLICIT INTEGER(I-N), xx(A-H,O-Z) {xx = DOUBLE PRECISION, REAL, REAL*8, etc.]. This proposal intends fully not to affect in any adverse manner any such existing code that makes explicit use of IMPLICIT statements.

The intended benefit of this one modification is to set in motion finally a positive change where IMPLICIT NONE becomes the default in any and all program units and in all the interface bodies, gone will be the need to ensure the inclusion of implicit none in a list of explicit interfaces:

interface
   function foo(..) result(..)
      [import .. ]
      implicit none !<-- Per current standard, forget this and face peril
      ..
   end function
   function bar(..) result(..)
      [import .. ]
      implicit none !<-- Per current standard, forget this and face peril
      ..
   end function
   subroutine foobar(..)
      [import .. ]
      implicit none !<-- Per current standard, forget this and face peril
      ..
   end subroutine
end interface

Almost every processor tries to offer a compiler option to enforce the gist of this proposal, with fpm and LFortran considering making this even the default. Why not standardize all such good intent?

What say you all, can you support this for Fortran 202Y? Please keep in mind even with 202Y, it may be year 2040 by the time this can become practicable. Is it not time now to start giving this a serious consideration?

Please provide your feedback preferably at the above GitHub site for Fortran proposals, or here?

7 Likes

Though I have never used implicit typing myself, I do have a soft corner for it. The reason is I have long envisioned Fortran as an interpreted language, in addition to compiled, even before learned about LFortran. Interpreted languages are generally dynamically typed. One reason for this is that explicit typing will be to cumbersome for quick explorations in a dynamic environment. In this context, implicit typing in Fortran appears to be an innovative idea (even though it was introduced for a completely different reason). It offers best of both worlds. Straightforwardly interpreted strong typing, sans explicit declarations.

I think more useful “implicit typing” would be to infer the type from the right hand side, so that you can do things like:

a = [1., 2., 3.]
sin(a)

This would not be possible with the Fortran’s implicit typing because you can’t declare arrays that way (I think), only scalar variables.

2 Likes

I have suggested using ASSOCIATE for this, dropping the current requirement that each ASSOCIATE statement be paired with an END ASSOCIATE statement. There would be an implicit END ASSOCIATE when the end of the program unit is reached.

So would anyone be deterred from using fpm if it required you to add a “relaxed_rules=true” option to the manifest file (fpm.toml) to just use the default compiler behaviors (ie. do what it does now) or otherwise it would (where available) uses switches to enforce what the consensus seems to be would be a step forward (implied “implicit none”, no source line limit, assume all source files are free form, possibly require an interface definition)? So, for example the default for gfortran(1) would now include

-ffree-form -ffree-line-length-none -fimplicit-none

??
Maybe --fimplicit-private and -fimplicit-procedure too? Maybe a survey like “would you not use fpm if it did this?”, “would you be encouraged to use fpm if it did this?” “would you be discouraged from using it?”, it would be a nuance you would always turn off, etc.?

2 Likes

I think the answer is no, it would not deter anyone. That’s the approach that I would like to take.

I think people are effectively trying to define a Modern Fortran subset through fpm options. In the past there was F and ELF90, which were subsets of Fortran 90 (maybe with a bit of F95). Books were published about these subsets, including by Metcalf and Reid and Meissner. Using F and ELF90 helped me transition from Fortran 77 to modern Fortran.

If a subset of modern Fortran is to be defined, it should have a name. Would it be too confusing to call it F? Walt Brainerd, the primary developer of the original F, has passed away. He originally sold F through modified compilers from commercial vendors and later created an F option within g95. A modern Fortran would use the gfortran -fimplicit-none option, and what else? A subset could be the union of F and ELF90 plus the new features of Fortran 2003/2008/2018. A deletion from F/ELF90 could be the (//) syntax for arrays, since [] is now allowed.

I think this is the kind of poll worth doing, especially for developing “modern defaults.” I think it’s the kind push we’d really like to give to developers to encourage them to modernize their codes, but would backfire if it prevented from adopting fpm in the first place.

So far I have converted several influential, legacy code bases to building with fpm. I have found the process to be almost painless in most cases. I don’t think setting the defaults to be more modern would make that process much more difficult, and would actually give me something I would like to have. I would have a few lines in the fpm.toml file to point at and tell the owners of those codes, “You’re long term goal for this code should be the ability to remove those lines, so you can be using modern defaults.”

To me it would provide a very clear signal when reviewing other’s codes. Without having to look at any of the source code, I could have something to point at and say, “ok, here’s a good indication of the state of this code base.”

3 Likes

The precedent for this was set in Fortran 77. It defined a “full” language (“FORTRAN”) and a “subset” language (“Subset FORTRAN”). The ANSI standard document had both languages defined, with the full language described on the left-hand pages, and the subset defined on the right-hand pages.

As a work of love and devotion, we could consider creating a “Subset Fortran 2018” in the same way, page by page defining how the subset differs from the full specification.

I’d thought about this in the past, but didn’t think that it would be of interest. I may be wrong. (My interest was in terms of having a language whose semantics were simplified, for investigating Fortran formal semantics.)

1 Like

What would be the goal of a subset of Fortran?

One goal could be a simple(r) compiler: if you would be willing to restrict your code to the subset that the compiler supports, you might get some advantages, such as faster compilation. But that can be done already by anybody who is interested. What other goals / advantages would it have?

1 Like

Simpler compiler is one advantage. Another great advantage I think is that a smaller language gives opportunity for a simpler language that is easier to read and understand, has fewer language exceptions, and thus harder for a programmer to make mistakes.

I wrote “opportunity” above because a smaller language is not necessarily simpler. For example, C. But a valid subset of Fortran can only be simpler I think.

3 Likes

A good starting point for a subset would be a language without obsolescent features. These features are:

(1) Alternate return
(2) Computed GO TO
(3) Statement functions
(4) DATA statements amongst executable statements
(5) Assumed length character functions
(6) Fixed form source
(7) CHARACTER* form of CHARACTER declaration
(8) ENTRY statements
(9) Label form of DO statement
(10) COMMON and EQUIVALENCE statements, and the block data program unit
(11) Specific names for intrinsic function
(12) FORALL construct and statement

The market has already rejected subset compilers, both the F77 subset @gak mentions as well as the F and ELF90 compilers (as also mentioned earlier.) I don’t know of any vendor who bothered building an F77 subset compiler, and it was a waste of effort by the standards committee.

I’m not averse to making implicit typing obsolescent, in the way that fixed form source is already. Compilers would still support it. Some would flag usage by default, others would require the user to ask for such diagnostics. As for actually deleting it from the standard, I would be a hard NO on that - but I have never been a fan of deleting features.

If we did this, though, it would kill one of the best Fortran jokes: “GOD is real, unless declared INTEGER.”

3 Likes

But then we could say that believing that GOD is real is obsolescent. (I am not seriously making any statement about religion here.)

3 Likes

cc: @certik, thank you for bringing attention to @sblionel 's role also as WG5 convenor and the kind of soft influence such a position can bring in terms of vision and direction of Fortran.

To all readers,

The original post in this thread strives hard to differentiate between implicit typing and implicit mapping:

  • implicit typing also encompasses what is possible with explicit IMPLICIT statements, the likes of which can be noticed considerably in codes whose primary development was based majorly on Fortran processors prior to Fortran 90 standard revision.
  • whereas with implicit mapping, the scope is rather narrow, it pertains essentially to that one sentence in the standard that leads to objects whose types are not explicitly declared to have implicit types depending on the first letter of their names.

The proposal tries to make obvious it only addresses the latter i.e., implicit mapping i.e., no change is directed at what is achieved in code via explicit IMPLICIT statements.

Also, note the proposal is not trying to delete anything from the standard, only to change just one long-standing semantics involving implicit mapping. It is a change that only tries to standardize what is a standard coding practice being pursued in practically every program unit by all the Fortranners everywhere. The number of coding instances where the current semantics with implicit mapping is desirable has to be statistically insignificant to be considered as absolute zero.

Moreover the time horizon for change is years away, possibly even two decades out! That is, if any action toward this change is initiated now in which case the earliest it will be considered is with Fortran 202Y for which there is no timeline at the moment. And note the eventual adoption is entirely up to processors, it can be a decade or more later after the date of the standard publication.

Is all this not clear? Can readers please provide their input as to where things are unclear?

The reason also for my plea is because nomenclature is extremely important: if this proposal gets mischaracterized again as deleting of the feature implicit typing which can happen due to mislabeling like in the quoted comment above by @sblionel, it will immediately fail. Hence my request and hope the proposal here not be misrepresented like that.

Ultimately though, this whole thing is an aspect of vision for Fortran, something that would be of constant attention and importance to a WG5 convenor.

The fact is the current semantics with the rules around implicit mapping inflicts damage upon Fortran e.g., in a team I work with in industry, a few missing implicit none statements in a long list of interface blocks (see snippet in original post with foo, bar, etc.) toward interoperability with a library in another processor not only led to disastrous and costly bugs, it also added to negative perception of Fortran and migration away from it.

I reckon there is hardly much of anything positive to be gained by retaining the current implicit mapping rules in the standard for beyond 202X. As the original post mentions, existing codes that prefer such implicit mapping already convey their intent with explicit IMPLICIT statements. IMPLICIT INTEGER(I-N), DOUBLE PRECISION(A-H,O-Z) being ubiquitous in such codes. Thus the risk of breaking existing code is miniscule to zero. More importantly though, should any existing code even “break”, it may even be a welcome event to many users and the gatekeepers of such codes!

Considering all of above, it comes down to this:

Is it possible at all to envision that by year 20XY (say 2040), the Fortran standard would advance to the point a Fortranner can expect a standard-conforming program unit and an interface body to have *implicit none* by default, independent of any processor options?

Is such a small aspect of a vision unacceptable and/or objectionable to you as a member of the Fortran Community? If yes, can you please post your reasons and objections here?

2 Likes

In my opinion, changing the default semantics for implicit typing, that is, requiring an IMPLICIT statement, is not going to fly. This would break a very large number of existing programs and would lead to a revolt by users. I agree that implicit typing is a bad thing, but we’re stuck with it. What we can do is nudge people away from it by making it obsolescent.

  1. Re: “This would break a very large number of existing programs,” there is no data really to back this up. The number of programs that would truly break are likely to be insignificant statistically.

  2. But as homage and consideration to a few codes that might break, the Fortran Community can come together to initiate a Communication and Volunteering campaign now to help them transform their codes to a good coding practice. The old codes will have 2+ decades to prepare for this.

1 Like

I have nearly four decades doing compiler support for a commercial vendor. I have seen first-hand, many times, what happens when a new version of a compiler doesn’t compile a user’s code. It’s one thing if you can say the old code was incorrect, it’s quite another to say that the language changed incompatibly and they have to change tens of thousands of lines of code.

You want to accelerate the move away from Fortran? Then keep pushing for breaking changes. That is not the Fortran way.

4 Likes

No, it would not break anything. Everyone is free to compile with -stand f18 or whatever standard the code is written in.
Python managed the transition from v2 to v3 without a loss in popularity. Breaking changes are clearly annoying, but if they are announced early and improve the language, chances are high that a majority accepts them.

1 Like

I’ll answer it: absolutely. Not only that, we can do it without breaking people’s codes, which I 100% agree with @sblionel that it is important.

Here is how to do it:

  1. First we need to get the community to use some common infrastructure. I am hoping the Fortran Package Manager (fpm) will eventually fill that role.

  2. The fpm can then provide ways to use implicit none by default, but allowing older code to compile (forever) by allowing to turn this default off for a given project or file. We already started implementing exactly this functionality.

  3. Provide good tutorials and get the community to use this new default.

  4. As new codes and existing open source codes and eventually in-house codes start using this default, it becomes less and less of an issue in practice. Older codes that just need to keep running will turn this default off. This can work forever, I don’t see a technical problem there.

  5. As this becomes now the prevalent expectation in the Fortran community, we can start a discussion how to add this to the Fortran standard. I believe the Fortran standard should only standardize prevalent practice, it should not drive such change. The community, which means compilers, tooling, users, committee members etc. should drive such a change.

2 Likes