Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28477 Discussions

Is the following use of procedure pointers standard compliant?

thomas_boehme
New Contributor II
270 Views
Hello,

I have a question regarding standard compliance of a specific use of a procedure pointer.

In the following code, I use a procedure pointer that "almost", but not fully matches the interface with which the pointer was declared. Almost because one actual argument of the procedure the pointer points is an extension of the type defined in the interface.
I was suprised that the compiler accepted the code and actually works as intended for method 1 (see sample code). Note that there is an error shown when directly assigning the procedure pointer without an extra subroutine.

I guess the standard compliant way would be what I have included as method 2. However, this incurs a significant runtime overhead vs. method 1.

Therefore I would like to know if you think that the method 1 is standard compliant or not.

Best regards,
Thomas

[fortran]MODULE TestModule

!> A base class
TYPE tBase  
  REAL(8) :: Value 
END TYPE
! An extenstion of that calss
TYPE, EXTENDS (tBase) :: tBaseExt
  REAL(8) :: ValueExt  
END TYPE

TYPE, EXTENDS (tBaseExt) :: tBaseExt2
  REAL(8) :: ValueExt2  
END TYPE

TYPE, EXTENDS (tBaseExt2) :: tBaseExt3
  REAL(8) :: ValueExt3  
END TYPE

! A test class for procedure pointers
TYPE :: tProcPtrTest
  PROCEDURE (IGet), POINTER, NOPASS :: Proc    
  CLASS (tBase), POINTER :: MyClass
CONTAINS
  PROCEDURE SetProcPointer
  PROCEDURE CallPrint
END TYPE

! Interface for procedure pointer
ABSTRACT INTERFACE
  SUBROUTINE IGet(base, result)
    IMPORT tBase
    CLASS (tBase) :: base
    REAL(8) :: result
  END SUBROUTINE  
END INTERFACE
  
CONTAINS
  ! Print routine with a select type.
  SUBROUTINE Print(base, result)
    CLASS (tBase) base
    REAL(8) :: result
    SELECT TYPE (base)
      CLASS IS (tBaseExt)
         result = base%ValueExt
    END SELECT
  END SUBROUTINE
  ! Print routine without select type and directly using BaseExt
  SUBROUTINE PrintExt(BaseExt, result)
    CLASS (tBaseExt) BaseExt
    REAL(8) :: result
         result = BaseExt%ValueExt
  END SUBROUTINE  
  
  SUBROUTINE SetProcPointer(this, Proc, ClassPtr)
  CLASS (tProcPtrTest) :: this
  PROCEDURE (IGet), POINTER, INTENT(IN) :: Proc
  CLASS (tBase), TARGET, INTENT(IN) :: ClassPtr
  this%Proc => Proc 
  this%MyClass => ClassPtr
  END SUBROUTINE
  
  SUBROUTINE CallPrint(this, result)
    CLASS (tProcPtrTest) :: this
    REAL(8) :: result
    CALL this%Proc(this%MyClass, result)
  END SUBROUTINE 

END MODULE

    program ProcedurePointerTest
    USE TestModule    
    implicit none
    
    TYPE (tProcPtrTest) :: procPtrTest
    TYPE (tBase) :: base
    TYPE (tBaseExt) :: baseExt
    REAL(8) :: result, sum, tStart, tEnd
    INTEGER :: i    
    baseExt%ValueExt = 3
    
    !! Method 1
    ! Assigning a not fully matching procedure pointer works when using a subroutine
    CALL procPtrTest%SetProcPointer(PrintExt, baseExt)
    ! Note that assigning a not fully matching procedure pointer is not allowed directly. 
    ! The following, if uncommented gives an error: 
!    procPtrTest%Proc => PrintExt
!    procPtrTest%MyCmpnt => baseExt

    CALL CPU_TIME(tStart)
    sum = 0.0
    DO I=1,1e8
      CALL procPtrTest%CallPrint(result)
      sum = sum + result
    END DO
    CALL CPU_TIME(tEnd)
    WRITE (*,*) sum, tEnd-tStart

    ! Method 2
    ! in this case, the interface really matches and a select type is used.
    CALL procPtrTest%SetProcPointer(Print, baseExt)

    CALL CPU_TIME(tStart)
    sum = 0.0
    DO I=1,1e8
      CALL procPtrTest%CallPrint(result)
      sum = sum + result
    END DO
    CALL CPU_TIME(tEnd)
    WRITE (*,*) sum, tEnd-tStart
      
end program ProcedurePointerTest

[/fortran]








0 Kudos
1 Solution
Steven_L_Intel1
Employee
270 Views
Thomas,

Interesting questions.  I had to spend some time with the program and the standard to decide on how to respond.

First, the second commented-out line has two errors: There is no component MyCmpnt in type tProcPtrTest, it should be MyClass, and baseExt needs the TARGET attribute in order to be allowed as the target of a pointer assignment.  Neither of these are germane to your questions.

I believe that your first method is not standard-conforming and that the compiler should give an error for the procedure call, but as is often the case, one has to chase around the standard to see why.

12.5.2.9 (Actual arguments associated with dummy procedure entities) says:

