Length(s) of allocatable character array?

One compiler printed

words: "firstsecond" lengths: 5 6

with this program:

  implicit none
  character(:),allocatable::a,b,words(:)
  a = 'first'
  b = 'second'
  allocate(character(max(len(a),len(b))) :: words(2))
  words(1) = a
  words(2) = b
  print "(4A,2I2)",'words: "',words,'" lengths:',len(words(1)),len(words(2))
end program

I suspect that different elements of an allocatable character array can’t have different lengths, but does the Fortran standard say so? If so, where?

See the first response in Character array constructor

But here, there is no array constructor. Instead, we have two assignments to words elements 1 and 2. The array surely has all elements of the same length, 6. So the only guess that comes to my mind is that your compiler treats ‘A’ descriptor as the F2023 new ‘AT’, i.e. with auto-trimming.
Edit: my guess is wrong, as it also gives len(words(1)) as 5.

NB. gfortran 14.2, ifx 2025.0.4 and ifort 2021.13.1 all give, IMHO poperly:
words: "first second" lengths: 6 6

1 Like

This is a very interesting question. Length is a type parameter, so changing the length of an individual array element would imply changing that element’s type parameter, but elements don’t have type parameters, only variables do; I haven’t found words saying so explicitly, though (they must exist somewhere!)

I then was looking at the description of intrinsic assignment, which is where you’re changing the length. 10.2.1.3 is where this is found, and it says, in part, “If the variable is an allocated allocatable variable, it is deallocated if expr is an array of different shape, any corresponding length type parameter values of the variable and expr differ, or the variable is polymorphic and the dynamic type or any corresponding kind type parameter values of the variable and expr differ.” You can’t, of course, deallocate an array element, but it seems to me that this wording could use some improvement. I will ask.

2 Likes

If the programmer wants this behavior, that is different array elements can have different lengths, or even different allocation status, then in fortran it is done with a derived type array where each element has an allocatable component. An example would be

type string
   character(:), allocatable :: s
end type string
type(string) :: words(1:2)
...
words(1)%s = 'first'
words(2)%s = 'second'

There are a couple of downsides to this approach. The programmer cannot initialize such an array

type(string) :: words(1:2)=['first', 'second']

or define such an array as a parameter constant. It would be nice if the language were extended to allow those things, but for now it is not allowed.

A second downside is that this is a user defined type, not an intrinsic type, so that introduces compatibility issues when codes and libraries from different origins are mixed together. In these case, the programmer must manually copy or move_alloc() the components among the various derived types.

I have always found the requirement to add the allocatable keyword to deferred length strings to be confusing. For folks relatively new to Fortran and who don’t understand that the elements of an array have to have a fixed length, the current syntax might imply that an array of variable length strings is possible (and I would love a way to construct an array of variable length strings without using a derived type). My personal preference would be that the allocatable keyword is only necessary when you want to create an array of strings of fixed length. For a scalar, I would think doing character(:) should be enough. You would only need to add the ALLOCATABLE if you want to create an array of fixed length strings at run time ala

character(:) , allocatable :: strings(:)
allocate(character(20):: strings(50))

and for just a scalar you want to set at runtime

character(:) :: a_string

a_string = "This is a string"

One can write an assignment like:
words = [string ('first'), string ('second')]

1 Like

Yes, the assignment works, but not initialization or as a parameter constant.

    6 |    type(string) :: words(1:2) = [string('first'),string('second')]
      |                                        1
Error: Invalid initialization expression for ALLOCATABLE component 's' in structure constructor at (1)

This is a general limitation of allocatable entities of any type, character, integer, real, etc., or in this case, of an allocatable component.

The F2023 standard does forbid character array elements having different lengths: 3.3 says an array is a set of scalar data, all of the same type and type parameters, and 7.2 para 2 says a type parameter is either a kind type parameter or a length type parameter.
I have reported the bug in the offending compiler. We shall all be interested to see what happens to 10.2.1.3.

Thanks for finding that - I had hoped such wording appeared, but I had not found it.

As for 10.2.1.3, that’s not a problem I now realize because, as we’ve said before, an array element cannot itself have the allocatable (nor pointer) attribute.

1 Like

My problem with 10.2.1.3 was due to the declaration

  character(:),allocatable::a,b,words(:)

where the second (:) says words is an allocatable array but the first (:) says the elements have an allocatable length.

I don’t see the problem with this declaration. You have two allocatable scalars of deferred length, and one allocatable array of deferred length. Can you elaborate? Maybe I’m overlooking something.

There was indeed no problem with that declaration. My mistake was thinking of the two (:) as indicating the same sort of allocatability. The difference between deferred length and deferred shape became clearer when gfortran and ifx reported that one of these declarations was not valid:

    character(:), allocatable:: x(2)
    character(2), allocatable:: y(:)
1 Like