Repeat count for modern-style initializations

One of the common suggestions for modernization is to replace

real var
data var / 0.0 /

with

real :: var = 0.0

But is there a modern form of the repeat count? For example, this fills a 200-element array.

real y(200)
data y / 50*0.0, 50*1.0, 50*2.0, 25*3.0, 25*4.0 /

But this form doesn’t work:

real,dimension(200) :: y = [ 50*0.0, 50*1.0, 50*2.0, 25*3.0, 25*4.0 ]
init.f90(4): error #7948: In this initialization, there are more variables than values assigned to the variables.   [Y]
real,dimension(200) :: y = [ 50*0.0, 50*1.0, 50*2.0, 25*3.0, 25*4.0 ]
-----------------------^
compilation aborted for init.f90 (code 1)
1 Like

There are implied do-loops, for example

implicit none
integer :: i
integer :: v(5) = [(4, i=1,2), (8, i=1,3)]
print "(*(1x,i0))", v ! 4 4 8 8 8
end
2 Likes

Thanks, I can see how that works. Implied do-loops are much more powerful than simple repeat counts. But for the trivial case in my example, implied do is a bit clunky, with the throwaway integer variable.

1 Like

This can be done in some cases, usually simpler ones, but not for all. For example, the data statements allow partial initialization of arrays (the first few elements, or the even elements, etc.), while the assignment syntax doesn’t. The data statements can be broken up into a series of statements, while the assignment syntax requires everything to be together in a single statement. Also, the array constructor syntax is more verbose, and if RESHAPE() is necessary, more cumbersome.

You can avoid the loop variable by defining an operator:

module m
implicit none
interface operator(.r.)
   module procedure rep
end interface
contains
function rep(val, n) result(vec)
integer, intent(in) :: n, val
integer :: vec(n)
integer :: i
vec = [(val, i=1,n)]
end function rep
end module m
!
program main
use m, only: operator(.r.)
implicit none
integer :: i
integer :: v(5) = [(4, i=1,2), (8, i=1,3)]
character (len=*), parameter :: fmt_i="(*(1x,i0))"
print fmt_i, v ! 4 4 8 8 8
print fmt_i,[4.r.2, 8.r.3] ! same
end program main
1 Like

While this works for array constructors in executable statements, ifx 2024 doesn’t like user-defined operators in initialization.

repeat.f90(20): error #6973: This is not a valid initialization expression.
integer :: w(5) = [4.r.2, 8.r.3]
--------------------^
compilation aborted for repeat.f90 (code 1)

And gfortran 8 says it can only use intrinsic functions in initialization expressions.

repeat.f90:20:23:

 integer :: w(5) = [4.r.2, 8.r.3]
                       1
Error: Function ‘rep’ in initialization expression at (1) must be an intrinsic function

I’ve also tried a similar approach, here using a usual function (ones()). But even if it is made pure, the compiler (here gfortran) rejects it as illegal, because ones() is not an intrinsic function. Because this function has no side effect, I wonder why it cannot be used at compile time…

module mylib
    implicit none
contains
    pure function ones(n) result(arr)
        integer, intent(in) :: n
        real :: arr(n)
        arr(:) = 1
    end
end module

program main
    use mylib
    real :: y(20) = [ ones(5)*0, ones(5)*1, ones(5)*2, ones(3)*3, ones(2)*4 ]
    print *, y(:)
end

$ gfortran test.f90
   19 |     real :: y(20) = [ ones(5)*0, ones(5)*1, ones(5)*2, ones(3)*3, ones(2)*4 ]
      |                          1
Error: Function 'ones' in initialization expression at (1) must be an intrinsic function

That is unlikely a “common suggestions for modernization”.

What might be FORTRAN code as

     REAL VAR
     DATA VAR /0.0/

will require analysis to ascertain whether the “implied SAVE” is really necessary. The refactoring decision will depend on this analysis.

More often than not, the modern Fortran replacement will be

   real, parameter :: VAR = 0.0

In a few cases, it might call for an object definition in the executable section of the code separate from the variable declaration:

   ..
   real :: var
   ..
   var = 0.0

In a few unfortunate situations, the modern Fortran replacement may need to

   real, save :: var = 0.0   !<-- inform the reader explicitly the object has the SAVE attribute

Integer :: ints(100)=[spread(50,1,49).0.0,spread(-50,1,49)]