"5 If a dummy argument is a procedure pointer [which in this case it is], the corresponding actual argument shall be a procedure pointer, a reference to the intrinsic function NULL, or a valid target for the dummy pointer in a pointer assignment statement."

It's this last clause that applies, so let's find the rule for that.  This would be 7.2.2.4 (Procedure pointer assignment):

"3 If the pointer object has an explicit interface [it does], its characteristics shall be the same as the pointer target ... [rest does not apply]"

So are the characteristics of Proc (the procedure pointer dummy argument) and PrintExt (the procedure target) the same?  Back to chapter 12, 12.3.1 (Characteristics of procedures):

"1 The characteristics of a procedure are the classification of the procedure as a function or subroutine, whether it is pure, whether it is elemental, whether it has the BIND attribute, the characteristics of its dummy arguments, and the characteristics of its result value if it is a function."

The only item in question here is the characteristics of the dummy arguments.  So let's see:

Proc (the procedure dummy argument) is declared using the abstract interface Iget, which is:

SUBROUTINE IGet(base, result)
    CLASS (tBase) :: base
    REAL(8) :: result
  END SUBROUTINE 

PrintExt is declared as follows:

SUBROUTINE PrintExt(BaseExt, result)
    CLASS (tBaseExt) BaseExt
    REAL(8) :: result
  END SUBROUTINE 

Are the characteristics of the first argument the same?  No - one is CLASS(tBase) and one is CLASS(tBaseExt).  While these may be type compatible in one direction, they are not "the same", and therefore this is not allowed.  The compiler makes the correct call when the pointer assignment is done directly, but misses it when checking the procedure arguments.  I will let the developers know about that. Issue ID is DPD200235421.

What is "slow" about the second method is the need to figure out the SELECT TYPE in procedure Print - this generates an awful lot of code whereas PrintExt is just using the declared type and moves the value directly. Maybe this can be improved - I will ask.

View solution in original post

0 Kudos
3 Replies
Steven_L_Intel1
Employee
271 Views
Thomas,

Interesting questions.  I had to spend some time with the program and the standard to decide on how to respond.

First, the second commented-out line has two errors: There is no component MyCmpnt in type tProcPtrTest, it should be MyClass, and baseExt needs the TARGET attribute in order to be allowed as the target of a pointer assignment.  Neither of these are germane to your questions.

I believe that your first method is not standard-conforming and that the compiler should give an error for the procedure call, but as is often the case, one has to chase around the standard to see why.

12.5.2.9 (Actual arguments associated with dummy procedure entities) says:

"5 If a dummy argument is a procedure pointer [which in this case it is], the corresponding actual argument shall be a procedure pointer, a reference to the intrinsic function NULL, or a valid target for the dummy pointer in a pointer assignment statement."

It's this last clause that applies, so let's find the rule for that.  This would be 7.2.2.4 (Procedure pointer assignment):

"3 If the pointer object has an explicit interface [it does], its characteristics shall be the same as the pointer target ... [rest does not apply]"

So are the characteristics of Proc (the procedure pointer dummy argument) and PrintExt (the procedure target) the same?  Back to chapter 12, 12.3.1 (Characteristics of procedures):

"1 The characteristics of a procedure are the classification of the procedure as a function or subroutine, whether it is pure, whether it is elemental, whether it has the BIND attribute, the characteristics of its dummy arguments, and the characteristics of its result value if it is a function."

The only item in question here is the characteristics of the dummy arguments.  So let's see:

Proc (the procedure dummy argument) is declared using the abstract interface Iget, which is:

SUBROUTINE IGet(base, result)
    CLASS (tBase) :: base
    REAL(8) :: result
  END SUBROUTINE 

PrintExt is declared as follows:

SUBROUTINE PrintExt(BaseExt, result)
    CLASS (tBaseExt) BaseExt
    REAL(8) :: result
  END SUBROUTINE 

Are the characteristics of the first argument the same?  No - one is CLASS(tBase) and one is CLASS(tBaseExt).  While these may be type compatible in one direction, they are not "the same", and therefore this is not allowed.  The compiler makes the correct call when the pointer assignment is done directly, but misses it when checking the procedure arguments.  I will let the developers know about that. Issue ID is DPD200235421.

What is "slow" about the second method is the need to figure out the SELECT TYPE in procedure Print - this generates an awful lot of code whereas PrintExt is just using the declared type and moves the value directly. Maybe this can be improved - I will ask.
0 Kudos
thomas_boehme
New Contributor II
270 Views
Hi Steve,

thanks a lot for this really detailed explanation. I agree with your conclusion, that the use in not standard compliant and there should be at least a warning from the compiler.

I also agree with you, that the select type construct seems to create a lot of code and I really hope that this can be improved in the future. In our current code base, we are not using select type anymore in inner loops due to the current overhead. Of course, I am aware that there will always be some overhead when using the OO-features, but I hope that there is still room for improvement.

Best regards,
Thomas


0 Kudos
Steven_L_Intel1
Employee
270 Views

I expect this to be fixed in the 15.0 release later this year.

0 Kudos
Reply