派生类型#

正如前面在 变量 中所讨论的,Fortran 中有五种内置数据类型。 派生类型 是一种特殊形式的数据类型,可以封装其它内置类型以及其它派生类型。它可以被认为等同于 C 和 C++ 编程语言中的 struct

快速了解派生类型#

这是一个基本派生类型的示例:

type :: t_pair
  integer :: i
  real :: x
end type

创建类型为 t_pair 的变量并访问其成员的语法是:

! Declare
type(t_pair) :: pair
! Initialize
pair%i = 1
pair%x = 0.5

百分比符号 % 用于访问派生类型的成员。

在上面的代码片段中,我们声明了一个派生类型的实例并显式初始化了它的成员。你还可以通过调用派生类型构造函数来初始化派生类型成员。

使用派生类型构造函数的示例:

pair = t_pair(1, 0.5)      ! Initialize with positional arguments
pair = t_pair(i=1, x=0.5)  ! Initialize with keyword arguments
pair = t_pair(x=0.5, i=1)  ! Keyword arguments can go in any order

默认初始化示例:

type :: t_pair
  integer :: i = 1
  real :: x = 0.5
end type

type(t_pair) :: pair
pair = t_pair()       ! pair%i is 1, pair%x is 0.5
pair = t_pair(i=2)    ! pair%i is 2, pair%x is 0.5
pair = t_pair(x=2.7)  ! pair%i is 1, pair%x is 2.7

派生类型详解#

具有所有可选属性的派生类型的完整语法如下所示:

type [,attribute-list] :: name [(parameterized-declaration-list)]
  [parameterized-definition-statements]
  [private statement or sequence statement]
  [member-variables]
contains
  [type-bound-procedures]
end type

声明派生类型的选项#

attribute-list 可能指的是以下内容:

  • 访问类型公共私有

  • bind(c) 提供与 C 编程语言的互操作性

  • extends(parent),其中_parent_是先前声明的派生类型的名称,当前派生类型将继承其所有成员和功能

  • abstract —— 一个面向对象的特征,在高级编程教程中涉及到

如果使用属性 bind(c) 或语句 sequence,那么派生类型不能有属性 extends,反之亦然。

sequence 属性仅可用于声明以下成员应按照它们在派生类型中定义的相同顺序被访问。

使用 sequence 的例子:

type :: t_pair
  sequence
  integer :: i
  real :: x
end type
! Initialize
type(t_pair) :: pair
pair = t_pair(1, 0.5)

使用语句 sequence 的前提是下面定义的数据类型既不是 allocatable 也不是 pointer 类型。 此外,它并不意味着这些数据类型将以任何特定的形式存储在内存中,也就是说,与 contiguous 属性没有关系。

如果使用 访问类型 属性 publicprivate,则声明所有在下面声明的成员变量将被自动分配相应的属性。

属性bind(c)是用来实现 Fortran 的派生类型和 C 的结构体之间的兼容性。

使用 bind(c) 的例子:

module f_to_c
  use iso_c_bindings, only: c_int
  implicit none

  type, bind(c) :: f_type
    integer(c_int) :: i
  end type

end module f_to_c

匹配以下 C 结构体类型:

struct c_struct {
  int i;
};

一个具有 bind(c) 属性的 Fortran 派生类型不能具有 sequenceextends 属性。 此外,它不能包含任何 Fortran pointerallocatable 类型。

parameterized-declaration-list 是一个可选的特性。 如果使用,那么参数必须列在 [parameterized-definition-statements] 的位置上,并且必须是 lenkind 参数,或者两者都是。

具有 parameterized-declaration-listpublic 属性的派生类型的例子:

module m_matrix
 implicit none
 private

 type, public :: t_matrix(rows, cols, k)
   integer, len :: rows, cols
   integer, kind :: k = kind(0.0)
   real(kind=k), dimension(rows, cols) :: values
 end type

end module m_matrix

program test_matrix
 use m_matrix
 implicit none

 type(t_matrix(rows=5, cols=5)) :: m

end program test_matrix

在这个例子中,参数 k 已经被分配了一个默认值 kind(0.0)(单精度浮点)。 因此,它可以被省略,就像这里的主程序内部声明一样。

默认情况下,派生类型和它们的成员是公共的。 然而,在这个例子中,属性 private 被用在模块的开头。 因此,除非明确声明为 public,否则模块内的一切都将默认为 private。 如果在上面的例子中,t_matrix 类型没有被赋予 public 属性,那么编译器会在 program test 中抛出一个错误。

F2003 标准中增加了 extends 属性,它引入了面向对象范式(OOP)的一个重要特征,即继承。 它通过让子类型从可扩展的父类型派生出来,实现了代码的可重用性。 type, extends(parent) :: child。 这里,child 继承了 type :: parent 的所有成员和功能。

有属性 extends 的例子:

