Silverfrost Forums

Welcome to our forums

Subroutines as optional arguments

15 May 2012 10:10 #10154

I am trying to pass the name of a subroutine as an argument to a function, but cannot work out how to avoid a compilation error. I can pass a function as an optional argument, but not a subroutine. In the following code, module m0 defines a function and a subroutine. Modules m1 and m2 then define functions that take an optional function and subroutine, respectively, as arguments. The compiler complains at the definition of s as external, but if s is not optional (and the test for whether s is present is removed) then the program compiles.

Any assistance on what I need to do to get this to work would be greatly appreciated.

MODULE m0
CONTAINS
 FUNCTION f ()
  INTEGER :: f
  f=1
  RETURN
 END FUNCTION f
 SUBROUTINE s ()
  CONTINUE
  RETURN
 END SUBROUTINE s
END MODULE m0

MODULE m1
CONTAINS
 FUNCTION f1(f)
  INTEGER, EXTERNAL, OPTIONAL :: f
  IF (PRESENT(f)) THEN
    f1=f()
  ELSE
    f1=0
  END IF
  RETURN
 END FUNCTION f1
END MODULE m1

MODULE m2
CONTAINS
 FUNCTION f2(s)
  EXTERNAL, OPTIONAL :: s
  IF (PRESENT(s)) THEN
    CALL s ()
    f2=1
  ELSE
    f2=0
  END IF
  RETURN
 END FUNCTION f2
END MODULE m2

PROGRAM p
  USE m0
  USE m1
  USE m2
  i=f1(f)
  i=f2(s)
END PROGRAM p
15 May 2012 5:31 #10161

This compiles for me. Write the optional and external declarations as [u:fdcdc237bf]two[/u:fdcdc237bf] statements. You can either use external or provide an interface for the subroutine. With the interface block method, the compiler can check if your actual subroutine argument has the correct interface. Also the interface method must be used if aaa and proc are both PURE (I think.)

module foo
contains

   function aaa(a, proc)
      real, intent(in) :: a
      optional :: proc
      external :: proc

      ! Or delete external and enable the following interface block      

      !interface
      !   subroutine proc(a)
      !   real, intent(in) :: a
      !   end subroutine proc
      !end interface
   
      ! Make call if proc supplied
      if (present(proc)) then
         call proc(a)
      end if
      
      aaa = 0.0
      
   end function aaa   

end module foo
17 May 2012 1:45 #10174

Can you wrap the subroutine into a function, as with many of the API functions ? You may still have a problem with the general argument list.

Thinking of a wrapper function, why are all the zzz@ functions written in C and require a C_EXTERNAL definition. Could they have been written in Fortran and contained the C_EXTERNAL definition when calling the WINAPI routine.

Or is it only a direct call to the WINAPI routine, providing a syntax conversion ? eg: C_EXTERNAL UPDATE_WINDOW@ '__update_window' (VAL)

WINDOW_UPDATE# appears in the .map file, but not __update_window

John

Please login to reply.