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

Procedure pointer as an argument to abstract subroutine

Jon_D
New Contributor I
860 Views

Hello,

Is it possible to have a procedure pointer as an argument for a subroutine declared within an abstract interface block? Below is the general idea behind my code:

 

MODULE MyMod
    
    TYPE,ABSTRACT MyType
    CONTAINS
       PROCEDURE(Abstract_Proc),PASS,DEFERRED :: Proc
    END TYPE MyType
    
CONTAINS

    ABSTRACT INTERFACE
       SUBROUTINE Abstract_Proc(MyData,pFunc)
         IMPORT :: MyType,Func
         CLASS(MyType),INTENT(IN)         :: MyData
         PROCEDURE(Func),OPTIONAL,POINTER :: pFunc
       END SUBROUTINE Abstract_Proc
    END INTERFACE
    
    
    SUBROUTINE Func(...)
      ....
    END SUBROUTINE Func
    
END MODULE MyMod

 Based on the example, compiler gives me the following error:

    error #8169: The specified interface is not declared. [FUNC]

 

Is there a way to get the compiler recognize Func as an explicit interface?

Thanks,

Jon

0 Kudos
13 Replies
FortranFan
Honored Contributor II
847 Views

@Jon_D ,

Yes, there is.  Though most readers who can help will likely need to see an actual reproducer to point out to you what to fix in the code you have now.

However you may also want to consider another approach that is more akin to "conventional wisdom" given the influence of C "family" of languages and which is to apply an abstract interface for your function pointer as well.  That wat you separate the implementation from the interface and the implementation can be "remote" (often an advantage in terms of module and/or IP management, etc.) and the compiler will raise diagnostics during procedure pointer assignment if there is an interface mismatch.  That is, you can take a look at something like this:

module m
   type, abstract :: t
   contains
      procedure(Iproc), pass, deferred :: proc
   end type t
   abstract interface
      function Ifunc() result(r)  !<-- an arbitrary function interface
         integer :: r
      end function 
      subroutine Iproc(mydata, pfunc)
         import :: t, Ifunc
         class(t),intent(in)                 :: mydata
         procedure(Ifunc), optional, pointer :: pfunc
      end subroutine
   end interface
end module m

 

0 Kudos
Steve_Lionel
Honored Contributor III
830 Views

I don't see why this shouldn't work. I corrected the syntax errors in your pseudocode, including moving the abstract interface to before the CONTAINS):

MODULE MyMod
    
    TYPE,ABSTRACT :: MyType
    CONTAINS
       PROCEDURE(Abstract_Proc),PASS,DEFERRED :: Proc
    END TYPE MyType

    ABSTRACT INTERFACE
       SUBROUTINE Abstract_Proc(MyData,pFunc)
         IMPORT :: MyType,Func
         CLASS(MyType),INTENT(IN)         :: MyData
         PROCEDURE(Func),OPTIONAL,POINTER :: pFunc
       END SUBROUTINE Abstract_Proc
    END INTERFACE
    
CONTAINS

    SUBROUTINE Func()
     ! ....
    END SUBROUTINE Func
    
END MODULE MyMod

Both ifort and nagfor complain that Func can't be imported because it doesn't exist. This... confuses me, and I am going to ask for clarification. I'd expect the name Func to be accessible in the module (it certainly would be in other module procedures, and one could name it in a PRIVATE statement.)

The following is accepted, however. I haven't expanded this to a complete example.

MODULE MyMod
    
    TYPE,ABSTRACT :: MyType
    CONTAINS
       PROCEDURE(Abstract_Proc),PASS,DEFERRED :: Proc
    END TYPE MyType

    ABSTRACT INTERFACE
       SUBROUTINE Func_INT()
       END SUBROUTINE FUNC_INT
       SUBROUTINE Abstract_Proc(MyData,pFunc)
         IMPORT :: MyType,Func_Int
         CLASS(MyType),INTENT(IN)         :: MyData
         PROCEDURE(Func_Int),OPTIONAL,POINTER :: pFunc
       END SUBROUTINE Abstract_Proc
    END INTERFACE
    
CONTAINS

    Subroutine Func()
     ! ....
    END SUBROUTINE Func
    
END MODULE MyMod

What I did here was create an abstract interface for a procedure that has the same interface as Func.

 

0 Kudos
FortranFan
Honored Contributor II
806 Views

It is surprising to find Intel Fortran and gfortran also raise errors when they process ok a variant below which is admittedly more straightforward in that there is no aspect of a forward reference coming into play:

module k
contains
   function func() result(r)
      integer :: r
      r = 0
   end function 
end module 
module m
   use k, only : func
   type, abstract :: t
   contains
      procedure(Iproc), pass, deferred :: proc
   end type t
   abstract interface
      subroutine Iproc(mydata, pfunc)
         import :: t, func
         class(t),intent(in)                :: mydata
         procedure(func), optional, pointer :: pfunc
      end subroutine
   end interface
end module m

Based on a quick glance at the standard, I didn't notice any restriction with the IMPORT of a host entity that is a module procedure.

 

Ostensibly 3 different compilers appear to have gotten the semantics wrong which I do find hard to believe but the standard  looks alright in this case.

0 Kudos
Steve_Lionel
Honored Contributor III
802 Views

Another observation - if I add PUBLIC:: FUNC to my first rewrite above, NAG accepts it but ifort doesn't (ifort doesn't complain about the PUBLIC, but the IMPORT.) Something very weird is happening here.

0 Kudos
Steve_Lionel
Honored Contributor III
785 Views