module m_employee
  implicit none
  private
  public t_date, t_address, t_person, t_employee
  ! Note another way of using the public attribute:
  ! gathering all public data types in one place.

  type :: t_date
    integer :: year, month, day
  end type

  type :: t_address
    character(len=:), allocatable :: city, road_name
    integer :: house_number
  end type

  type, extends(t_address) :: t_person
    character(len=:), allocatable :: first_name, last_name, e_mail
  end type

  type, extends(t_person)  :: t_employee
    type(t_date) :: hired_date
    character(len=:), allocatable :: position
    real :: monthly_salary
  end type

end module m_employee

program test_employee
  use m_employee
  implicit none
  type(t_employee) :: employee

  ! Initialization

  ! t_employee has access to type(t_date) members not because of extends
  ! but because a type(t_date) was declared within t_employee.
  employee%hired_date%year  = 2020
  employee%hired_date%month = 1
  employee%hired_date%day   = 20

  ! t_employee has access to t_person, and inherits its members due to extends.
  employee%first_name = 'John'
  employee%last_name  = 'Doe'

  ! t_employee has access to t_address, because it inherits from t_person,
  ! which in return inherits from t_address.
  employee%city         = 'London'
  employee%road_name    = 'BigBen'
  employee%house_number = 1

  ! t_employee has access to its defined members.
  employee%position       = 'Intern'
  employee%monthly_salary = 0.0

end program test_employee

用于声明派生类型成员的选项#

[member-variables] 指的是所有成员数据类型的声明。 这些数据类型可以是任何内置的数据类型,和/或其它派生类型,正如在上述例子中已经展示的。 然而,成员变量可以有自己广泛的语法,其形式为:type [,member-attributes] :: name[attr-dependent-spec][init]

type:任何内置类型或其它派生类型

member-attributes(可选):

  • publicprivate 访问属性

  • protected 访问属性

  • 带有或不带有 dimensionallocatable 以指定动态数组

  • pointercodimensioncontiguousvolatileasynchronous

常见案例示例:

type :: t_example
  ! 1st case: simple built-in type with access attribute and [init]
  integer, private :: i = 0
  ! private hides it from use outside of the t_example's scope.
  ! The default initialization [=0] is the [init] part.

  ! 2nd case: protected
  integer, protected :: i
  ! In contrary to private, protected allows access to i assigned value outside of t_example
  ! but is not definable, i.e. a value may be assigned to i only within t_example.

  ! 3rd case: dynamic 1-D array
  real, allocatable, dimension(:) :: x
  ! the same as
  real, allocatable :: x(:)
  ! This parentheses' usage implies dimension(:) and is one of the possible [attr-dependent-spec].
end type

以下属性:pointercodimensioncontiguousvolatileasynchronous快速入门 教程中不会涉及的高级特性。然而,在这里展示它们,是为了让读者知道这些特征确实存在并能够识别它们。这些特性将在接下来的《高级编程》迷你书中详细介绍。

类型绑定过程#

派生类型可以包含_绑定_到它的函数或子例程。我们将它们称为_类型绑定过程_。类型绑定过程遵循 contains 语句,而该语句又遵循所有成员变量声明。

如果不深入研究现代 Fortran 的 OOP 特性,就不可能完整地描述类型绑定过程。现在我们将专注于一个简单的例子来展示它们的基本用法。

这是具有基本类型绑定过程的派生类型的示例:

module m_shapes
  implicit none
  private
  public t_square

  type :: t_square
  real :: side
  contains
    procedure :: area  ! procedure declaration
  end type

contains

  ! Procedure definition
  real function area(self) result(res)
    class(t_square), intent(in) :: self
    res = self%side**2
  end function

end module m_shapes

program main
  use m_shapes
  implicit none

  ! Variables' declaration
  type(t_square) :: sq
  real :: x, side

  ! Variables' initialization
  side = 0.5
  sq%side = side

  x = sq%area()
  ! self does not appear here, it has been passed implicitly

  ! Do stuff with x...

end program main

什么是新的:

  • self 是一个任意名称,我们选择它来表示类型绑定函数内的派生类型 t_square 的实例。这允许我们访问其成员并在调用类型绑定过程时自动将其作为参数传递。

  • 我们现在在 area 函数的接口中使用 class(t_square) 而不是 type(t_square)。这允许我们使用扩展 t_square 的任何派生类型调用 area 函数。关键字 class 引入了 OOP 特性多态性。

在上面的例子中,类型绑定过程 area 被定义为一个函数,并且只能在表达式中调用,例如 x = sq%area()print *, sq%area()。如果将其定义为子例程,则可以从其自己的 call 语句中调用它:

! Change within module
contains
  subroutine area(self, x)
    class(t_square), intent(in) :: self
    real, intent(out) :: x
    x = self%side**2
  end subroutine

! ...

! Change within main program
call sq%area(x)

! Do stuff with x...

与类型绑定函数的示例相比,我们现在有两个参数:

  • class(t_square), intent(in) :: self —— 派生类型本身的实例

  • real, intent(out) :: x —— 用于存储计算面积并返回给调用者