Building a derived type array in a loop

Hello,

I’m fairly new to Fortran and I am trying to modernize some ancient Fortran code in an effort to a) understand what it is doing b) get it working again as it will not compile.

I am having some issues brining over a structure into a derived type in that the variable does not have a fixed size and is built in a do loop

Here is (a variation) of the original:

   structure/inDX/
      character*10 name
      integer      in_num
      integer      nex
   end structure
   record /indx/ SRTNDX(*)
   parameter  (nslt=1000) !this is going to be an input value into the subroutine

  DO  I=1,nslt
   SRTNDX(I).name   ='          '
   SRTNDX(I).in_num =    0
   SRTNDX(I).nex    =    0
  ENDDO

For which I have replaced it with:

  type :: indx
        character(10)  :: name
        integer       :: in_num
        integer       :: nex
  end type
  type(indx),allocatable :: SRTNDX(:)
  integer :: nslt  !set to 1000 when the subroutine is called
  DO  I=1,nslt
       SRTNDX(I)%name   ='          '
       SRTNDX(I)%in_num =    0
       SRTNDX(I)%nex    =    0
  ENDDO

This gives me an error of invalid memory reference
I would like to know:
a) how to get this working in the methods given;
b) how could I just simply populate all the values in srtndx to a default value without having a loop

a) You have to allocate the array srtndx before you can index it. Also, nslt needs to be given an actual value before you can allocate/loop.

1 Like

great thanks.
such a simple thing…just needed the work allocate to be in my head

1 Like

The dot nomenclature is much more readable than the %. It’s just odd that that nomenclature wasn’t carried over to derived types.

1 Like

One way is sourced allocation.The array elements are set within the allocate statement. It looks like this.

allocate( SRTNDX(nslt), source=indx(' ',0,0) )

In this statement, the scalar derived type is copied to each array element. This approach is useful is you want to allocate several different arrays of that type, each with different initial values.

Another way to do this is with default initialization. First, you define the derived type as

type :: indx
   character(10) :: name = ' '
   integer       :: in_num = 0
   integer       :: nex = 0
end type indx

Then when you allocate the array,

allocate( SRTNDX(nslt) )

no further assignments are required.

edit: There is also the possibility of an array assignment.

allocate( SRTNDX(nslt) )
SRTNDX(:) = indx(' ',0,0)

Of course in this, and in the other cases, the computer instructions are indeed performing a loop over the array elements, even though your fortran code does not have a “loop”.

2 Likes

The dot nomenclature is much more readable than the %.

The presentation of derived types in the learning section only uses the % sign. Does it even mention one can substitute it by the dot?

The component separator in Fortran is “%”, not “.”, so there’s nothing to substitute :slight_smile:

1 Like

Besides @RonShepard’s great example, another way I often use is to define parameters for structures that have well defined elements. This removes the need for the ugly percent signs.
In your case, you may have

type(indx), parameter :: EMPTY_INDEX = indx(name='EMPTY',in_num=0,nex=0)

Then use it anywhere you like just like another scalar, some examples: :

STRNDX(1:25:7) = EMPTY_INDEX
where (STRNDX%nex<0) STRNDX = EMPTY_INDEX

etc.

IIRC, my old copy of Digital Visual Fortran had the dot nomenclature as an extension —which means it was either DEC’s own extension or something introduced by Microsoft (and likely supported by Intel compilers).

But consider this:

      cond=a.eq.b.and.c.eqv.d

Since relational/logical operators and the boolean constants in Fortran are enclosed by dots (maybe because the original IBM keyboards lacked “<” and “>”? ), fixed-form source is not space-aware, and also because Fortran doesn’t have any reserved keywords, something else had to be picked when they introduced derived types into the language.

(Although “->” was an obvious second choice, maybe they didn’t want to deal with two keystrokes)

As a trade-off for using “%”, we were also given user-defined operators.

Depending on your editor, different coloring could be applied to the “%” occurrences.

1 Like

I’ve heard the argument many times about how the dot nomenclature is impossible due to the way Fortran does Boolean. But what I’ve learned from this thread is that in reality it was possible, because one one of the most popular compilers in the Fortran ecosystem already doing it. Now its a question of picking the right tradeoffs (Readability vs a parsing complexity, etc) It’s all academic at this point anyway.

1 Like

This is a legacy feature from f77-era compilers. F77 did not have user-defined operators. Once user-defined operators were added in f90, I think it became impossible to distinguish expressions from nested component notation using periods. The statement above cond=a.eq.b.and.c.eqv.d is a good example. Is that a simple nested component assignment, or an expression involving components, or a mixed expression of derived types with components, or an expression involving derived types with user-defined operators? You cannot tell from just the syntax.

Independendly of the parsing complexity, readability of the dot notation is questionable in Fortran, precisely because there exists the user defined operators. v = x.y is unambiguous, but v = x.y.z is: if you read it in a code that you haven’t written and that you don’t know, you may wonder if it’s a nested derived type reference, or a user defined operator .y.. Even if the compiler was able to parse it correctly by using the context (*), you will have to do your own parsing by examining other parts of the code.

(*) You are probably talking about the Intel compiler here, but there are cases were the Intel compiler is not able to disambiguate the dot notation and produces a compilation error. Admittedly these are corner cases that a developer should not write like that, but this illustrates that there is a fundamental issue with the dot notation.

It’s not impossible, but ambiguous. The compiler can…

  • Compile correctly and produce the right code.
  • Compile correctly but produce wrong code.
  • Fail to compile.

And there’s also the issue of opting-in to vendor lock-in.

(I admit that I’m so used to % that I fail to see its perceived ugliness, and I sometimes default to it when coding in a different language, e.g., by typing fmt%Println when in Go)