Allow newunit to allocate an integer variable

Could the newunit specifier of the open statement be extended so that if an allocatable integer variable that has not been allocated is passed, it is allocated by the open statement? For example, in the code below, I would like the invalid line to be valid.

implicit none
! integer, allocatable :: iu ! invalid
integer :: iu
open (newunit=iu, file="temp.txt", action="write")
write (iu,*) "hello"
end

A benefit of using an allocatable integer as a unit number is that when you write

call foo(x, y, log_unit)

you can turn logging on or off by allocating (or not) log_unit before calling foo, since
an unallocated variable passed as an argument is not PRESENT. You don’t need separate call statements for logging or not logging. This proposal is motivated by the current thread Writing to a file or a string with the same function.

2 Likes

Interesting idea. There is some precedence here, as we now allow unallocated, allocatable, deferred-length character variables in a handful of places now. That said, your motivating use case/design is still achievable without the feature, even if the opening of the file would take multiple lines, so I don’t see a high priority on this.

I thought of another rationale for my proposal. Before a statement

open (newunit=iu, file="temp.txt", action="write")

the variable iu typically will not have been set. If you allow iu to be allocatable, then using it before the open statement will cause a run-time error. If iu is not allocatable, using it before it is initialized may pass unnoticed.

1 Like

There’s a related concept (I think) in which an unallocated character string can’t be used for the iomsg argument of the open statement. The issue is that the max/actual length of iomsg is unknown, so fixed-length and preallocation are not good solutions.

Under the hood does it make sense though? My understanding is that these would be passed by reference, so passing an unallocated variable as an argument has no meaning. Would you require the compiler to identify such a case and implicitly allocate it before passing? But if it’s allocated before passing, how would the compiler ensure the allocation conforms with what the called function needs?

@Machalot ,

Thankfully the current standard revision, Fortran 2023, has addressed this aspect

You can look for the feature in compilers seeking to support Fortran 2023 when they decide do so, this year or X years from now.

It is routine to pass an unallocated argument to a subroutine, but the dummy argument must have the allocatable attribute. I think this situation in f2023 is a little different because the actual argument might not be allocatable, so the argument association mechanism must be able to tell the difference. A normal subroutine does not have that flexibility.

OPEN is a Fortran statement - not a function or subroutine. The compiler can do whatever it wants to correctly implement the statement, without being bound to normal calling sequences.

I agree that such things are possible, and there are numerous examples of this already in the language, but is this something that we programmers should be encouraging? If some feature is useful for the language semantics, then it is very likely to be useful for programmers too. And the contrapositive is that if something is forbidden for programmers, then maybe it should not be encouraged as part of the intrinsic language.

The print, write, read, allocate, and deallocate statements can take any number of “arguments” of any type, kind, and rank, and Fortran would be much less convenient if those statements did not have such flexibility. I think the closest a procedure can come to this is to have many class(*),intent(in),optional arguments. It would be nice if a non-intrinsic function could have a return type that depends on a kind argument that is known at compile time, as
real(a [, kind]) does. Does the intrinsics proposal allow that?

1 Like

I did write up such a proposal for this as a F202Y work item, but the committee did not feel this was a good approach, and that the use of mold arguments was generally sufficient.