Separation of declaration and initiation of variables

I am not sure in which direction you are going either ?
In the sample code, in SUBROUTINE ppnd16, all the declared variables with assigned values MUST have a SAVE status for the algorithm to function. The implicit save from these declarations is essential for the code to work.

I hope your claimed “Authority” to “even contest the existence of any code that employs the implicit save feature on purpose” is far removed from any influence to changes to the Fortran standard.
It is a very reckless position to propose, as clearly AlanMiller’s and many other codes would not work if you had your way.

Is this some delusion of Authority ?

Why do you say that? These should be parameters (as they were in the original code). For example:

REAL (dp),parameter :: a0 = 3.3871328727963666080D0

Making them implicit save has obscured their purpose, and made the routine a minefield if it ever had to be modified for some reason.

I agree that the example does not use the save feature at all. The variables are only read and not assigned to (except for initialisation). So they act as parameters.

The code as linked upthread by @Beliavsky from “Alan Miller” has no legitimate reason to use implied save, those variables should have been named constants in the first place. That they were not is a reflection of some issue (compiler support with PARAMETER as an attribute starting Fortran 90 revision vs PARAMETER as a statement in the earlier standard perhaps?) at the time of the “translation” to free-form source (f90 as known colloquially) from the fixed-form “original” as linked above by @jacobwilliams which did have these objects as named constants…

To not apply the PARAMETER attribute to those objects cannot be acceptable as a conscientiously good coding practice. That “Alan Miller” gets associated with said code, and should the choice of implicit save instead in the code then be seen as some notion of a good practice by an “experienced” Fortranner of great repute and thus be considered “kosher” will be a poor argument best nipped in the bud.

TL;DR: the “Alan Miller” code linked here is a “textbook” example of the need to refactor certain existing Fortran code for the sake of continued good use of Fortran in numerical and scientific computing. The deletion of implied SAVE from the Fortran language standard can facilitate such useful refactoring. The benefits with breaking backward compatibility with this implied SAVE far exceed keeping it in the standard.

I have a timer code that I often use that relies on implied save. The concept is simple and I don’t think I will stop using it any time soon.

   real*8 function delta_seconds ()
     Integer*8 :: start = 0, rate = -1, finish
      if ( rate < 0 ) Call System_clock( start, rate )
      Call System_clock( finish )
      delta_seconds = dble( finish - start ) / dble ( rate )
      start = finish
   end function delta_seconds
1 Like

It would work like this as well, but reads clearer, no?

   real*8 function delta_seconds ()
     Integer*8, save :: start = 0, rate = -1
     Integer*8 :: finish
      if ( rate < 0 ) Call System_clock( start, rate )
      Call System_clock( finish )
      delta_seconds = dble( finish - start ) / dble ( rate )
      start = finish
   end function delta_seconds
2 Likes

Agreed! There’s nothing intrinsically wrong with EXPLICIT save (integer, save :: ..). It’s very clear, obvious, and self-documenting. It’s not the minefield that is implicit save.

I rarely if ever use save variable though. Any time it seems like something needs a global state like that is a clue that it probably should be a class.

1 Like

The clock rate argument to SYSTEM_CLOCK is allowed to be either integer or real. Any particular reason for favoring integer over real?

Re: “probably should be a class,” - aka a derived type in Fortran parlance.

And there have been many illustrations of that online generally and with Fortran including at this forum, see here.

With this, a simple timing “instrumentation” becomes

   call timer%start()
   .. ! some instructions here  
   call timer%stop()
   ! the "delta seconds" are fetched via timer%t()
   print *, timer%t()

Bottom-line here: no SAVE variables needed with this. Such a “timer” type can then also be used in codes which are not the traditional sequential/serial execution ones.

1 Like

Classes require declaration (and potentially also initialization) which might not be desirable. Of course you could expose only a single, global, timer instance. IMO, this depends a lot on your requirements/needs and tastes.

Both cpu_time and system_clock maintain a global state and are not derived types. Having a “timer” or “stopwatch” type is really more about convenience/flexibility of the interface, IMO.

Here’s a few “stopwatch” classes I’m aware of:

Probably you could find dozens more similar classes in large Fortran codebases. Given how many times this has been re-invented, it would make a nice addition to stdlib: Timer support · Issue #607 · fortran-lang/stdlib · GitHub

