@aerosayan , you may want to keep “Modern Fortran Explained” handy as that can provide a ready handbook reference with a fair amount of prose to provide the background on the semantics and syntax of the ISO IEC language standard for Fortran which online forum comments cannot quite provide.
With that in mind, you can review this example:
module solver_m
abstract interface
function Ifunc( x ) result(r)
! Argument list
real, intent(in) :: x
! Function result
real :: r
end function
end interface
contains
subroutine eval( x, func )
! Argument list
real, intent(in) :: x
procedure(Ifunc) :: func
print *, "In eval: f(x) = ", func(x)
end subroutine
end module
module calc_m
use solver_m, only : eval
contains
subroutine sub( x )
! Argument list
real, intent(in) :: x
call eval( x, myfunc ) !<-- NOTE: `myfunc` as procedure argument
contains
function myfunc( x ) result(r)
! Argument list
real, intent(in) :: x
! Function result
real :: r
real, parameter :: a = 1.0, b = 2.0, c = 1.0
r = a*x**2 + b*x + c
end function
end subroutine
end module
use calc_m, only : sub
call sub( x=99.0 )
end
- The response you can expect by a processor as confirmed by
gfortran
on Windows is as follows:
C:\temp>gfortran -ffree-form p.f -o p.exe
C:\temp>p.exe
In eval: f(x) = 10000.0000
Now, note my strong recommendation to Fortranners will be to strive for IMPORT, NONE
if they decide to pursue such internal subprograms. However, the gfortran
users will have to become developers or support development to enhance the GCC/gfortran to support this Fortran 2018 feature.
..
contains
function myfunc( x ) result(r)
import, none
! Argument list
real, intent(in) :: x
..
- response using Intel Fortran:
C:\temp>ifort /free /standard-semantics p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.10.0 Build 20230609_000000
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation. All rights reserved.
-out:p.exe
-subsystem:console
p.obj
C:\temp>p.exe
In eval: f(x) = 10000.00
C:\temp>ifx /free /standard-semantics p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023.2.0 Build 20230627
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation. All rights reserved.
-out:p.exe
-subsystem:console
p.obj
C:\temp>p.exe
In eval: f(x) = 10000.00