module foo
type :: bar
integer :: n
end type
contains
subroutine init(this, n)
type(bar), intent(out) :: this
integer, intent(in) :: n
this%n = n
block
real :: array(this%n) ! <== COMPILATION ERROR HERE
end block
end subroutine
end module
Both the gfortran and oneapi compilers flag the array declaration as an error because THIS is an INTENT(OUT) dummy argument and thus cannot be used in a specification expression.
The NAG compiler compiles without error (and does the “expected” thing). On the surface this seems entirely reasonable, because THIS is defined before the block and there shouldn’t be any issue with the declaration of ARRAY which is local to the block and not the subroutine.
However the 2018 standard doesn’t appear to make any distinction for specification expressions used in a BLOCK versus a procedure (11.1.4, 10.1.11 par 1,2a). So unless I’m missing something, NAG is wrong here. It’s as if such declarations within a block are partly lifted as a declaration at the host procedure level and thus subject to the same restrictions. But do note 11.1.4 par 3: “Execution of a BLOCK construct causes evaluation of the specification expressions within its specification part in a processor-dependent order […]”
This looks like an oversight and it strongly reminds me of another related issue: the block and associate constructs were not included initially in the openmp standards. In particular, in remained unspecified whether a variable declared within a block statement is shared or private:
!$omp parallel default(private)
block
integer :: i
! race condition?
i = 5
print *,i
end block
!$omp end parallel
The sensible attribute would be private. But ifort actually assumed it as shared. Your observation (i.e. that a declaration within a block is partly lifted as a declaration at the host procedure level) partially explains this rather unexpected behaviour.
On the other hand, variable specification expressions, which can only be evaluated within the procedure, are specifically allowed and work as expected, like in:
program block_localvar
implicit none
call test()
contains
subroutine test()
integer :: i
read(*,*) i
block
integer, dimension(1:i) :: a
print *,size(a)
end block
end subroutine test
end program block_localvar
nvfortran is OK with this code, too. But I can’t say if ifx and gfortran or wrong or not here. Looking at the standard, I can’t find anything that differentiates the declarations at the top of a procedure or within a block, which tends to mean that this is not a conforming code (and that nag and nvfortran are more permissive than the standard).
The corresponding internal routine also gives the same error with gfortran-{10,11,12}.
module foo
type :: bar
integer :: n
end type
contains
subroutine init(this, n)
type(bar), intent(out) :: this
integer, intent(in) :: n
this%n = n
!! call set(this%n, n) !! some routine from elsewhere (*)
contains
subroutine intsub()
real :: array(this%n) ! <== COMPILATION ERROR HERE
end subroutine
end subroutine
end module
The reason why this (with intent(out)) cannot be used for declaration might be related to that it is not generally straightforward to reason about the current state of this for use in subsequent declarations (e.g. when other routines like set() is used). But access to this in a statement like print *, this%n is allowed, so I guess the standard might have chosen a safeguard (?) approach rather than “it is your responsibility” approach (unless both gfortran and ifx have bugs )
EDIT: But local variables also can have the same complexity, so there seems no inherent reason why this cannot be used for declarations in block or internal routines…
BTW, I wonder what happens for i in a C/C++ code corresponding to the Fortran code below in which block is replaced by a curly block ({...}). Because block and {...} are similar, the treatment of i (private vs shared) may have common aspects.
!$omp parallel default(private)
block
integer :: i
! race condition?
i = 5
print *,i
end block
!$omp end parallel
OpenMP 6.0 is bringing block enhancements like this:
subroutine hello()
use omp_lib
implicit none
!$omp parallel
block
integer :: tid
tid = omp_get_thread_num()
print '(A,I4)', 'Hello from', tid
end block
end subroutine
To see what happens at run time (if a compiler lets a program get there) I provided a main program using the module and made it print something, thus:
! file blockproblem.f90
module foo
type :: bar
integer :: n
end type
contains
subroutine init(this, n)
type(bar), intent(out) :: this
integer, intent(in) :: n
this%n = n
block
real :: array(this%n) ! <== COMPILATION ERROR HERE
integer :: i
array = [ (i,i = 1,this%n) ]
print "(A,*(1X,F0.3))",'array =',array
end block
end subroutine
end module foo
program blockproblem
use foo
type(bar):: this
call init(this,4)
print "(A,*(1X,I0))", 'this%n =',this%n
end program blockproblem
Lfortran and AMD flang both printed
array = 1.000 2.000 3.000 4.000
this%n = 4
FWIW I did not find a prohibition in the standard of having an intent(out) variable in a specification expression in a block inside the subroutine, but in this program that variable is evaluated before the block is executed. It would not make sense to do it only after executing the block. Is that why variables from outside the block cannot be used inside it as if they were host-associated?
There is a blanket prohibition against using an intent(out) dummy in a specification expression; it doesn’t distinguish between those for variables local to a subroutine vs those local to a block.
Is that why variables from outside the block cannot be used inside it as if they were host-associated?
But variables outside the block can be used inside the block.
I brought this up only because once you move declarations to the host procedure level, restrictions like prohibiting intent(out) and making those variables shared by default make sense. At least to some extend, as the usage of local variables whose value is determined only at runtime is allowed.
Otherwise I do not see any conceptual difference between an intent(out) variable and a local variable of the same type. Both are undefined at the start of a procedure. It should not make any difference to a compiler, except where to find/place such a variable.
(BTW: associate and block constructs were introduced in openmp 5.1)
I have now found where the standard forbids INTENT(OUT) in @nncarlson’s program:
F2018 or F2023 10.1.11 para 2 item (2). Note that INTENT(INOUT) would have been OK.
I apologise @nncarlson if I offended you: I merely wanted to put on record where in the standard the prohibition was, because there are many references to INTENT(OUT).
I’m just showing what OpenMP 6.0 offers. If you don’t like it, you don’t have to use it. If you like end directives, you can add them. tid is privatized by the block scope.
This is one of those theorem proving exercises that is hard to intuit from a straightforward reading of the standard. NAG is correct in accepting this code because within a scoping unit entities accessed by host association are not dummy arguments. I.e.
subroutine s(x)
real :: x ! x is a dummy argument
...
! up to here
block ! x is not a dummy argument within here
...
end block
! back in original scope, so x is a dummy argument
...
end subroutine
I.e., from 10.1.11 par. 2, item (4) applies
an object designator with a base object that is made accessible by use or host association,
Is this convention stated clearly in this way in the standard? Or is there a statement that an entity cannot both be host associated and be a dummy argument?
edit: It should be added in this context that host association of a dummy argument can occur both for BLOCK constructs and for contained subprograms. I would think that the loss or retention of the dummy argument status would apply to both cases in the same way.
Unless I’m misunderstanding this comment, the allocatable attribute of a host associated entity is not lost within a BLOCK or within a contained subprogram. It is only when that entity is associated through a dummy argument that it loses its allocatable attribute. In this case, the bounds of the entity can also change, so there are other associated features in this case too.
The key word is analogous. I’m just saying that there’s precedence for certain things being invisible (even) within the same scoping unit:
In the block (not block-construct) of a type-guard-stmt (which is part of the select-type-construct), the allocatable attribute is invisible.
EDIT: the following code illustrates my point:
implicit none
type :: a
end type
type, extends(a) :: b
end type
class(a), allocatable :: x
type(b) :: y
x = y ! x is allocatable
select type (x)
class is (a)
x = y ! x is not allocatable
end select
x = y ! x is allocatable
end
The gfortran, ifx and flang_new compilers emit the appropriate error about x being polymorphic but not allocatable within the type-guard-stmt’s block —and ifx even throws an extra error just to confuse things, .
In the program below, the block in my previous one is replaced by an internal subroutine blocksub, in which this%n is host-associated so may be allowed in a specification expression, but it was INTENT(OUT) in the host so may not. Lfortran segfaults with this program but it ran my previous version.
! file subproblem.f90
module foo
type :: bar
integer :: n
end type
contains
subroutine init(this, n)
type(bar), intent(out) :: this
integer, intent(in) :: n
this%n = n
call blocksub
contains
subroutine blocksub ! replacing block in blockproblem.f90
real :: array(this%n) ! bad if intent(out), good if host-associated
integer :: i
array = [ (i,i = 1,this%n) ]
print "(A,*(1X,F0.3))",'array =',array
end subroutine blocksub
end subroutine init
end module foo
program blockproblem
use foo
type(bar):: this
call init(this,4)
print "(A,*(1X,I0))", 'this%n =',this%n
end program blockproblem
I thought it good to bring this topic to a conclusion. Some time after starting this topic, I posted the validity question to the J3 mailing list with the same example here which I extended to include the internal subroutine case posed by @septc. The final response from Robert Corbett seemed to be definitive with no push-back: the internal subroutine case is valid (pretty obviously so) and the block case is not valid. He gives a compelling analysis of the block case. You can read the email thread here. He suggests, as others have here, that the constraint for the block case was likely an oversight and not intentional. It’s interesting that of all the compilers tested, they either accept both as valid or reject both.