回调函数中的类型转换#
基本上有五种不同的类型转换方法,每种方法都有其自身的优缺点。
方法 I、II 和 V 可用于 C 和 Fortran。方法 III 和 IV 仅在 Fortran 中可用。方法 VI 已过时,不应使用。
工作数组#
传递一个“工作数组”,其中包含调用方所需的所有内容,并由被调用例程解包。这是旧方法,例如 LAPACK 的使用方法。
积分器
module integrals
use types, only: dp
implicit none
private
public simpson
contains
real(dp) function simpson(f, a, b, data) result(s)
real(dp), intent(in) :: a, b
interface
real(dp) function func(x, data)
use types, only: dp
implicit none
real(dp), intent(in) :: x
real(dp), intent(inout) :: data(:)
end function
end interface
procedure(func) :: f
real(dp), intent(inout) :: data(:)
s = (b-a) / 6 * (f(a, data) + 4*f((a+b)/2, data) + f(b, data))
end function
end module
用法
module test
use types, only: dp
use integrals, only: simpson
implicit none
private
public foo
contains
real(dp) function f(x, data) result(y)
real(dp), intent(in) :: x
real(dp), intent(inout) :: data(:)
real(dp) :: a, k
a = data(1)
k = data(2)
y = a*sin(k*x)
end function
subroutine foo(a, k)
real(dp) :: a, k
real(dp) :: data(2)
data(1) = a
data(2) = k
print *, simpson(f, 0._dp, pi, data)
print *, simpson(f, 0._dp, 2*pi, data)
end subroutine
end module
通用结构#
定义一个包含您实际需要(或将来可能需要)的变体的通用结构。然后,如果需要,可以在将来需要/想法允许的情况下更改此单个结构类型,但可能不需要从传递实数更改为文本编辑器的实例化。
积分器
module integrals
use types, only: dp
implicit none
private
public simpson, context
type context
! This would be adjusted according to the problem to be solved.
! For example:
real(dp) :: a, b, c, d
integer :: i, j, k, l
real(dp), pointer :: x(:), y(:)
integer, pointer :: z(:)
end type
contains
real(dp) function simpson(f, a, b, data) result(s)
real(dp), intent(in) :: a, b
interface
real(dp) function func(x, data)
use types, only: dp
implicit none
real(dp), intent(in) :: x
type(context), intent(inout) :: data
end function
end interface
procedure(func) :: f
type(context), intent(inout) :: data
s = (b-a) / 6 * (f(a, data) + 4*f((a+b)/2, data) + f(b, data))
end function
end module
用法
module test
use types, only: dp
use integrals, only: simpson, context
implicit none
private
public foo
contains
real(dp) function f(x, data) result(y)
real(dp), intent(in) :: x
type(context), intent(inout) :: data
real(dp) :: a, k
a = data%a
k = data%b
y = a*sin(k*x)
end function
subroutine foo(a, k)
real(dp) :: a, k
type(context) :: data
data%a = a
data%b = k
print *, simpson(f, 0._dp, pi, data)
print *, simpson(f, 0._dp, 2*pi, data)
end subroutine
end module
实际上只需要有限的灵活性。例如,您可以为此目的定义两种结构类型,一种用于薛定谔,一种用于狄拉克。然后,每种类型都将足够通用,并包含所有必需的部分以及所有正确的标签。
重点是:它不必是“一个包含所有内容的抽象类型”或失败。在“所有”和“无”之间存在自然且可行的选择。
私有模块变量#
通过传入模块变量完全隐藏变量参数。
积分器
module integrals
use types, only: dp
implicit none
private
public simpson
contains
real(dp) function simpson(f, a, b) result(s)
real(dp), intent(in) :: a, b
interface
real(dp) function func(x)
use types, only: dp
implicit none
real(dp), intent(in) :: x
end function
end interface
procedure(func) :: f
s = (b-a) / 6 * (f(a) + 4*f((a+b)/2) + f(b))
end function
end module
用法
module test
use types, only: dp
use integrals, only: simpson
implicit none
private
public foo
real(dp) :: global_a, global_k
contains
real(dp) function f(x) result(y)
real(dp), intent(in) :: x
y = global_a*sin(global_k*x)
end function
subroutine foo(a, k)
real(dp) :: a, k
global_a = a
global_k = k
print *, simpson(f, 0._dp, pi)
print *, simpson(f, 0._dp, 2*pi)
end subroutine
end module
但是,如果可能,最好避免使用此类全局变量,即使它们实际上只是半全局变量。但有时它可能是最简单最干净的方法。但是,经过一番思考,通常会有更好的、更安全、更明确的方法,例如 II 或 IV。
嵌套函数#
积分器
module integrals
use types, only: dp
implicit none
private
public simpson
contains
real(dp) function simpson(f, a, b) result(s)
real(dp), intent(in) :: a, b
interface
real(dp) function func(x)
use types, only: dp
implicit none
real(dp), intent(in) :: x
end function
end interface
procedure(func) :: f
s = (b-a) / 6 * (f(a) + 4*f((a+b)/2) + f(b))
end function
end module
用法
subroutine foo(a, k)
use integrals, only: simpson
real(dp) :: a, k
print *, simpson(f, 0._dp, pi)
print *, simpson(f, 0._dp, 2*pi)
contains
real(dp) function f(x) result(y)
real(dp), intent(in) :: x
y = a*sin(k*x)
end function f
end subroutine foo
使用 type(c_ptr) 指针#
在 C 中,将使用 void *
指针。在 Fortran 中,可以将 type(c_ptr)
用于完全相同的目的。
积分器
module integrals
use types, only: dp
use iso_c_binding, only: c_ptr
implicit none
private
public simpson
contains
real(dp) function simpson(f, a, b, data) result(s)
real(dp), intent(in) :: a, b
interface
real(dp) function func(x, data)
use types, only: dp
implicit none
real(dp), intent(in) :: x
type(c_ptr), intent(in) :: data
end function
end interface
procedure(func) :: f
type(c_ptr), intent(in) :: data
s = (b-a) / 6 * (f(a, data) + 4*f((a+b)/2, data) + f(b, data))
end function
end module
用法
module test
use types, only: dp
use integrals, only: simpson
use iso_c_binding, only: c_ptr, c_loc, c_f_pointer
implicit none
private
public foo
type f_data
! Only contains data that we need for our particular callback.
real(dp) :: a, k
end type
contains
real(dp) function f(x, data) result(y)
real(dp), intent(in) :: x
type(c_ptr), intent(in) :: data
type(f_data), pointer :: d
call c_f_pointer(data, d)
y = d%a * sin(d%k * x)
end function
subroutine foo(a, k)
real(dp) :: a, k
type(f_data), target :: data
data%a = a
data%k = k
print *, simpson(f, 0._dp, pi, c_loc(data))
print *, simpson(f, 0._dp, 2*pi, c_loc(data))
end subroutine
end module
与往常一样,随着这种重新转换的优势,因为 Fortran 允许您在确实需要时这样做,也带来了编译时和运行时检查能够捕获错误的可能性更少;随之而来的是,不可避免地会出现更多漏洞、容易出错的代码。因此,人们总是必须权衡成本和收益。
通常,在科学编程的背景下,其主要目标是表示和解决精确的数学公式(而不是创建具有无数按钮、下拉菜单和其他界面元素的 GUI),最简单、最不容易出错且最快的使用先前方法之一。
transfer() 内在函数#
在 Fortran 2003 之前,执行类型转换的唯一方法是使用 transfer
内在函数。它在功能上等效于方法 V,但更冗长且更容易出错。它现在已过时,应该使用方法 V 代替。
示例
http://jblevins.org/log/transfer
http://jblevins.org/research/generic-list.pdf
http://www.macresearch.org/advanced_fortran_90_callbacks_with_the_transfer_function
面向对象方法#
模块
module integrals
use types, only: dp
implicit none
private
public :: integrand, simpson
! User extends this type
type, abstract :: integrand
contains
procedure(func), deferred :: eval
end type
abstract interface
function func(this, x) result(fx)
import :: integrand, dp
class(integrand) :: this
real(dp), intent(in) :: x
real(dp) :: fx
end function
end interface
contains
real(dp) function simpson(f, a, b) result(s)
class(integrand) :: f
real(dp), intent(in) :: a, b
s = ((b-a)/6) * (f%eval(a) + 4*f%eval((a+b)/2) + f%eval(b))
end function
end module
抽象类型准确规定了集成例程需要什么,即评估函数的方法,但对用户没有强加其他任何限制。用户扩展此类型,提供 eval 类型绑定过程的具体实现,并将必要上下文数据作为扩展类型的组件添加。
用法
module example_usage
use types, only: dp
use integrals, only: integrand, simpson
implicit none
private
public :: foo
type, extends(integrand) :: my_integrand
real(dp) :: a, k
contains
procedure :: eval => f
end type
contains
function f(this, x) result(fx)
class(my_integrand) :: this
real(dp), intent(in) :: x
real(dp) :: fx
fx = this%a*sin(this%k*x)
end function
subroutine foo(a, k)
real(dp) :: a, k
type(my_integrand) :: my_f
my_f%a = a
my_f%k = k
print *, simpson(my_f, 0.0_dp, 1.0_dp)
print *, simpson(my_f, 0.0_dp, 2.0_dp)
end subroutine
end module
void * 与 type(c_ptr) 和 transfer() 的完整示例#
以下有三段等效代码:一段使用 void *
的 C 代码和两段使用 type(c_ptr)
和 transfer()
的 Fortran 代码
语言 |
方法 |
链接 |
---|---|---|
C |
|
|
Fortran |
|
|
Fortran |
|
C 代码使用标准 C 方法编写接受回调和上下文的可扩展库。两段 Fortran 代码展示了如何执行相同的操作。type(c_ptr)
方法等效于 C 版本,这应该是使用的方法。
此处仅为了完整性而提供 transfer()
方法(在 Fortran 2003 之前,它是唯一的方法),它有点繁琐,因为用户需要为其每种类型创建辅助转换函数。因此,应改用 type(c_ptr)
方法。