I’m trying to build some simple numerical functions as a way of getting used to Fortran, and I’m starting with derivatives. I want to write a function that returns me the Jacobian of any function that I pass, independent of the number of inputs and outputs. I’ve built the following module:
module solvers
use kinds, only: wp => dp
implicit none
abstract interface
function func(x) result (y)
! y = f(x), scalar function
import :: wp
real(wp), intent(in) :: x
real(wp) :: y
end function func
function func2(x) result (y)
! function with arbitrary number of inputs and outputs
! y(1) = f(x1, x2, ...), y(2) = g(x1, x2, ...), etc...
import :: wp
real(wp), intent(in), dimension(:) :: x
real(wp), dimension(:) :: y
end function func2
end interface
contains
function diff(x, F, opt_h, opt_method) result (J)
procedure(func1) :: F
! code to calculate derivatives...
end function diff
This code doesn’t compile because of func2 with the error: Error: Array 'y' at (1) cannot have a deferred shape
. It does compile if I declare y as allocatable on the abstract interface. But then, all functions that I pass to the function diff need to have an allocatable output, otherwise i get the error Error: Interface mismatch in dummy procedure 'f' at (1): ALLOCATABLE attribute mismatch in function result
.
Ideally I’d like my generic diff function to work with whatever function I pass to it, regardless if its result is allocatable or not. Is this possible?
Additionally, I’m defining the diff function like this:
function diff(x, F, opt_h, opt_method) result(J)
real(wp), intent(in), dimension(:) :: x
real(wp), intent(in), optional :: opt_h
procedure(func2) :: F
character(len=20), optional :: opt_method
real(wp) :: h
real(wp), allocatable, dimension(:) :: F_x
integer :: i, n_vars, n_funcs
character(len=20) :: method
real, allocatable, dimension(:,:) :: J
n_vars = size(x)
F_x = F(x)
n_funcs = size(F_x)
! code to calculate derivatives...
end function diff
Basically, I’m calling F to find out the size of the array F returns. This works in this situation, but is there any way of evaluating the size of a function return array without the function call?
Thanks in advance!