Allocate an allocatable character variable along with other data types

It is convenient to allocate multiple variables in the same statement. I am starting to use allocatable (dynamic length) character variables in my codes and wonder if it possible to allocate them in the same statement as other types of variables. My attempt to do so in the code below, commented ! not legal, did not work. (Would it be possible to extend the language so that it was legal?)

program main
implicit none
character (len=:), allocatable :: word
real, allocatable :: x(:)
integer, allocatable :: ivec(:)
allocate (character (len=5) :: word)
allocate (x(2),ivec(2))
allocate (x(2), character (len=5) :: word) ! not legal
end program main

I can’t think of an issue that would block this, but some might object to it as “syntactic sugar”. It would complicate the description of ALLOCATE because you’d have to explain how the type was chosen for allocate-objects that don’t have a type specified (think polymorphic).

I think there may be some syntactic ambiguities that make describing the feature, and detecting erroneous code a bit tricky. For example

class(base), allocatable :: foo, bar
...
allocate(type(child) :: foo, bar)

Is this allocating both foo and bar with dynamic type child? Or (assuming base isn’t abstract) does bar have dynamic type base?

class(base), allocatable :: foo
type(unrelated), allocatable :: bar
...
allocate(type(child) :: child, bar)

Is this allowed?

Note first there is an error in syntax: the standard oddly enough does not require nor permit the type-based declaration in a type-spec and instead asks users to go bare:

   allocate( child :: foo, bar )

With this syntax correction then, the answer to " Is this allocating both foo and bar with dynamic type child ?" is yes per the standard, it is allowed.

In the second case, I assume what you meant to show was

class(base), allocatable :: foo
type(unrelated), allocatable :: bar
...
allocate( child :: foo, bar )  !<-- i.e., not child, bar.

And in this case, one of the constraints in the ALLOCATE statement section of the standard re: type-compatibility should kick in and require a processor to detect and report it.

It is probably too late, but instead of the “NAME_OF_TYPE :: list” syntax, a functional syntax like

allocate(foo(len=10,dimension=4),bar(len=30,dimension=40),....) 

would have been better in my mind. Having a syntax almost like but not quite like a declaration statement where all the items on the RHS of the “::” have to be the same versus something without the “::” being allowed to be different types seems to have been a complicated solution, in that the behavior becomes so different as to act like two different statements.

Yeah, this is what I was trying to show, and I agree with your assessment. But this doesn’t address the OP’s question of “can we allocate variables of different types in the same allocate statement, where one (or more) of the variables require a type-spec in order to specify a length or kind type parameter?”

Now I don’t think it would be a bad idea to allow for this, but it’s not quite so easy as it might at first appear to design this capability in a way that avoids these pitfalls.

Can parentheses be required to avoid ambiguity? For example

allocate ((character (len=5) :: w1, w2), (character (len=1) :: a), x(2))

The type-spec would be required to be just before the variables it pertains to. One would write

allocate ((real(kind=dp) :: x(2)), (character (len=5) :: w1, w2), (character (len=1) :: a))