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

Question on procedure pointers (I think)

Gustavo_Colvero
Beginner
844 Views
Hi,

sorry for asking something related to the fortran language rather than to the
intel fortran compiler. My question is simple, though.

I'm trying to declare a procedure of the form

f(x) => g(x, k1, k2, k3...)

where k1, k2, etc, are parameters fixed for the moment.

I really don't know the name of what i'm trying to do, but, in words, what I
want is to declare a function f whose only argument is x but i want it to be
related to another function, g, having more arguments.

To be plenty specific, I'm trying to do something like

z1(x) = g(x, y=y1)

If this question is really impertinent can someone please tell me the name
of this kind of procedure so I can google for it?

I have some (perhaps little) familiarity with procedure pointers, what led me to think
the solution would come by this way, but I'm receiving some

"When the target is an expression it must deliver a pointer result"

compiling errors so I'm not sure anymore.

Thanks,
Gustavo
0 Kudos
5 Replies
Gustavo_Colvero
Beginner
844 Views
Well,

I managed to do it using type-bound procedures.

What I do now is to declare a class having k1, k2, etc as members
and a type-bound function (method).

I'm doing something like

type foo
double precision, pointer :: k1, k2, ...
contains
procedure, public :: fk => desired_function
end type

...

function desired_function(foo1,x)
implicit none
class(foo) :: foo1
double precision :: x, desired_fnction

desired_function = x + foo1%k1...

end function desired_function

...

program test
type(foo) :: foo1
double precision, target :: k1, k2...
double precision :: x, res

k1 = ...
k2 = ...
...

x = ...

res = foo1%fk(x)

end program


This is working so far.

What I still can't do is to make a procedure pointer point to the
method fk as

f => foo1%fk

The compiler always complain with

"error #8191: The procedure target must be a procedure or a procedure pointer."

Any ideas?

Thanks!
0 Kudos
John4
Valued Contributor I
844 Views

There's no such thing as "Fortran by C" (i.e., you cannot assume Fortran is just like C, but with a different syntax).

First, you may not need to use Fortran pointers for k1 and k2. If you want them to just store double precision values, declare them as such:

[fortran]real(DOUBLE) :: k1, k2[/fortran]
If you need a procedure pointer as a component of the derived type, you can declare it as:
[fortran]procedure(foofunction), pointer :: ptr => NULL()[/fortran]
If you need a type-bound procedure (which is different from a procedure pointer), you can declare it as:
[fortran]procedure :: fk => foofunction[/fortran]
And if you need a regular procedure pointer (not as a component of the derived type), you can declare it as:
[fortran]procedure(foofunction), pointer :: f => NULL()[/fortran]

The following code explains the differences a little bit:

[fortran]module mod1

    implicit none

    integer, parameter :: DOUBLE = KIND(1.D0)   !declare the desired precision in one place

    type, public :: foo
        real(DOUBLE) :: k1 = 1, k2 = 2      !you can declare default values for the components
        procedure(foofunction), pointer :: ptr => NULL()    !it's a pointer, so it should be initially null.
                                                            !this pointer can only point to procedures 
                                                            !similar to foofunction
    contains
        procedure :: fk => foofunction      !it's not a pointer, so NULL() is not allowed here
    end type

contains
    function foofunction(this,x) result(res)
      real(DOUBLE) :: res
      class(foo), intent(IN) :: this    !declaring intent for arguments is recommended
      real(DOUBLE), intent(IN) :: x
      res = x + this%k1 + this%k2
    end function

    function foofunction2(this,x) result(res)
      real(DOUBLE) :: res
      class(foo), intent(IN) :: this
      real(DOUBLE), intent(IN) :: x
      res = foofunction(this,x)
    end function
end module

program test

    use mod1

    implicit none

    type(foo), target :: foo1
    real(DOUBLE) :: x
    procedure(foofunction), pointer :: f => NULL()

    x = 3

    !invoke the type-bound procedure
    print '("res(foo1%fk) = ", g10.3)', foo1%fk(x)

    !make the procedure pointer component point to a foofunction
    foo1%ptr => foofunction

    !invoke the procedure pointer component
    print '("res(foo1%ptr) = ", g10.3)', foo1%ptr(x)

    !make the procedure pointer point to foo1%ptr
    f => foo1%ptr

    !invoke the procedure pointer
    print '("res(f => foo1%ptr) = ", g10.3)', f(foo1, x)

    !make the procedure pointer point to a foofunction-like procedure
    f => foofunction2

    !invoke the procedure pointer
    print '("res(foofunction2) = ", g10.3)', f(foo1, x)

