Implied save behavior for defined-and-initialized variables

I hope that you are aware that Intel Fortran for Windows and Linux may be obtained, installed and used without any license fees having to be paid? Optional paid support contracts are available. A version for OSX on Intel CPUs was available in the past, but that version disappeared when Apple switched to ARM/Apple silicon.

1 Like

I donā€™t like the automatic reallocation either simply from the perspective of maximum performance: I want Fortran to keep the door open to maximum performance in Release mode, and it seems to me this feature closes the door, as it requires a mandatory runtime check. I think the priorities for Fortran should be: maximum performance in Release mode, and safety in Debug mode.

Fortunately, compilers can fix this: by disabling the automatic LHS reallocation, the compiler can give a nice runtime error if the shape does not match in Debug mode, and then not do any checks in Release mode.

That way if your code passes the Debug run, it will also work with automatic reallocation and with other Fortran compilers (possibly slower). And if you have some code that requires automatic reallocation, then you enable the automatic reallocation for just that code.

2 Likes

@wspector casually writes, " If the automatic reallocation isnā€™t wanted, instead of s use s(:),"

This change in Fortran 2023 actually breaks code - that is the point.

I find the statement by @wspector in rather poor taste.

Consider the case of ā€œimplied SAVEā€ with

..
integer :: x = 42  !<-- object x is implied to have SAVE attribute
..

There has long been a proposal to remove this ā€œimplied SAVEā€ from the standard whereby the standard includes a numbered constraint that requires a conforming processor to detect this implied attribute and report it as nonconforming.

Meaning, in a future revision of the standard

..
integer :: x = 42  !<-- Not ok - shall be detected and reported by the Fortran processor as nonconforming
integer, SAVE :: x = 42 !<-- Ok
..

But this will be never passed by any committee, all under the guise of backward compatibility with the ridiculous argument there are codes out there that will break. What codes? I would really like to know, seriously.

Whereas when it came to the Fortran 2023 change, the committee was casually willing to break the one code I genuinely knew about. If people on the committee really wanted to play doubting Thomas with me, I could have arranged for an official letter on company letterhead from the affected manager(s) of a company that is actually creating physical products all over the world that literally help transition of the energy sector away from carbon-based to renewable and using computational technology in various forms including Fortran to help the transition, all at great financial risk and effort it is putting in. But instead, in my case, the committee gave me the proverbial ā€œmiddle fingerā€

And how many other codes will be broken with the change in Fortran 2023 is not yet known.

It is this inconsistency with Fortran standard revisions that is so bothersome:

  • In one instance, recklessly change the semantics that silently modifies the behavior of conforming programs - break codes willy-nilly - and state nonchalantly with no regard for others that is not a big deal and impose a significant cost of change on users. So, is it these users less equal than others?
  • But in other cases like with implied SAVE, utterly refuse to change what can help with the practice of Fortran far more than it can hurt. So, is it the ā€œusersā€ who may have to update their code to include an explicit SAVE treated as more equal than others? Will @wspector et al. forcefully write to these users, ā€œIf the SAVE wanted is wanted, write the SAVE attributeā€? No, instead they will join the bandwagon this cannot be changed in the Fortran standard.

That is the crux of the problem with the practice of Fortran: discrimination.

Itā€™s a sticky wicket. I have always disliked implied SAVE when using initializers as well. (Yet another case where they failed to learn lessons from ALGOL.)

My comment on using s(:), rather than just s, for in-core writes is simply pointing out that the usage then becomes consistent with how allocatables have worked for the past 20+ years in other contexts. I am sorry you find it in bad taste.

My priorities these days tend to be reliability/robustness first, with performance a close second. Character string handling has always been ā€˜interestingā€™ in this regard. Generally character string stuff isnā€™t in the critical path of HPC code performance. So Iā€™m not that worried about it here. However if a compiler wants to offer helpful hints, such as pointing out hidden allocates/deallocates in inner loops, Iā€™m always willing to look at it.

But I donā€™t sit on the Committee and certainly canā€™t speak for them. Like many here, Iā€™ve occasionally offered suggestions for new capabilities and been ignored. Finally got error stop in F2008 after Iā€™d suggested it in writing to Rich Reagan (CDCā€™s Committee rep) back in the early 1980s.