But if by using a class a.k.a. derived type you are referring to some global state variables defined in a module, you still build upon an implicit save, now attributed (since F2008) by default to all module variables.
If you just allocate a DT object in a procedure, set some variables in it but then exit the procedure, it will be deallocated automatically unless given explicit save attribute. Same with a locally defined DT object. Am I right?

What I had in mind was the singleton pattern, where you keep the type definition private and only expose an instance:


module global_timer

type, private :: timer_type
   ! ... timer state ...
contains
   ! ... timer methods ...
end type

type(timer_type), public :: timer = timer_type(...)

end module

Right. For this reason the change is extremely unlikely ever to happen.
The best we can hope for is a directive to change the default, like implicit none(save)
suggested in https://github.com/j3-fortran/fortran_proposals/issues/40.

Are there any compilers that (even optionally) warn about this? It seems odd they wouldn’t,
considering how dire the problem seems to be based on this discussion.

1 Like

Huh?! something that is a system/processor state in a de facto critical section and which doesn’t present a data race or a lock condition scenario is in no way equivalent to a user introducing some static data with a needless SAVE attribute.

No, this is not correct. It doesn’t have to be this way. The standard could simply no longer allow this syntax in subroutines and functions:

integer :: i = 1

That would be a syntax error. It wouldn’t be changed into something else. This is no different then, for example, removing forall, which was also done. So, any forall statement in old code are now no longer standard, and you get an error If you tell the compiler to rigorously enforce the standard.

Although, honestly, if the standard was changed to make the above equivalent to:

integer :: i
i = 1

I am 100% percent sure that it would fix more bugs than it causes.

What a nightmare if this comes to pass. Adding yet more boilerplate to every single fortran file in order to remove some dumb old feature that nobody should be using anyway. Where will it end?

module modern_fortran_2525
   implicit none (type, external, save, block data, namelist, hollerith, enumerator, blork, photon, strawberries)
...
1 Like

If you have Fortran syntax: " integer :: i = 1", but you want to change the definition to it not implying save, then what does it mean ?

What do you propose the functionality of the statement " integer :: i = 1" becomes ?

Without implied save, the statement does nothing.
Is it some statement of intent for the compiler to ignore ?

It has been an accepted statement for 30 years. How many bugs would be introduced by removing implied save ?

The statement only has meaning if save is implied.

Regarding my use of " seconds = delta_seconds () " to time a section of code, can anyone appreciate the simplicity of this approach ?
Why make it so much more complex with class etc but without any improvement ?

Forall has been made obsolescent but has not been deleted. To get an error you would need to use an option that turns compiler warnings about obsolescent features into errors.

Knowing the history makes more sense of the behavior. To keep it short there has always been a way to set the value upon each entry by having an statement in the executable block of a routine by just using
NAME=VALUE. So the assignment on the declaration was basically introduced to duplicate the behavior of a DATA statement at the time, not to duplicate the C feature. There is a very convoluted pre-history which makes the story more complicated (most systems that ran image-in image-out without any dynamic allocation and/or loading saved everything, but the standard did not really have a model for data that went out of scope; as that was added the whole saga of how DATA, COMMON, and then BLOCKDATA and SAVE interacted, …). So if you are not locked into assuming that something must act like C to be intuitive it is not that bad. As it is not really does not bother me personally; what did bother me was all the inconsistent behavior before that and when codes that had been written on platforms that saved everything were moved to machines that did not the codes often worked by accident if the programs never paged during execution (but then would fail “mysteriously” intermittently on heavily loaded machines). Convincing people they needed to go through their code and mark what should be saved and what should not be often failed, resulting in many older codes just having a plain “SAVE” statement in every routine, and so on. So i actually appreciate in new code that I can forget BLOCKDATA, COMMON, and SAVE statements existed, and use the parameter attribute and/or declare a value to get all those old behaviors in a predictable manner. If some of the changes described were made, they need to take all that behavior into account combined with the behavior of the PARAMETER attribute.

In my mind I wish something like the PURE attribute would have meant the procedure could use no deprecated feature (no COMMON, implicit none implied, nothing saved, …) but the list of deprecated features will always be a moving target, so that is not a perfect solution either.

2 Likes