Structure constructor with procedure pointer component

I want to construct a parameter array of a derived type containing a procedure pointer, but I cannot find any hint anywhere as to how to provide an actual procedure in a structure constructor? The following code shows the problem. It is somewhat close to what I want to achieve, i.e. construct an array of procedures and select the proper procedure depending on an integer argument. The resulting code should be as local and compact as possible since I do this to avoid boiler plate code, it should not replace one kind of boiler plating with another.

The following code compiles and work with gfortran and ifort with the commented out variant (ap as variable), but the structure constructor in the parameter variant fails with both.

module mod

implicit none
private

public exec

contains

subroutine exec(i)
   integer, intent(in) :: i
   type :: t_proc
      procedure(sub_1), nopass, pointer :: sub => null()
   end type t_proc
   type(t_proc), dimension(1:2), parameter :: ap = [t_proc(sub_1), t_proc(sub_2)]
   !type(t_proc), dimension(1:2) :: ap
   procedure(sub_1), pointer :: sel

   ! works as expected if ap is declared as variable above
   !ap(1)%sub => sub_1
   !ap(2)%sub => sub_2

   ! variant 1
   call ap(i)%sub(17.0)

   ! variant 2
   sel => ap(i)%sub
   call sel(257.0)
end subroutine exec

subroutine sub_1(z)
   real, intent(in) :: z
   print *, 'sub_1: ', z
end subroutine sub_1

subroutine sub_2(z)
   real, intent(in) :: z
   print *, 'sub_2: ', z
end subroutine sub_2

end module mod




program procptr

use mod
implicit none

integer :: i

do i = 1,2
   call exec(i)
end do

end program procptr
1 Like

It took me a while to work through what the standard says about this.

First, you have an array constructor as the initialization value for a named (PARAMETER) constant. The standard requires that this be a constant expression.

Next, we go to the rules for constant expressions (10.1.12). Here, an array constructor is fine as long as each element is a constant expression.

We’re still in 10.1.12, (3)(b) in this case, for structure constructors, where each pointer component “is an initialization target or a reference to the intrinsic function NULL,”.

So, what is an initialization target? For that we go to 8.2 where we see this:

R805 initialization is = constant-expr
or => null-init
or => initial-data-target

Oh, look. Initialization to a procedure target is not allowed! Therefore, you can’t have a procedure in a constant expression.

I seem to recall that there was some discussion earlier of allowing initialization of procedure pointers, but it didn’t make it in.

3 Likes

Thanks a lot for checking. I already surmised by the error messages of the two compilers that the standard did not allow this, but could not think of a good reason why that should be the case. Maybe there is no good reason (except may that somebody would have to implement the feature).