Since f2003, the answer to this is for the programmer to change the lhs to a(:) or a(i:j) or something equivalent. This disables any runtime-checks to see if reallocation is necessary and allows the compiler to produce optimal code for performance. I assume the same thing can be done with the internal write situation in f2023.

The practical difference is that with f2003, the allocatable scalar was introduced also in that revision, so for the internal write situation, there was no backward compatibility issue. But now with f2023, there is 20 years worth of legacy code that uses the old convention that might break.

1 Like

Hi @RonShepard, Iā€™ve done some experiments with the following code, compiled on Windows 11 with ifort 2021.10.0. Here is what Iā€™ve found:

  • Iā€™m not aware of an option to disable implicit save.
  • /nostandard-realloc-lhs works as expected, but the right hand side gets truncated. Even /warn:all and /check:all do not detect this.
  • The length of the array after the internal write is still 10.

Maybe a newer compiler would have behaved differently.

program test_save_and_realloc

implicit none

integer*4 :: x
integer*4, allocatable, dimension(:) :: y

write(*, *) 'test_1: first call'
call test_1(x)
write(*, *) x

write(*, *) 'test_1: second call'
call test_1(x)
write(*, *) x

write(*, *) 'test_2:'
call test_2(y)
write(*, *) y

write(*, *) 'test_3:'
call test_3()


write(*, *) 'finished'

contains

subroutine test_1(a)

integer*4, intent(out) :: a
integer*4 :: b = 4  ! Implicit save.

b = b * 2
a = b

end subroutine test_1


subroutine test_2(a)

integer*4, allocatable, dimension(:), intent(out) :: a
integer*4 i

allocate(a(3))
a = 44
! With /standard-realloc-lhs  a = [1, 2, 3, 4, 5]
! With /nostandard-realloc-lhs  a = [1, 2, 3]
a = [(i, i=1,5)]

end subroutine test_2


subroutine test_3()

character(len=:), allocatable :: s
allocate(character(len=10) :: s)
write(s, fmt=*) "Hello"

! With /standard-realloc-lhs  len(s) = 10
! With /nostandard-realloc-lhs  len(s) = 10
write(*, *) "len(s) after write: ", len(s)

end subroutine test_3

end program test_save_and_realloc

@ricriv, you are not using a conforming Fortran 2023 processor, so your tests are not relevant to Fortran 2023 aspects of this subthread.

1 Like

I did not know I would strike a chord with this question, the behavior is definitely subpar regardless of its motivation. Obviously, 70-year old language must break things at some point. However, allow me to balance things out slightly;

If you remember my diatribes previously about the need for a better and contemporary (as opposed to ā€œmodernā€) array-first language I was not targeting just fortran :slight_smile:

I am as tired on the C++ side of things. Rust and Zig are really nice additions and I enjoy using them but hopefully this decade we will also have a contemporary array language and leave these discussions behind (not holding my breath but still hopeful).

1 Like

Yes, this reallocation within an internal write statement is a f2023 feature, so it would not be expected to be in a 2021 compiler.

You probably already know this, but this statement is not allowed without the reallocation semantics. Prior to f2003, a compiler might ignore some of the elements on the rhs (as your comment suggests), or it could overrun the array on the lhs and corrupt memory, or it could start WWIII. It was up to the programmer to ensure that such assignments did not occur.

1 Like

Yes. But it feels inconsistent. Consider an elemental function that inside does some polynomial evaluation, say r = x**2+x+1 (as a simple proxy example). Then letā€™s say you want to take this code, and only do it for a 3D array. You can just copy it as r = x**2+x+1 but now you are facing the LHS reallocation overhead. Or you can modify it to r(:,:) = x**2+x+1. But there are three issues:

  • you have to modify it
  • itā€™s not symmetric: some arrays are explicit with :, some are implicit. You could make it symmetric by further modification: r(:,:) = x(:,:)**2+x(:,:)+1, but itā€™s verbose.
  • Also the : modification is rank specific. The previous expression was rank agnostic.