As mentioned implied do is more general but that is as close to a matlab ones function that I know of. Would be nice to initialize data like with nameless data with repeat and skips and even user defined type support as mentioned but I actually like data statements but appreciate when the compiler warns not all values are initialized when it is not intentional

1 Like

If the throwaway index is a bother, a coder can always resort to various verbose options of fast decreasing levels of elegance:

   real, parameter :: zero(50) = 0.0, one(50) = 1.0, two(50) = 2.0, three(50) = 3.0
   real :: y(200) = [ zero, one, two, three ]  !<-- Note y has implied SAVE attribute

or an object definition in the executable section:

   real y(200)
   ..
   associate ( i => 1 ) 
      y = [ [( 0.0, i = 1,50 )], [( 1.0, i = 1,50 )], [( 2.0, i = 1,50 )], [( 3.0, i = 1,50 )] ]
   end associate

or a similar one with a BLOCK construct as opposed to ASSOCIATE.

And the NAMELIST option with the repeat specification!

   real :: y(200)
   namelist / dat / y
   character(len=:), allocatable :: s
   s = "&dat y=50*0.0,50*1.0,50*2.0,50*3.0 /"
   read( s, nml=dat )
   print *, y(1), y(51), y(101), y(151)
end
2 Likes

The old way of doing that on a single line

Real arr(100)/50*1.0,50*3.0/

Which I remember as an extension that I remember as being different from data in that the size had to fit but now I am thinking there is a chance that was std? It seems like I remember everyone had it but everyone had real*8 too

Another nice thing about DATA is it will fill multi- dimensional variables easily without calling RESHAPE. Ifx and gfortran support the inline data syntax too and ifx allows the vector to fill multi-dimensional arrays without reshaping.

Integer :: Ii(3,4)=[1,2,3,4,5,6,,8,9,10,11,12]
Integer  kk(3,4)/3*1,9*0/

Work in ifx

Is this standard or an extension?

I’m confused by this comment. Doesn’t a data statement imply save?

As I searched google for the answer to that question I found one of your posts saying that it does.
[Edit: The Fortran 2003 draft includes this language:]

image

If true, why would this be an “unlikely” suggestion if it’s semantically equivalent?

I would certainly not assume most data initialized variables should be treated as parameters. Some might have been used that way, but parameter has been part of the language for a long time and many developers would have used it where it was needed.

Both are extensions. Breaking the declaration and the data into two lines is standard

Integer :: ii(3,4):data ii /12*55/

Another one that might be wasteful

Integer,parameter:: ones(100)=1
Integer :: jj(10)=[ones(:10)*44]

That is, make a big vector of one or zero values and multiply or add values to subsections. Sort of a version of the matlab functions zeros and ones. Making an array big enough for your largest arrays would get wasteful depending on how clever the compiler is.

There is still much legacy code written before f77 (where PARAMETER was introduced to the language) that used DATA initialization. In those cases, the “modernization” to f77 would have consisted either of changing to PARAMETER or to DATA with a SAVE statement. So the same issue remains with this legacy code when modernizing to post-f77 standards. The difference now is that SAVE is implicit, where it was not in f77. In hindsight, that implicit save has turned out to be a poor choice in the language, and many programmers, including me, prefer to add the SAVE attribute explicitly even though it is now redundant.

I was asked once at a (Go-related) job interview for the best and worst features of the language (goroutines and enums, respectively).

In the case of Fortran, I would choose allocatable/allocate for best feature, and implicit SAVE as the worst one.

It seems to me that implicit SAVE often conflicts with the possibility of adding certain other features to the language… and it’s also a “gotcha” for newcomers.

1 Like

You can upvote the issue

1 Like

Is it reasonable to assume anyone who is running the F77 codes today is using a modern compiler in which data comes with implicit save? Or are people still using compiler options to force F77 semantics and turn off implicit save on data statements? Barring that kind of compiler option, I think the first two code snippets in my original post are semantically identical and should not change any current behavior of legacy codes.

In f77, the behavior was undefined when an unsaved variable was modified, so there isn’t really a meaning to “F77 semantics” in this case. The decision by the standard committee for implicit save was a way to bring such previously nonconforming code into conformance. It was the tail wagging the dog. And along with that, it complicated the issues of recursion and parallel execution. That was the trade for that decision. But, since implicit save has been part of the standard for over two decades (f2003, I think), it is unlikely to change.