模块和程序#
模块是创建现代 Fortran 库和应用程序的首选方式。按照惯例,一个源文件始终应只包含一个模块,而模块名称应与文件路径匹配,以便在大型项目中轻松导航。还建议在模块名称前添加库名称前缀,以避免在用作其他项目的依赖项时发生名称冲突。
此类模块文件的示例如下所示
!> Interface to TOML processing library.
!>
!> ...
module fpm_toml
use fpm_error, only : error_t, fatal_error, file_not_found_error
use fpm_strings, only : string_t
use tomlf, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
& set_value, toml_parse, toml_error, new_table, add_table, add_array, &
& toml_serializer, len
implicit none
private
public :: read_package_file
public :: toml_table, toml_array, toml_key, toml_stat, get_value, set_value
public :: new_table, add_table, add_array, len
public :: toml_error, toml_serializer, toml_parse
contains
!> Process the configuration file to a TOML data structure
subroutine read_package_file(table, manifest, error)
!> TOML data structure
type(toml_table), allocatable, intent(out) :: table
!> Name of the package configuration file
character(len=*), intent(in) :: manifest
!> Error status of the operation
type(error_t), allocatable, intent(out) :: error
! ...
end subroutine read_package_file
end module fpm_toml
此示例模块中有一些需要强调的内容。首先,每个模块都以注释开头,记录模块的目的和内容。类似地,每个过程都以注释开头,简要描述其目的和虚拟参数的意图。无论使用何种语言,文档都是创建长期存在软件的最重要部分之一。
其次,显式给出导入(use)和导出(public),这允许在查看模块源代码时,快速检查使用的和可用的过程、常量和派生类型。导入通常限于模块范围,而不是在每个过程或接口范围内重新导入。类似地,通过在单行上添加private语句并在public语句中显式列出所有导出的符号来显式导出。
最后,implicit none
语句适用于整个模块,无需在每个过程中重复。
模块内的变量是静态的(隐式保存)。强烈建议将模块变量的使用限制在常量表达式(例如参数或枚举器)上,或者将其导出为受保护而不是公共。
子模块可用于打破长的依赖关系链并缩短 Fortran 程序中的重新编译级联。它们还提供了提供专门和优化的实现的可能性,而无需使用预处理器。
Fortran 标准库中的一个示例是求积模块,它只定义了对模块过程的接口,而不是实现
!> Numerical integration
!>
!> ...
module stdlib_quadrature
use stdlib_kinds, only: sp, dp, qp
implicit none
private
public :: trapz
! ...
!> Integrates sampled values using trapezoidal rule
interface trapz
pure module function trapz_dx_dp(y, dx) result(integral)
real(dp), intent(in) :: y(:)
real(dp), intent(in) :: dx
real(dp) :: integral
end function trapz_dx_dp
module function trapz_x_dp(y, x) result(integral)
real(dp), intent(in) :: y(:)
real(dp), intent(in) :: x(:)
real(dp) :: integral
end function trapz_x_dp
end interface trapz
! ...
end module stdlib_quadrature
虽然实现是在单独的子模块中提供的,例如此处给出的梯形积分规则。
!> Actual implementation of the trapezoidal integration rule
!>
!> ...
submodule (stdlib_quadrature) stdlib_quadrature_trapz
use stdlib_error, only: check
implicit none
contains
pure module function trapz_dx_dp(y, dx) result(integral)
real(dp), intent(in) :: y(:)
real(dp), intent(in) :: dx
real(dp) :: integral
integer :: n
n = size(y)
select case (n)
case (0:1)
integral = 0.0_dp
case (2)
integral = 0.5_dp*dx*(y(1) + y(2))
case default
integral = dx*(sum(y(2:n-1)) + 0.5_dp*(y(1) + y(n)))
end select
end function trapz_dx_dp
! ...
end submodule stdlib_quadrature_trapz
请注意,模块过程不必在同一个子模块中实现。可以使用多个子模块来减少大型模块的编译负载。
最后,在设置程序时,建议将程序主体中的实际实现降到最低。重用模块中的实现允许您编写可重用代码,并将程序单元重点放在将用户输入传递到相应的库函数和对象上。