派生类型#
如之前在变量中所述,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
可以指以下内容:
access-type,可以是
public
或private
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
属性无关。
如果使用access-type属性public
和private
,则声明下面声明的所有成员变量将自动相应地分配属性。
属性bind(c)
用于实现 Fortran 的派生类型和 C 的 struct 之间的兼容性。
带有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 类型
struct c_struct {
int i;
};
具有属性
bind(c)
的 Fortran 派生类型不能具有sequence
和extends
属性。此外,它不能包含任何 Fortranpointer
或allocatable
类型。
parameterized-declaration-list
是一个可选功能。如果使用,则参数必须列在[parameterized-definition-statements]
的位置,并且必须是len
或kind
参数,或两者兼而有之。
具有parameterized-declaration-list
和属性public
的派生类型的示例
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
用于模块的开头。因此,模块中的所有内容默认情况下都将是private
,除非显式声明为public
。如果类型t_matrix
在上例中未被赋予属性public
,则编译器将在program test
内部抛出错误。
属性extends
是在 F2003 标准中添加的,它引入了面向对象范式 (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
(可选)
public
或private
访问属性protected
访问属性allocatable
带或不带dimension
来指定动态数组pointer
、codimension
、contiguous
、volatile
、asynchronous
常见案例示例
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
以下属性:
pointer
、codimension
、contiguous
、volatile
、asynchronous
是高级特性,在本《快速入门》教程中不会介绍。但是,这里列出它们是为了让读者知道这些特性确实存在,并能够识别它们。这些特性将在即将推出的《高级编程》小册子中详细介绍。
类型绑定过程#
派生类型可以包含与其**绑定**的函数或子程序。我们将它们称为**类型绑定过程**。类型绑定过程遵循contains
语句,该语句依次遵循所有成员变量声明。
在不深入探讨现代 Fortran 的面向对象特性的情况下,不可能完整地描述类型绑定过程。现在,我们将重点关注一个简单的示例,以展示其基本用法。
这是一个带有基本类型绑定过程的派生类型的示例
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
引入了面向对象特性**多态性**。
在上面的示例中,类型绑定过程 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
– 用于存储计算出的面积并返回给调用方