I asked Malcolm Cohen (NAG, world's best expert on the fine details of the language) about this. He pointed me to:

C8101 Within an interface body, an entity that is accessed by host association shall be accessible by host or use association within the host scoping unit, or explicitly declared prior to the interface body. (8.8 IMPORT statement)

He then commented, "i.e., what we usually term “previously declared”. This is how we prevent circular dependencies (and avoid requiring the processor to topologically sort declarations by their dependencies)."

I then went hunting for words that would support the appearance of Func in the PUBLIC statement as being a prior explicit declaration, and found 3.48 which defines "declaration" as "specification of attributes for various program entities", so I suppose that counts.

Given this, ifort should have accepted the version with the uncommented PUBLIC and I'll report that to Intel.

0 Kudos
Steve_Lionel
Honored Contributor III
784 Views

Regarding @FortranFan 's example, nagfor accepts this, as it should per C8101. As for ifort, it compiled without complaint for me, so I am not sure what FortranFan saw.

0 Kudos
FortranFan
Honored Contributor II
761 Views

@Steve_Lionel wrote:

Regarding @FortranFan 's example, nagfor accepts this, as it should per C8101. As for ifort, it compiled without complaint for me, so I am not sure what FortranFan saw.


Re: "not sure what FortranFan saw," here is my synopsis:

  • IFORT accepts the suggestion I made in my first reply on this thread i.e.,
module m
   type, abstract :: t
   contains
      procedure(Iproc), pass, deferred :: proc
   end type t
   abstract interface
      function Ifunc() result(r)  !<-- an arbitrary function interface
         integer :: r
      end function 
      subroutine Iproc(mydata, pfunc)
         import :: t, Ifunc
         class(t),intent(in)                 :: mydata
         procedure(Ifunc), optional, pointer :: pfunc
      end subroutine
   end interface
end module m
  • IFORT raises error #8169: "The specified interface is not declared. [FUNC]" message with the PROCEDURE declaration in the abstract interface when the trick with PUBLIC is attempted - see below.  This is the same as what was mentioned by @Steve_Lionel earlier.
module m
   type, abstract :: t
   contains
      procedure(Iproc), pass, deferred :: proc
   end type t
   public :: func !<-- this does not help with IFORT
   abstract interface
      subroutine Iproc(mydata, pfunc)
         import :: t, func
         class(t), intent(in)               :: mydata
         procedure(func), optional, pointer :: pfunc
      end subroutine
   end interface
contains
   function func() result(r)  !<-- an arbitrary function interface
      integer :: r
   end function 
end module m

 

0 Kudos
Steve_Lionel
Honored Contributor III
782 Views

I noted that, with the PUBLIC declaration, ifort complains about the PROCEDURE statement saying "The specified interface is not declared." It didn't complain about the IMPORT, which is good.

So, I chased down the PROCEDURE declaration statement and found:

C1515 (R1516) The name shall be the name of an abstract interface or of a procedure that has an explicit interface. If name is declared by a procedure-declaration-stmt it shall be previously declared. 

In this example, Func does have an explicit interface and is not declared by a procedure-declaration-stmt, so there is no requirement that it be previously declared.

0 Kudos
FortranFan
Honored Contributor II
759 Views

Another option that works with gfortran but not IFORT is to declare a dispensable object with the procedure pointer attribute that has the same interface as `func`:

module m
   type, abstract :: t
   contains
      procedure(Iproc), pass, deferred :: proc
   end type t
   procedure(func), pointer :: foo => null() !<-- This "trick" helps with gfortran, but not IFORT
   abstract interface
      subroutine Iproc(mydata, pfunc)
         import :: t, func
         class(t), intent(in)               :: mydata
         procedure(func), optional, pointer :: pfunc
      end subroutine
   end interface
contains
   function func() result(r)  !<-- an arbitrary function interface
      integer :: r
   end function 
end module m
0 Kudos
JohnNichols
Valued Contributor III
732 Views

IMHO

You are asking a lot of the poor compiler writers to get this correct the first time.  

The number of test combinations must be enormous.  

Case in point:

In 1972, A. SUDHAKAR, a brilliant young engineering programmer, who sadly died too young, invented ULARC.  

ULARC provided the starting code for a lot of more advanced, but less useful programs.  His program is simple and fast, but the follow-on programs are bloated and slow.  

One line has 17HMember,4HNode

Clearly, in error, a lot of people have looked at this output over many years, it was only on Friday I noticed that the 17H should be 7.  

Humans make errors.  

Thank the gods, that we have a large body of human nerds, who are able to test the stuff and have the place to report the errors.  

That is one of Fortran's gifts to the gods and Intel and NAG etc... 

Anyway, I enjoy the discussion.  

 

 

0 Kudos
JohnNichols
Valued Contributor III
728 Views

An example of our Father's code again:

 

EigenSolver and PARDISO SOLVER.
                      IMPLEMENTATION OF THE JACOBI EIGENVALUE-VECTOR PROGRAM BY
                      H. RUTISHAUSER, HANDBOOK FOR AUTOMATIC COMPUTING, VOL II,
                      SPRINGER-VERLAG, NEW YORK (1971) PP.202-211
                      WRITTEN 28 January 1975, BY PAUL S. JENSEN

 

0 Kudos
Steve_Lionel
Honored Contributor III
725 Views

@FortranFan , I misunderstood what you wrote, when you said, "It is surprising to find Intel Fortran and gfortran also raise errors when they process ok a variant below which is admittedly more straightforward in that there is no aspect of a forward reference coming into play:", getting confused by your saying both "raise errors" and "process ok". On a reread I think I understand now what you were getting at.

I have submitted a problem report to Intel on this matter.

0 Kudos
Steve_Lionel
Honored Contributor III
438 Views

This error was fixed in the 2023.0 release.

0 Kudos
Reply