Also when I learned modern Fortran, around 2010 or so, the advice given to me by an experienced Fortran user (physicist) was to use r = x**2+x+1. So it shows that this LHS reallocation issue is not obvious (or was not obvious).

The compiler can warn against this, and recommend to insert (:,:) to avoid the runtime check. That might be the best solution.

2 Likes

One wonders, in hindsight, if there might have been a better way to invoke reallocation that could have sidestepped all of these issues you list. Say something like

realloc(r) = x**2+x+1

if realloction (and the associated tests) are required, otherwise the simple expression would not invoke reallocation or (at least with optimization) perform the tests.

1 Like

@RonShepard Indeed. One can consider various other syntax for that as well, such as r <- x**2 + x + 1. I think the hard part is that there are two classes of use cases: One is performance oriented array computation, where you donā€™t want to do automatic reallocation. The other is Matlab style interactive computation where you just want the language to handle allocation automatically (for a slight runtime performance hit).

We havenā€™t got to this point yet with LFortran, but once we reach beta quality, I want to investigate all such cases from the runtime performance perspective, and figure out a (compiler enforced) subset that gives maximum performance, and actually deliver it.

Fortran overall is great, and it is really close to optimal, but it has these corner cases that still need to be addressed in my opinion.

Interesting side discussion on allocate on assignment. Iā€™m one of those people that got burned when all the major compilers moved from requireing something like -assume realloc_lhs to making allocation on assignment the default (which I think is what the standard required but nobody initially implemented it that way in the first releases of 2003 compilers.) I wasted a day chasing a segmentation fault that I thought was due to something I did only to find the system folks had upgraded the compiler that I was using and it now assumed allocation on assignment was the default. I personally would have preferred allocation on assignment not be the default for arrays but keep it for deferred strings. Also, another side question. Why is the ALLOCATABLE attribute required on deferred length strings ? I would think that having the : for the LEN parameter would be enough. In other words, ALLOCATABLE should only be needed when you are creating an array or an allocatable scalar. I guess a deferred string can be thought of as a scalar but I still think that ALLOCATABLE is overkill in that particular case.

1 Like

Yes, the strings should be handled separately, and I think reallocation there is fine.

I think this is due to the asymmetry in notation between character strings and arrays for dummy arguments. F77 used the notation character(*) to denote what is more or less the same as a modern assumed shape array x(:). That is, in both cases the size is determined by the actual argument and can be queried in the subprogram with the LEN() and SIZE() intrinsics respectively. If f77 had used character(:) notation instead, then things might look a little more consistent now, and the ALLOCATABLE attribute would be used for allocatable entities, (:) would be used for assumed shape entities, and when used together they would mean the same for characters and other data types. Of course, that would have required looking ahead several years in the 1970s to anticipate array syntax in fortran.

Since the title of this thread is about initialization, perhaps it would be useful to point out that fortran does not now allow any allocatable entity to be initialized, they can only be declared. It would be very useful if programmers could initialize allocatable entities. For example:

integer, allocatable :: array(-1:1)  ! initial size and bounds, undefined values.
integer, allocatable :: array(:) = [1,1,2]  ! initial size and values, default [1:3] bounds.

This would eliminate the need for many runtime allocations and assignments of allocatable entities, and simplify the logic for programmers in many algorithms and for many data structures related to allocation tests.

1 Like

@RonShepard , you know this has been discussed countless times on comp.lang.fortran earlier whenever you have brought it up and also on this forum. But it has not gained traction.

You should try to develop a paper proposing your idea further and start at the Issues Ā· j3-fortran/fortran_proposals Ā· GitHub site.

You can take heart from the work by @PierU on the following paper on ā€œcomplex pointers to real arraysā€ and see how well it has moved to the next stage, for this it was championed to an extent by @everythingfunctional . That is a model you can consider adopting:

You @RonShepard know best the semantics and facilities you have in mind with initialization of objects with ALLOCATABLE attribute and thus the onus is on you to advance this idea of yours forward. You can get help from @certik et al. to further refine the idea and/or even prototype your thoughts in LFortran. Give all this a shot, please. Otherwise, you may want to consider mothballing it, you know with ā€œfollow up now, or forever hold your peaceā€ rule.

1 Like