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

'dynamic' user defined callback functions

andrew_4619
Honored Contributor III
755 Views

I am try to replicate some functionality from a C program and I don't quite understand how to do it in fortran. In pseudo code:

[fortran]! in the main aplication we have:
subroutine part_of_my_main_application()
use myModule
INTERFACE
SUBROUTINE fred()
IMPORT
END SUBROUTINE fred
END INTERFACE
call mymodulesubroutine_set_callback(fred)
!do other stuff
end subroutine part_of_my_main_application


subroutine fred() !also part of my main app
!do stuff
end subroutine fred
[/fortran]

In a routine within 'mymodule' I would like to call the subroutine that is defined by the last call to mymodulesubroutime_set_callback. Further, it would be nice if possible to be able to check if the call back has been set before try to do it. I guess setting a dummycallback in the modukle initialisation routine would be a workaround.

I am sure this is quite simple when you know the necessary syntax to set up mymodulesubroutine_set_callback and the caller routine for what is set! Help Please!
Andrew

0 Kudos
6 Replies
IanH
Honored Contributor III
755 Views

If I follow correctly, xxx_set_callback(...) takes a dummy procedure argument, then associates a procedure pointer that is perhaps a module variable with that argument.  Later that procedure is referenced through the pointer.  You can initialise the procedure pointer to NULL() and test its association status to test if it has been set.

[fortran]MODULE my_module
  IMPLICIT NONE
  ABSTRACT INTERFACE
    SUBROUTINE proc_intf()
    END SUBROUTINE proc_intf
  END INTERFACE
  PROCEDURE(proc_intf), POINTER :: proc_ptr => NULL()
CONTAINS
  SUBROUTINE set_callback(dummy_proc)
    PROCEDURE(proc_intf) :: dummy_proc
    proc_ptr => dummy_proc
  END SUBROUTINE set_callback
  SUBROUTINE call_me_later
    IF (ASSOCIATED(proc_ptr)) THEN
      CALL proc_ptr
    ELSE
      PRINT "('Call back not set')"
    END IF
  END SUBROUTINE call_me_later
END MODULE my_module[/fortran]

0 Kudos
andrew_4619
Honored Contributor III
755 Views

Fanstastic, that is exactly what the Doctor ordered, you are on my Christmas card list. It would have been 2 days of head scratching to work that one out! The working test sample is below. Just being greedy but is it possible to define a type in the module such that in console I could have something like:

type(set_callback_type), external :: billy

My test case is trivial but if billy had a ruck of parameters the interfaces in console would look a bit messy and it keeps my_module nicely out on the way never to be looked at again.

![fortran]
MODULE my_module
IMPLICIT NONE

ABSTRACT INTERFACE
SUBROUTINE proc_intf()
END SUBROUTINE proc_intf
END INTERFACE
PROCEDURE(proc_intf), POINTER :: proc_ptr => NULL()

CONTAINS
SUBROUTINE set_callback(dummy_proc)
PROCEDURE(proc_intf) :: dummy_proc
proc_ptr => dummy_proc
END SUBROUTINE set_callback
SUBROUTINE call_me_later
IF (ASSOCIATED(proc_ptr)) THEN
CALL proc_ptr
ELSE
PRINT "('Call back not set')"
END IF
END SUBROUTINE call_me_later
END MODULE my_module

program Console
use my_module
implicit none
INTERFACE
SUBROUTINE billy()
END SUBROUTINE billy
END INTERFACE
!external billy

call billy() !we have an hello world event (HWE)
call call_me_later() !not HWE as callback not set
call set_callback(billy) !set the callback
call call_me_later() !Magic we get a HWE :-)
stop
end program Console

subroutine billy()
print *, 'Hello World'
end subroutine ![/fortran]

0 Kudos
IanH
Honored Contributor III
755 Views

app4619 wrote:
...Just being greedy but is it possible to define a type in the module such that in console I could have something like:

type(set_callback_type), external :: billy

