Fortran 数据类型与声明示例
Fortran 支持多种内置数据类型,包括:
- integer:整型,根据
kind
参数可指定不同字节长度。 -
可移植性说明:虽然在 gfortran、Intel Fortran 等编译器中常见地把
kind=4
视为 32 位、kind=8
视为 64 位,但标准并不强制这一对应关系。建议用selected_int_kind
或iso_fortran_env
中的int32
/int64
来获得可移植的kind
值。 - real:实型。默认是单精度(通常 32 位);也可通过
kind
指定更高精度。 -
可移植性说明:推荐使用
selected_real_kind
或iso_fortran_env
中的real32
/real64
来指定精度。 - double precision:双精度实型。
-
备注:若要严格遵循标准,可写成
real(kind=real64)
而非扩展关键字double precision
。 - complex:复数类型,可指定单精度
complex
或双精度complex(kind=8)
。 - logical:布尔类型,值为
.true.
或.false.
。 - character(len=n):定长字符类型;也可
len=*
由赋值决定长度。 - derived type:用户自定义类型,可由基本类型组合而成(参见“派生类型”部分)。
- parameter (常量声明):在声明中加
parameter
属性定义常量,不可修改。 - kind 参数:通过内置函数
selected_int_kind(n)
、selected_real_kind(p,r)
或use iso_fortran_env
中的类型常量来获得可移植的kind
值。
整型 (integer)
- 说明:整数类型。根据
kind
参数可以指定不同字节长度。例如integer(kind=4)
表示 4 字节整型,integer(kind=8)
表示 8 字节整型。 - 示例:
program integer_examples implicit none integer :: i_default ! 默认整型,编译器决定字节长度 integer(kind=4) :: i4 ! 4 字节整型 integer(kind=8) :: i8 ! 8 字节整型 integer, parameter :: i_const = 42 ! 带 kind 默认(或指定)和 parameter 属性的常量 integer(kind=selected_int_kind(10)) :: i_large ! 至少可表示 10 位十进制数 print *, "i_default =", i_default, "i4 =", i4, "i8 =", i8, "i_const =", i_const, "i_large =", i_large end program integer_examples
实型 (real)
- 说明:单精度实型,通常为 4 字节浮点数。也可通过
kind
指定字节长度,例如real(kind=4)
、real(kind=8)
。 - 示例:
program real_examples implicit none real :: r_default ! 默认单精度实型 real(kind=4) :: r4 ! 4 字节实型 real(kind=8) :: r8 ! 8 字节实型(相当于双精度) real, parameter :: pi = 3.1415926 ! 默认实型常量 real(kind=selected_real_kind(6,37)) :: r_precise ! 指定至少 6 位有效数字、指数范围 print *, "r_default =", r_default, "r4 =", r4, "r8 =", r8, "pi =", pi, "r_precise =", r_precise end program real_examples
双精度 (double precision)
- 说明:双精度实型,通常对应 8 字节浮点数;等价于
real(kind=8)
。 - 示例:
program double_precision_examples implicit none double precision :: dp_default ! 双精度实型 real(kind=8) :: dp_kind ! 等同于 double precision double precision, parameter :: dp_const = 1.23456789012345D0 ! D0 表示双精度常量 print *, "dp_default =", dp_default, "dp_kind =", dp_kind, "dp_const =", dp_const end program double_precision_examples
复数 (complex)
- 说明:复数类型。可以是单精度
complex
或双精度complex(kind=8)
(也称complex*16
)。 - 示例:
program complex_examples implicit none complex :: c_default ! 单精度复数 (2*4 字节) complex(kind=8) :: c_double ! 双精度复数 (2*8 字节) complex, parameter :: c_const = (3.0, 4.0) ! 单精度复数常量 complex(kind=selected_real_kind(15,307)) :: c_precise ! 高精度复数 print *, "c_default =", c_default, "c_double =", c_double, "c_const =", c_const, "c_precise =", c_precise end program complex_examples
双精度复数 (double complex)
- 说明:在某些编译器中可使用
double complex
,等价于complex(kind=8)
。 - 示例:
program double_complex_examples implicit none double complex :: dc ! 双精度复数 complex(kind=8) :: dc_kind ! 等同于 double complex double complex, parameter :: dc_const = (1.0D0, 2.0D0) ! 双精度复数常量 print *, "dc =", dc, "dc_kind =", dc_kind, "dc_const =", dc_const end program double_complex_examples
布尔类型 (logical)
- 说明:布尔类型,取值为
.true.
或.false.
。 - 示例:
program logical_examples implicit none logical :: flag_default ! 默认布尔类型 logical :: flag_true = .true. ! 初始化为真 logical :: flag_false = .false. ! 初始化为假 print *, "flag_default =", flag_default, "flag_true =", flag_true, "flag_false =", flag_false end program logical_examples
字符串 (character)
- 说明:定长字符类型。
character(len=n)
表示长度为 n 的字符串。 - 示例:
program character_examples implicit none character(len=10) :: str_fixed ! 长度为 10 的字符串 character(len=*) :: str_star = 'Fortran' ! 星号表示由赋值决定长度,这里为 7 character(len=20) :: str_init = 'Hello, World!' ! 初始化 print *, "str_fixed(before) =", '"'//str_fixed//'"' str_fixed = 'ABC' ! 剩余部分补空格 print *, "str_fixed(after) =", '"'//str_fixed//'"' print *, "str_star =", '"'//str_star//'"' print *, "str_init =", '"'//str_init//'"' end program character_examples
派生类型 (derived type)
- 说明:用户自定义类型,可由基本类型组合而成。类似于结构体(struct)。
-
示例:
module person_mod implicit none type :: Person character(len=50) :: name integer :: age real :: height logical :: is_student end type Person contains subroutine print_person(p) type(Person), intent(in) :: p print *, 'Name:', trim(p%name) print *, 'Age:', p%age print *, 'Height:', p%height print *, 'Is student?:', p%is_student end subroutine print_person end module person_mod program test_person use person_mod implicit none type(Person) :: stu stu%name = '张三' stu%age = 20 stu%height = 1.75 stu%is_student = .true. call print_person(stu) end program test_person
Parameter (常量声明)
- 说明:使用
parameter
属性定义常量,值不可更改。 - 示例:
program parameter_examples implicit none integer, parameter :: N = 100 ! 整型常量 N = 100 real, parameter :: PI = 3.1415926535 ! 实型常量 PI character(len=20), parameter :: GREETING = 'Hello, Fortran!' print *, "N =", N, "PI =", PI, "GREETING =", GREETING end program parameter_examples
kind 参数 (Kind Parameters)
- 说明:通过
selected_real_kind
、selected_int_kind
等内置函数指定不同精度或范围。 -
示例:
program kind_parameters_examples implicit none integer, parameter :: ik = selected_int_kind(10) ! 至少可表示 10 位十进制整数 integer, parameter :: rk = selected_real_kind(15, 307) ! 至少 15 位精度,指数范围 10^(-307) 到 10^307 integer(kind=ik) :: big_int real(kind=rk) :: high_prec_real big_int = 1234567890 high_prec_real = 1.234567890123456D0 print *, "big_int =", big_int print *, "high_prec_real =", high_prec_real end program kind_parameters_examples
数组类型 (Array Types)
-
说明:Fortran 原生支持多维数组,可在声明时指定维度,也可动态分配。
-
示例(固定维度):
program array_fixed_size implicit none integer, parameter :: n = 3, m = 4 real :: A(n, m) ! 声明一个 3x4 的二维实型数组 integer :: i, j ! 给数组赋值 do i = 1, n do j = 1, m A(i, j) = i * 10.0 + j end do end do print *, "A(1, : ) =", A(1, :) print *, "A(:, 2) =", A(:, 2) end program array_fixed_size
-
示例(动态分配):
program array_allocatable implicit none integer, allocatable :: B(:,:) integer :: p, q, i, j p = 5 q = 2 allocate(B(p, q)) ! 动态分配一个 p x q 的实型数组 B = 0 ! 将所有元素初始化为 0 do i = 1, p do j = 1, q B(i, j) = i + j end do end do print *, "B =", B deallocate(B) ! 释放内存 end program array_allocatable
指针 (pointer)
- 说明:指针可以指向目标对象,也可指向动态分配内存。常用于链表、动态数据结构等。
-
示例:
program pointer_examples implicit none real, allocatable :: E(:) real, pointer :: P(:) integer :: i allocate(E(10)) E = 1.0 ! 初始化 E 数组所有元素为 1.0 P => E ! 使 P 指向 E print *, "P(5) =", P(5) ! 输出 E(5) P(5) = 3.14 print *, "E(5) (after P change) =", E(5) nullify(P) ! 断开 P 与 E 之间的关联 deallocate(E) ! 释放 E end program pointer_examples
派生类型数组 (Array of Derived Types)
- 说明:可以声明包含派生类型元素的数组,用于存储对象列表。
-
示例:
module employee_mod implicit none type :: Employee integer :: id character(len=20) :: name real :: salary end type Employee end module employee_mod program employee_array_example use employee_mod implicit none type(Employee), allocatable :: staff(:) integer :: n, i n = 3 allocate(staff(n)) staff(1)%id = 101 staff(1)%name = 'Alice' staff(1)%salary = 50000.0 staff(2)%id = 102 staff(2)%name = 'Bob' staff(2)%salary = 55000.0 staff(3)%id = 103 staff(3)%name = 'Charlie' staff(3)%salary = 60000.0 do i = 1, n print *, 'ID:', staff(i)%id, 'Name:', trim(staff(i)%name), 'Salary:', staff(i)%salary end do deallocate(staff) end program employee_array_example
枚举 (Enumerations)
- 说明:Fortran 可使用
integer, parameter
定义枚举常量。 -
示例:
program enum_example implicit none integer, parameter :: RED = 1, GREEN = 2, BLUE = 3 integer :: color color = GREEN if (color == RED) then print *, 'Color is RED' elseif (color == GREEN) then print *, 'Color is GREEN' elseif (color == BLUE) then print *, 'Color is BLUE' end if end program enum_example
指定精度的类型 (Selected Precision Types)
- 说明:通过
iso_fortran_env
模块中定义的常量,指定整型和实型的预定义精度。 -
示例:
program selected_precision_examples use iso_fortran_env, only: real32, real64, int32, int64 implicit none integer(kind=int32) :: i32 integer(kind=int64) :: i64 real(kind=real32) :: r32 real(kind=real64) :: r64 i32 = 123456 i64 = 123456789012345 r32 = 1.2345 r64 = 1.23456789012345 print *, "i32 =", i32, "i64 =", i64 print *, "r32 =", r32, "r64 =", r64 end program selected_precision_examples
可空参数和指针声明 (Nullable Pointer Declarations)
- 说明:可以使用
pointer
和nullify
管理可选目标。 -
示例:
program nullable_pointer implicit none real, pointer :: P(:) if (.not. associated(P)) then print *, "P 尚未关联任何目标" end if allocate(P(5)) P = 2.0 nullify(P) if (.not. associated(P)) then print *, "P 已解除关联" end if end program nullable_pointer
指针到派生类型 (Pointer to Derived Type)
- 示例:
module employee_mod implicit none type :: Employee integer(kind=int32) :: id character(len=20) :: name real(kind=real32) :: salary end type Employee end module employee_mod program employee_array_example use employee_mod implicit none type(Employee), allocatable :: staff(:) integer :: n, i n = 3 allocate(staff(n)) staff(1)%id = 101 staff(1)%name = 'Alice' staff(1)%salary = 50000.0_real32 staff(2)%id = 102 staff(2)%name = 'Bob' staff(2)%salary = 55000.0_real32 staff(3)%id = 103 staff(3)%name = 'Charlie' staff(3)%salary = 60000.0_real32 do i = 1, n print *, 'ID:', staff(i)%id, 'Name:', trim(staff(i)%name), & 'Salary:', staff(i)%salary end do deallocate(staff) end program employee_array_example
发表回复
要发表评论,您必须先登录。