end program[/fortran]

Notice that in order for f to point to foo1%ptr, foo1 must be declared as a target.

0 Kudos
Gustavo_Colvero
Beginner
844 Views
Thanks, John!

Using your code as an example, what I really want to do is
[fortran]f => foo1%fk[/fortran]
to make a call like
[bash]y = f(x)[/bash]

I want this, because I need to pass such a function as argument to another subroutine
expecting a function with prototype
[fortran]double f(double x)
[/fortran]

Is this something I can do?

As I can already see, this can't be done because fk hasn't any explicit interface.

Please correct me if I'm talking nonsense, but I think if the procedure bound to the
class being defined had an interface explicitly declared and if the "this" object
were passed implicitly, than this would be an easy task, right?

Thanks again.


PS: To all this make sense, suppose I'm coding a Legendre_Polynomial class
for the P_l(x) polynomials. Each polynomial will be an object of this class with
a fixed value of l, say 2, for instance. Next I want to integrate P_2(x) using a
subroutine available in a numeric library, which integrates functions f(x).
0 Kudos
John4
Valued Contributor I
844 Views

The type-bound procedure already has an explicit interface! The "fk =>" part was just the syntax for an alias.

If I understand correctly, what you want is a (C++-like) pointer to a static method. I guess that's not possible with type-bound procedures (since, as the name implies, they're always bound to a type). The Fortran 2008 standard changes the rules for pointer initialization, so in that case one might be able to emulate a static method through a procedure pointer component that has the nopass attribute (although I'm not completely sure it'll be possible).

In the code below, I show different ways of dealing with user supplied procedures ---maybe one of those will help you accomplish what you want.

[fortran]module mod1

    implicit none

    integer, parameter :: DOUBLE = KIND(1.D0)

    type, public :: foo
        real(DOUBLE) :: k1 = 1, k2 = 2
        procedure(fk), pointer :: ptr => NULL()
        procedure(someprototype), pointer, nopass :: ptr2f => NULL() !the nopass attribute implies 
                                                                     !that the derived type (i.e., the class()) 
                                                                     !will not be passed as (firs) argument
    contains
        procedure :: fk                     !the interface to the actual procedure is explicit.  
                                            !the compiler will enforce it by checking that the first
                                            !argument is of class(foo)
        procedure :: fk_alias => fk         !the name to the left of the "=>" is just an alias for 
                                            !the actual procedure
        procedure :: gk
        procedure, nopass :: hk
    end type

    abstract interface           !this is an interface to a non-existent procedure
        function someprototype(x) result(res)
import !this imports DOUBLE from the surrounding module real(DOUBLE) :: res real(DOUBLE), intent(INOUT) :: x end function end interface contains function fk(this, x) result(res) real(DOUBLE) :: res class(foo), intent(IN) :: this real(DOUBLE), intent(IN) :: x res = x + this%k1 + this%k2 end function function gk(this, x, f) result(res) real(DOUBLE) :: res class(foo), intent(INOUT) :: this real(DOUBLE), intent(IN) :: x procedure(someprototype) :: f !this procedure is supplied as an argument and must !correspond to the prototype real(DOUBLE) :: tmp this%ptr2f => f !point to the user-supplied procedure tmp = x res = this%ptr2f(tmp) !invoke the user-supplied procedure res = this%hk(x,f) !pass the procedure to another "method" res = this%hk(x,this%ptr2f) !pass the pointer to another "method" end function function hk(x, f) result(res) real(DOUBLE) :: res real(DOUBLE), intent(IN) :: x procedure(someprototype) :: f real(DOUBLE) :: tmp tmp = x res = f(tmp) end function !... end module [/fortran]

0 Kudos
Gustavo_Colvero
Beginner
844 Views
Thank you, very much, for the time you spent here, John.

There's a lot of information here.

This "import" statement is totally new for me. I guess I should
RTFM more carefully. This is the problem of trying to do things
in a hurry.


Cheers!


PS: plenty of OO is that performance-compromising? Because
I can't imagine the concept of a class having more use than in
the realm of computational Physics. I mean, we have classes of
equations, classes of systems, matrices, solvers, and so on...
And why should a simple concept as of that of a function pointer
be as new as of 2003! On the other hand, why can't cpp even
these days have a simple intrinsic inquiry function as fortran's
SIZE for arrays? Oh... the performance of fortran for numeric
computation and the flexibility of cpp... I would rest in peace :)
0 Kudos
Reply