My test case is trivial but if billy had a ruck of parameters the interfaces in console would look a bit messy and it keeps my_module nicely out on the way never to be looked at again.

Not sure I quite follow what you want there.  Guessing perhaps wildly - in some cases it is more appropriate/useful to pass an object that represents a procedure call, than actually passing a procedure.  In that object you can have whatever components you desire that are then accessible inside the procedure itself, along with the "normal" arguments.  The procedure proper to call is then a binding of the object.  For example:

[fortran]MODULE mod_a
  IMPLICIT NONE
  PRIVATE
  TYPE, PUBLIC :: Parent
  CONTAINS
    PROCEDURE(proc_intf), DEFERRED :: Proc
  END TYPE Parent
  ABSTRACT INTERFACE
    SUBROUTINE proc_intf(obj, arg)
      IMPORT :: Parent
      CLASS(Parent), INTENT(IN) :: obj
      INTEGER, INTENT(IN) :: arg
    END SUBROUTINE proc_itf
  END INTERFACE
  CLASS(Parent), ALLOCATABLE :: saved_object
CONTAINS
  SUBROUTINE set_callback(obj)
    CLASS(Parent), INTENT(IN) :: obj
    ALLOCATE(saved_object, SOURCE=obj)
    ! One day in ifort (F2008) : saved_object = obj
  END SUBROUTINE set_callback
  SUBROUTINE call_me_later(arg)
    INTEGER, INTENT(IN) :: arg
    IF (ALLOCATED(saved_object)) THEN
      CALL saved_object%Proc(arg)
    ELSE
      PRINT "('Callback not set')"
    END IF
  END SUBROUTINE call_me_later
END MODULE mod_a

MODULE mod_b
  USE mod_a
  IMPLICIT NONE
  TYPE, EXTENDS(Parent) :: Child
    INTEGER :: other_params
    REAL :: more_params
  CONTAINS
    PROCEDURE :: Proc => child_Proc
  END TYPE Child
CONTAINS
  SUBROUTINE child_Proc(obj, arg)
    CLASS(Child), INTENT(IN) :: obj
    INTEGER, INTENT(IN) :: arg
    !****
    ! Stuff using arg, obj%other_params, obj%more_params, etc.
  END SUBROUTINE child_Proc
END MODULE mod_b

PROGRAM example
  USE mod_a
  USE mod_b
  IMPLICIT NONE
  TYPE(Child) :: obj
  obj = Child(OTHER_PARAMS=1, MORE_PARAMS=2.0)
  CALL set_callback(obj)
  !....
  CALL call_me_later(99)
END PROGRAM example[/fortran]

0 Kudos
andrew_4619
Honored Contributor III
755 Views

Thanks for the reply, I have just spent a few minutes looking at that and it will take some more thinking and some testing to get my head around it, your mind is clearly in another dimension on this subject! I don't think I could actually use a construct that complicated in real code because I like to keep things simple, if I can't easily see what is happening it can only lead to headache in the future....

 Having said that there is an intellectual challange that will have to be explored and perhaps my initial thoughts will be revised?

Thanks again :-)

0 Kudos
IanH
Honored Contributor III
755 Views

Fortran's verbosity might obscure things a little - but as an object oriented programming concept it is pretty typical - perhaps even ubiquitous.  The Parent type defines the interface that client code (stuff in mod_b) needs to have (in this case those requirements are simple and hence we might be into sledgehammer-to-crack-a-nut-zone here - the type defined by the client code must have a binding called Proc that has the interface of proc_intf).  In Fortran (and some other languages) type extension is the mechanism that client code uses to say "objects of this client type will meet the requirements of the parent type". 

Thinking about it, another, far simpler approach is to wrap everything that `call_me_later` doesn't need to specifically know about in an unlimited polymorphic argument.  The callback procedure presumably has some idea of what it will be called with, so it can SELECT TYPE the argument appropriately.

0 Kudos
andrew_4619
Honored Contributor III
755 Views

Thanks, I will have to study this one again when I have a moment. :-)

0 Kudos
Reply