类型和种类#

这些内置函数允许将一种类型的变量显式转换为另一种类型,或者在使用多态变量时可用于基于变量类型有条件地执行代码块。

Fortran 数据类型#

Fortran 提供了五种基本的内置数据类型:

  • 整数类型

    整数类型只能保存整数值。

  • 实数类型

    存储浮点数,例如 2.0、3.1415、-100.876 等。

  • 复数类型

    复数有两个部分,实部和虚部。两个连续的浮点存储单元存储这两个部分。

  • 逻辑类型

    只有两个逻辑值:.true. 和 .false.

  • 字符类型

    字符类型存储字符串。字符串的长度可以由 len 说明符指定。如果没有指定长度,则为 1。

这些“类型”可以是许多“种类”。通常不同的数字类型占用不同的存储大小,因此可以表示不同的范围;但不同的种类可以有其它的含义。例如, character 变量可能表示 ASCII 字符或 UTF-8 或 Unicode 字符。

你也可以从这些基本类型派生出你自己的数据类型。

隐式类型#

Fortran 允许一种称为隐式类型的功能,即,你不必在使用前声明某些变量。默认情况下,如果未声明变量,则其名称的第一个字母将确定其类型:

  1. i-n (“整数”的前两个字母)开头的变量名称指定 integer 变量。

  2. 所有其它变量名默认为 real

但是,在大多数圈子中,声明所有变量被认为是良好的编程习惯。为了强制执行,你可以使用关闭隐式类型的语句开始变量声明部分:语句

implicit none

有关详细信息,请参阅 隐式 声明。

aimag#

名称#

aimag(3) - [TYPE:NUMERIC] 复数的虚部

Synopsis#

    result = aimag(z)
     elemental complex(kind=KIND) function aimag(z)

      complex(kind=KIND),intent(in) :: z

Characteristics#

  • The type of the argument z shall be complex and any supported complex kind

  • 返回值是 real 类型,带有参数的 kind 类型参数。

说明#

aimag(3) yields the imaginary part of the complex argument z.

This is similar to the modern complex-part-designator %IM which also designates the imaginary part of a value, accept a designator can appear on the left-hand side of an assignment as well, as in val%im=10.0.

选项#

  • z

    The complex value to extract the imaginary component of.

结果#

The return value is a real value with the magnitude and sign of the imaginary component of the argument z.

That is, If z has the value (x,y), the result has the value y.

示例#

示例程序:

program demo_aimag
use, intrinsic :: iso_fortran_env, only : real_kinds, &
 & real32, real64, real128
implicit none
character(len=*),parameter :: g='(*(1x,g0))'
complex              :: z4
complex(kind=real64) :: z8
   ! basics
    z4 = cmplx(1.e0, 2.e0)
    print *, 'value=',z4
    print g, 'imaginary part=',aimag(z4),'or', z4%im

    ! other kinds other than the default may be supported
    z8 = cmplx(3.e0_real64, 4.e0_real64,kind=real64)
    print *, 'value=',z8
    print g, 'imaginary part=',aimag(z8),'or', z8%im

    ! an elemental function can be passed an array
    print *
    print *, [z4,z4/2.0,z4+z4,z4**3]
    print *
    print *, aimag([z4,z4/2.0,z4+z4,z4**3])

end program demo_aimag

结果:

 value= (1.00000000,2.00000000)
 imaginary part= 2.00000000 or 2.00000000
 value= (3.0000000000000000,4.0000000000000000)
 imaginary part= 4.0000000000000000 or 4.0000000000000000

 (1.00000000,2.00000000) (0.500000000,1.00000000) (2.00000000,4.00000000)
 (-11.0000000,-2.00000000)

   2.00000000       1.00000000       4.00000000      -2.00000000

标准#

FORTRAN 77

另见#

Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:

abs(3), acosh(3), acos(3), asinh(3), asin(3), atan2(3), atanh(3), atan(3), cosh(3), cos(3), co_sum(3), dble(3), dot_product(3), exp(3), int(3), is_contiguous(3), kind(3), log(3), matmul(3), precision(3), product(3), range(3), rank(3), sinh(3), sin(3), sqrt(3), storage_size(3), sum(3), tanh(3), tan(3), unpack(3),

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

cmplx#

名称#

cmplx(3) - [TYPE:NUMERIC] Conversion to a complex type

Synopsis#

    result = cmplx(x [,kind]) | cmplx(x [,y] [,kind])
     elemental complex(kind=KIND) function cmplx( x, y, kind )

      type(TYPE(kind=**)),intent(in)          :: x
      type(TYPE(kind=**)),intent(in),optional :: y
      integer(kind=**),intent(in),optional    :: KIND

Characteristics#

  • x may be integer, real, or complex.

  • y may be integer or real. y is allowed only if x is not complex.

  • KIND is a constant integer initialization expression indicating the kind parameter of the result.

The type of the arguments does not affect the kind of the result except for a complex x value.

  • if kind is not present and x is complex the result is of the kind of x.

  • if kind is not present and x is not complex the result if of default complex kind.

NOTE: a kind designated as ** may be any supported kind for the type

说明#

The cmplx(3) function converts numeric values to a complex value.

Even though constants can be used to define a complex variable using syntax like

      z = (1.23456789, 9.87654321)

this will not work for variables. So you cannot enter

      z = (a, b)  ! NO ! (unless a and b are constants, not variables)

so to construct a complex value using non-complex values you must use the cmplx(3) function:

      z = cmplx(a, b)

or assign values separately to the imaginary and real components using the %IM and %RE designators:

      z%re = a
      z%im = b

If x is complex y is not allowed and cmplx essentially returns the input value except for an optional change of kind, which can be useful when passing a value to a procedure that requires the arguments to have a different kind (and does not return an altered value):

      call something(cmplx(z,kind=real64))

would pass a copy of a value with kind=real64 even if z had a different kind

but otherwise is equivalent to a simple assign. So if z1 and z2 were complex:

      z2 = z1        ! equivalent statements
      z2 = cmplx(z1)

If x is not complex x is only used to define the real component of the result but y is still optional – the imaginary part of the result will just be assigned a value of zero.

If y is present it is converted to the imaginary component.

cmplx(3) 和双精度#

Primarily in order to maintain upward compatibility you need to be careful when working with complex values of higher precision that the default.

It was necessary for Fortran to continue to specify that cmplx(3) always return a result of the default kind if the kind option is absent, since that is the behavior mandated by FORTRAN 77.

It might have been preferable to use the highest precision of the arguments for determining the return kind, but that is not the case. So with arguments with greater precision than default values you are required to use the kind argument or the greater precision values will be reduced to default precision.

这意味着 cmplx(d1,d2),其中 d1d2doubleprecision,被视为:

      cmplx(sngl(d1), sngl(d2))

which looses precision.

So Fortran 90 extends the cmplx(3) intrinsic by adding an extra argument used to specify the desired kind of the complex result.

      integer,parameter :: dp=kind(0.0d0)
      complex(kind=dp) :: z8
     ! wrong ways to specify constant values
      ! note this was stored with default real precision !
      z8 = cmplx(1.2345678901234567d0, 1.2345678901234567d0)
      print *, 'NO, Z8=',z8,real(z8),aimag(z8)

      z8 = cmplx(1.2345678901234567e0_dp, 1.2345678901234567e0_dp)
      ! again, note output components are just real
      print *, 'NO, Z8=',z8,real(z8),aimag(z8)
      !
      ! YES
      !
      ! kind= makes it work
      z8 = cmplx(1.2345678901234567d0, 1.2345678901234567d0,kind=dp)
      print *, 'YES, Z8=',z8,real(z8),aimag(z8)

A more recent alternative to using cmplx(3) is “F2018 component syntax” where real and imaginary parts of a complex entity can be accessed independently:

value%RE     ! %RE specifies the real part
or
value%IM     ! %IM specifies the imaginary part

Where the designator value is of course of complex type.

The type of a complex-part-designator is real, and its kind and shape are those of the designator. That is, you retain the precision of the complex value by default, unlike with cmplx.

以下是复数部分代号的示例:

       impedance%re           !-- Same value as real(impedance)
       fft%im                 !-- Same value as AIMAG(fft)
       x%im = 0.0             !-- Sets the imaginary part of x to zero
       x(1:2)%re=[10,20]      !-- even if x is an array

NOTE for I/O#

Note that if format statements are specified a complex value is treated as two real values.

For list-directed I/O (ie. using an asterisk for a format) and NAMELIST output the values are expected to be delimited by “(” and “)” and of the form “(realpart,imaginary_part)”. For NAMELIST input parenthesized values or lists of multiple _real values are acceptable.

选项#

  • x

    The value assigned to the real component of the result when x is not complex.

    If x is complex, the result is the same as if the real part of the input was passed as x and the imaginary part as y.

     result = CMPLX (REAL (X), AIMAG (X), KIND).

That is, a complex x value is copied to the result value with a possible change of kind.

  • y

    y is only allowed if x is not complex. Its value is assigned to the imaginary component of the result and defaults to a value of zero if absent.

  • 种类

    一个 integer 初始化表达式,指示结果的种类参数。

结果#

The return value is of complex type, with magnitudes determined by the values x and y.

The common case when x is not complex is that the real component of the result is assigned the value of x and the imaginary part is zero or the value of y if y is present.

When x is complex y is not allowed and the result is the same value as x with a possible change of kind. That is, the real part is real(x, kind) and the imaginary part is real(y, kind).

示例#

示例程序:

program demo_aimag
implicit none
integer,parameter :: dp=kind(0.0d0)
real(kind=dp)     :: precise
complex(kind=dp)  :: z8
complex           :: z4, zthree(3)
   precise=1.2345678901234567d0

  ! basic
   z4 = cmplx(-3)
   print *, 'Z4=',z4
   z4 = cmplx(1.23456789, 1.23456789)
   print *, 'Z4=',z4
   ! with a format treat a complex as two real values
   print '(1x,g0,1x,g0,1x,g0)','Z4=',z4

  ! working with higher precision values
   ! using kind=dp makes it keep DOUBLEPRECISION precision
   ! otherwise the result would be of default kind
   z8 = cmplx(precise, -precise )
   print *, 'lost precision Z8=',z8
   z8 = cmplx(precise, -precise ,kind=dp)
   print *, 'kept precision Z8=',z8

  ! assignment of constant values does not require cmplx(3)00
   ! The following is intuitive and works without calling cmplx(3)
   ! but does not work for variables just constants
   z8 = (1.1111111111111111d0, 2.2222222222222222d0 )
   print *, 'Z8 defined with constants=',z8

  ! what happens when you assign a complex to a real?
   precise=z8
   print *, 'LHS=',precise,'RHS=',z8

  ! elemental
   zthree=cmplx([10,20,30],-1)
   print *, 'zthree=',zthree

  ! descriptors are an alternative
   zthree(1:2)%re=[100,200]
   print *, 'zthree=',zthree

end program demo_aimag

结果:

    Z4= (-3.000000,0.0000000E+00)
    Z4= (1.234568,1.234568)
    Z4= 1.234568 1.234568
    lost precision Z8= (1.23456788063049,-1.23456788063049)
    kept precision Z8= (1.23456789012346,-1.23456789012346)
    Z8 defined with constants= (1.11111111111111,2.22222222222222)
    LHS=   1.11111111111111      RHS= (1.11111111111111,2.22222222222222)
    zthree= (10.00000,-1.000000) (20.00000,-1.000000) (30.00000,-1.000000)
    zthree= (100.0000,-1.000000) (200.0000,-1.000000) (30.00000,-1.000000)

标准#

FORTRAN 77, KIND added in Fortran 90.

另见#

Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:

abs(3), acosh(3), acos(3), asinh(3), asin(3), atan2(3), atanh(3), atan(3), cosh(3), cos(3), co_sum(3), dble(3), dot_product(3), exp(3), int(3), is_contiguous(3), kind(3), log(3), matmul(3), precision(3), product(3), range(3), rank(3), sinh(3), sin(3), sqrt(3), storage_size(3), sum(3), tanh(3), tan(3), unpack(3),

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

int#

名称#

int(3) - [TYPE:NUMERIC] Truncate towards zero and convert to integer

Synopsis#

    result = int(a [,kind])
     elemental integer(kind=KIND) function int(a, KIND )

      TYPE(kind=**),intent(in) :: a
      integer,optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • a shall be of type integer, real, or complex, or a boz-literal-constant.

  • KIND shall be a scalar integer constant expression.

说明#

int(3) truncates towards zero and return an integer.

选项#

  • a

    is the value to truncate towards zero

  • 种类

    indicates the kind parameter of the result. If not present the returned type is that of default integer type.

结果#

returns an integer variable applying the following rules:

情况:

  1. 如果 ainteger 类型,则 int(a) = a

  2. 如果 a 的类型是 real|a| < 1,int(a) 等于 0。如果 |a| >= 1,则int(a)等于大小不超过a且符号与a符号相同的整数。

  3. 如果 acomplex 类型,则规则 2 应用于 areal 部分。

  4. 如果 a 是 boz-literal 常量,则将其视为指定 kindinteger

    最高有效位为 1 的位序列的解释取决于处理器。

如果无法以指定的整数类型表示,则结果未定义。

示例#

示例程序:

program demo_int
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer :: i = 42
complex :: z = (-3.7, 1.0)
real :: x=-10.5, y=10.5

   print *, int(x), int(y)

   print *, int(i)

   print *, int(z), int(z,8)
   ! elemental
   print *, int([-10.9,-10.5,-10.3,10.3,10.5,10.9])
   ! note int(3) truncates towards zero

   ! CAUTION:
   ! a number bigger than a default integer can represent
   ! produces an incorrect result and is not required to
   ! be detected by the program.
   x=real(huge(0))+1000.0
   print *, int(x),x
   ! using a larger kind
   print *, int(x,kind=int64),x

   print *, int(&
   & B"111111111111111111111111111111111111111111111111111111111111111",&
   & kind=int64)
   print *, int(O"777777777777777777777",kind=int64)
   print *, int(Z"7FFFFFFFFFFFFFFF",kind=int64)

   ! elemental
   print *
   print *,int([ &
   &  -2.7,  -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, &
   &  0.0,   &
   &  +0.5,  +1.0, +1.5, +2.0, +2.2, +2.5, +2.7  ])

end program demo_int

结果:

 >          -10   10
 >           42
 >           -3  -3
 >          -10  -10  -10   10   10  10
 >  -2147483648   2.14748467E+09
 >   2147484672   2.14748467E+09
 >   9223372036854775807
 >   9223372036854775807
 >   9223372036854775807
 >
 >  -2          -2          -2          -2          -1
 >  -1           0           0           0           1
 >   1           2           2           2           2

标准#

FORTRAN 77

另见#

aint(3), anint(3), nint(3), selected_int_kind(3), ceiling(3), floor(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

nint#

名称#

nint(3) - [TYPE:NUMERIC] 最近的整数

Synopsis#

    result = nint( a [,kind] )
     elemental integer(kind=KIND) function nint(a, kind )

      real(kind=**),intent(in) :: a
      integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • a is type real of any kind

  • KIND is a scalar integer constant expression

  • The result is default integer kind or the value of kind if kind is present.

说明#

nint(3) rounds its argument to the nearest whole number with its sign preserved.

用户必须确保该值是返回的 kind 范围内的有效值。如果处理器不能以指定的种类表示结果,则结果是未定义的。

If a is greater than zero, nint(a) has the value int(a+0.5).

If a is less than or equal to zero, nint(a) has the value int(a-0.5).

选项#

  • a

    The value to round to the nearest whole number

  • 种类

    can specify the kind of the output value. If not present, the output is the default type of integer.

结果#

The result is the integer nearest a, or if there are two integers equally near a, the result is whichever such integer has the greater magnitude.

如果无法以指定的整数类型表示,则结果未定义。

示例#

示例程序:

program demo_nint
implicit none
integer,parameter   :: dp=kind(0.0d0)
real,allocatable    :: in(:)
integer,allocatable :: out(:)
integer             :: i
real                :: x4
real(kind=dp)       :: x8

  ! basic use
   x4 = 1.234E0
   x8 = 4.721_dp
   print *, nint(x4), nint(-x4)
   print *, nint(x8), nint(-x8)

  ! elemental
   in = [ -2.7,  -2.5, -2.2, -2.0, -1.5, -1.0, -0.5, -0.4, &
        &  0.0,   &
        & +0.04, +0.5, +1.0, +1.5, +2.0, +2.2, +2.5, +2.7  ]
   out = nint(in)
   do i=1,size(in)
      write(*,*)in(i),out(i)
   enddo

  ! dusty corners
   ISSUES: block
   use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
   integer :: icheck
      ! make sure input is in range for the type returned
      write(*,*)'Range limits for typical KINDS:'
      write(*,'(1x,g0,1x,g0)')  &
      & int8,huge(0_int8),   &
      & int16,huge(0_int16), &
      & int32,huge(0_int32), &
      & int64,huge(0_int64)

      ! the standard does not require this to be an error ...
      x8=12345.67e15 ! too big of a number
      icheck=selected_int_kind(ceiling(log10(x8)))
      write(*,*)'Any KIND big enough? ICHECK=',icheck
      print *, 'These are all wrong answers for ',x8
      print *, nint(x8,kind=int8)
      print *, nint(x8,kind=int16)
      print *, nint(x8,kind=int32)
      print *, nint(x8,kind=int64)
   endblock ISSUES

end program demo_nint

结果:

 >               1          -1
 >               5          -5
 >      -2.700000              -3
 >      -2.500000              -3
 >      -2.200000              -2
 >      -2.000000              -2
 >      -1.500000              -2
 >      -1.000000              -1
 >     -0.5000000              -1
 >     -0.4000000               0
 >      0.0000000E+00           0
 >      3.9999999E-02           0
 >      0.5000000               1
 >       1.000000               1
 >       1.500000               2
 >       2.000000               2
 >       2.200000               2
 >       2.500000               3
 >       2.700000               3
 >     Range limits for typical KINDS:
 >     1 127
 >     2 32767
 >     4 2147483647
 >     8 9223372036854775807
 >     Any KIND big enough? ICHECK=          -1
 >     These are all wrong answers for   1.234566949990144E+019
 >        0
 >          0
 >     -2147483648
 >      -9223372036854775808

标准#

FORTRAN 77 , with KIND argument - Fortran 90

另见#

aint(3), anint(3), int(3), selected_int_kind(3), ceiling(3), floor(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

real#

名称#

real(3) - [TYPE:NUMERIC] 转换为实型

Synopsis#

  result = real(x [,kind])
   elemental real(kind=KIND) function real(x,KIND)

    TYPE(kind=**),intent(in) :: x
    integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • the type of x may be integer, real, or complex; or a BOZ-literal-constant.

  • kind is a integer initialization expression (a constant expression)

    • If kind is present it defines the kind of the real result

    • if kind is not present

      • when x is complex the result is a real of the same kind as x.

      • when x is real or integer the result is a real of default kind

  • a kind designated as ** may be any supported kind for the type

说明#

real(3) converts its argument x to a real type.

The real part of a complex value is returned. For complex values this is similar to the modern complex-part-designator %RE which also designates the real part of a complex value.

      z=(3.0,4.0)     ! if z is a complex value
      print *, z%re == real(z) ! these expressions are equivalent

选项#

  • x

    An integer, real, or complex value to convert to real.

  • 种类

    When present the value of kind defines the kind of the result.

结果#

  1. real(x) converts x to a default real type if x is an integer or real variable.

  2. real(x) converts a complex value to a real type with the magnitude of the real component of the input with kind type parameter the same as x.

  3. 如果 xcomplexinteger real 变量, real(x, kind) 转换为 real 类型并附带种类参数。

示例#

示例程序:

program demo_real
use,intrinsic :: iso_fortran_env, only : dp=>real64
implicit none
complex              :: zr = (1.0, 2.0)
doubleprecision      :: xd=huge(3.0d0)
complex(kind=dp) :: zd=cmplx(4.0e0_dp,5.0e0_dp,kind=dp)

   print *, real(zr), aimag(zr)
   print *, dble(zd), aimag(zd)

   write(*,*)xd,real(xd,kind=kind(0.0d0)),dble(xd)
end program demo_real

结果:

 1.00000000       2.00000000
 4.0000000000000000       5.0000000000000000
 1.7976931348623157E+308  1.7976931348623157E+308  1.7976931348623157E+308

标准#

FORTRAN 77

另见#

Fortran has strong support for complex values, including many intrinsics that take or produce complex values in addition to algebraic and logical expressions:

abs(3), acosh(3), acos(3), asinh(3), asin(3), atan2(3), atanh(3), atan(3), cosh(3), cos(3), co_sum(3), dble(3), dot_product(3), exp(3), int(3), is_contiguous(3), kind(3), log(3), matmul(3), precision(3), product(3), range(3), rank(3), sinh(3), sin(3), sqrt(3), storage_size(3), sum(3), tanh(3), tan(3), unpack(3),

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

dble#

名称#

dble(3) - [TYPE:NUMERIC] Converstion to double precision real

Synopsis#

    result = dble(a)
     elemental doubleprecision function dble(a)

      doubleprecision :: dble
      TYPE(kind=KIND),intent(in) :: a

Characteristics#

  • a my be integer, real, complex, or a BOZ-literal-constant

  • the result is a doubleprecision real.

说明#

dble(3) Converts a to double precision real type.

选项#

  • a

    a value to convert to a doubleprecision real.

结果#

返回值的类型为 doubleprecision。对于 complex 输入,返回值具有输入值实部的大小和符号。

示例#

示例程序:

program demo_dble
implicit none
real:: x = 2.18
integer :: i = 5
complex :: z = (2.3,1.14)
   print *, dble(x), dble(i), dble(z)
end program demo_dble

结果:

  2.1800000667572021  5.0000000000000000   2.2999999523162842

标准#

FORTRAN 77

See also#

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

transfer#

名称#

transfer(3) - [TYPE:MOLD] 传输位模式

Synopsis#

    result = transfer(source, mold [,size] )
     type(TYPE(kind=KIND)) function transfer(source,mold,size)

      type(TYPE(kind=KIND)),intent(in) :: source(..)
      type(TYPE(kind=KIND)),intent(in) :: mold(..)
      integer(kind=**),intent(in),optional :: size

Characteristics#

  • source shall be a scalar or an array of any type.

  • mold shall be a scalar or an array of any type.

  • size shall be a scalar of type integer.

  • result has the same type as mold

说明#

transfer(3) copies the bitwise representation of source in memory into a variable or array of the same type and type parameters as mold.

这大致相当于 C 概念中将一种类型“转换”为另一种类型。

选项#

  • 资源

    Holds the bit pattern to be copied

  • mold

    the type of mold is used to define the type of the returned value. In addition, if it is an array the returned value is a one-dimensional array. If it is a scalar the returned value is a scalar.

  • size

    If size is present, the result is a one-dimensional array of length size.

If size is absent but mold is an array (of any size or shape), the result is a one-dimensional array of the minimum length needed to contain the entirety of the bitwise representation of source.

If size is absent and mold is a scalar, the result is a scalar.

结果#

The result has the bit level representation of source.

If the bitwise representation of the result is longer than that of source, then the leading bits of the result correspond to those of source but any trailing bits are filled arbitrarily.

当生成的位表示不对应于与 mold 相同类型的变量的有效表示时,结果是未定义的,并且不能保证对结果的后续操作产生合理的行为。例如,可以为 var 和 .not 创建 logical 变量。 var 似乎都是真的。

示例#

示例程序:

program demo_transfer
use,intrinsic :: iso_fortran_env, only : int32, real32
integer(kind=int32) :: i = 2143289344
real(kind=real32)   :: x
character(len=10)   :: string
character(len=1)    :: chars(10)
   x=transfer(i, 1.0)    ! prints "nan" on i686
   ! the bit patterns are the same
   write(*,'(b0,1x,g0)')x,x ! create a NaN
   write(*,'(b0,1x,g0)')i,i

   ! a string to an array of characters
   string='abcdefghij'
   chars=transfer(string,chars)
   write(*,'(*("[",a,"]":,1x))')string
   write(*,'(*("[",a,"]":,1x))')chars
end program demo_transfer

结果:

   1111111110000000000000000000000 NaN
   1111111110000000000000000000000 2143289344
   [abcdefghij]
   [a] [b] [c] [d] [e] [f] [g] [h] [i] [j]

评论#

Joe Krahn:Fortran 使用 molding 而不是 casting

与 C 语言一样,铸造是一种就地重新解释。铸件是一种围绕物体构建以改变其形状的装置。

Fortran transfer(3) reinterprets data out-of-place. It can be considered molding rather than casting. A mold is a device that confers a shape onto an object placed into it.

The advantage of molding is that data is always valid in the context of the variable that holds it. For many cases, a decent compiler should optimize transfer(3) into a simple assignment.

There are disadvantages of this approach. It is problematic to define a union of data types because you must know the largest data object, which can vary by compiler or compile options. In many cases, an EQUIVALENCE would be far more effective, but Fortran Standards committees seem oblivious to the benefits of EQUIVALENCE when used sparingly.

标准#

Fortran 90

See also#

****(3)

fortran-lang intrinsic descriptions

logical#

名称#

logical(3) - [TYPE:LOGICAL] Conversion between kinds of logical values

Synopsis#

    result = logical(l [,kind])
     elemental logical(kind=KIND) function logical(l,KIND)

      logical(kind=**),intent(in) :: l
      integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • l is of type logical

  • KIND shall be a scalar integer constant expression. If KIND is present, the kind type parameter of the result is that specified by the value of KIND; otherwise, the kind type parameter is that of default logical.

说明#

logical(3) converts one kind of logical variable to another.

选项#

  • l

    The logical value to produce a copy of with kind kind

  • 种类

    indicates the kind parameter of the result. If not present, the default kind is returned.

结果#

返回值是一个 logical 值,等于 l,其种类对应于 kind,或者如果逻辑种类没有给出, kind 则为默认。

示例#

示例程序:

Linux
program demo_logical
! Access array containing the kind type parameter values supported by this
! compiler for entities of logical type
use iso_fortran_env, only : logical_kinds
implicit none
integer :: i

   ! list kind values supported on this platform, which generally vary
   ! in storage size as alias declarations
   do i =1, size(logical_kinds)
      write(*,'(*(g0))')'integer,parameter :: boolean', &
      & logical_kinds(i),'=', logical_kinds(i)
   enddo

end program demo_logical

结果:

 > integer,parameter :: boolean1=1
 > integer,parameter :: boolean2=2
 > integer,parameter :: boolean4=4
 > integer,parameter :: boolean8=8
 > integer,parameter :: boolean16=16

标准#

Fortran 95 , related ISO_FORTRAN_ENV module - fortran 2009

另见#

int(3)real(3)cmplx(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

kind#

名称#

kind(3) - [KIND:INQUIRY] Query kind of an entity

Synopsis#

    result = kind(x)
     integer function kind(x)

      type(TYPE,kind=**),intent(in) :: x(..)

Characteristics#

  • x may be of any intrinsic type. It may be a scalar or an array.

  • the result is a default integer scalar

说明#

kind(x)(3) returns the kind value of the entity x.

选项#

  • x

    Value to query the kind of.

结果#

The return value indicates the kind of the argument x.

Note that kinds are processor-dependent.

示例#

示例程序:

program demo_kind
implicit none
integer,parameter :: dc = kind(' ')
integer,parameter :: dl = kind(.true.)

   print *, "The default character kind is ", dc
   print *, "The default logical kind is ", dl

end program demo_kind

结果:

    The default character kind is            1
    The default logical kind is            4

标准#

Fortran 95

See also#

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

out_of_range#

名称#

out_of_range(3) - [TYPE:NUMERIC] 值是否不能安全转换。

Synopsis#

    result = out_of_range (x, mold [, round])
     elemental logical function(x, mold, round)

      TYPE,kind=KIND),intent(in) :: x
      TYPE,kind=KIND),intent(in) :: mold
      logical,intent(in),optional     :: round

Characteristics#

  • x is of type integer or real.

  • mold is an integer or real scalar.

  • round is a logical scalar.

  • the result is a default logical.

说明#

out_of_range(3) determines whether a value x can be converted safely to a real or integer variable the same type and kind as mold.

For example, if int8 is the kind value for an 8-bit binary integer type, out_of_range(-128.5, 0_int8) will have the value false and out_of_range(-128.5, 0_int8, .true.) will have the value .true. because the value will be truncated when converted to an integer and -128 is a representable value on a two’s complement machine in eight bits even though +128 is not.

选项#

  • x

    a scalar to be tested for whether it can be stored in a variable of the type and kind of mold

  • mold and kind are queried to determine the characteristics of what needs to be fit into.

  • round

    标记是否在将 xx 的值验证为和mold一样的整数值之前对其进行舍入。

    仅当 x 的类型为 realmold 的类型为 integer 时,round 才能存在。

结果#

标准:

Case (i): If mold is of type integer, and round is absent or present with the value false, the result is true if and only if the value of X is an IEEE infinity or NaN, or if the integer with largest magnitude that lies between zero and X inclusive is not representable by objects with the type and kind of mold.

Case (ii): If mold is of type integer, and round is present with the value true, the result is true if and only if the value of X is an IEEE infinity or NaN, or if the integer nearest X, or the integer of greater magnitude if two integers are equally near to X, is not representable by objects with the type and kind of mold.

Case (iii): Otherwise, the result is true if and only if the value of X is an IEEE infinity or NaN that is not supported by objects of the type and kind of mold, or if X is a finite number and the result of rounding the value of X (according to the IEEE rounding mode if appropriate) to the extended model for the kind of mold has magnitude larger than that of the largest finite number with the same sign as X that is representable by objects with the type and kind of mold.

注意

mold is required to be a scalar because the only information taken from it is its type and kind. Allowing an array mold would require that it be conformable with x. round is scalar because allowing an array rounding mode would have severe performance difficulties on many processors.

示例#

示例程序:

program demo_out_of_range
use, intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
use, intrinsic :: iso_fortran_env, only : real32, real64, real128
implicit none
integer            :: i
integer(kind=int8) :: i8, j8

    ! compilers are not required to produce an error on out of range.
    ! here storing the default integers into 1-byte integers
    ! incorrectly can have unexpected results
    do i=127,130
       i8=i
       j8=-i
       ! OUT_OF_RANGE(3f) can let you check if the value will fit
       write(*,*)i8,j8,' might have expected',i,-i, &
        & out_of_range( i,i8), &
        & out_of_range(-i,i8)
    enddo
    write(*,*) 'RANGE IS ',-1-huge(0_int8),'TO',huge(0_int8)
    ! the real -128.5 is truncated to -128 and is in range
    write(*,*) out_of_range (  -128.5, 0_int8)         ! false

    ! the real -128.5 is rounded to -129 and is not in range
    write(*,*) out_of_range (  -128.5, 0_int8, .true.) ! true

end program demo_out_of_range

结果:

  >  127 -127  might have expected         127        -127 F F
  > -128 -128  might have expected         128        -128 T F
  > -127  127  might have expected         129        -129 T T
  > -126  126  might have expected         130        -130 T T
  > RANGE IS         -128 TO  127
  > F
  > T

标准#

FORTRAN 2018

See also#

  • aimag(3)- 复数的虚部

  • cmplx(3) - Convert values to a complex type

  • dble(3) - Double conversion function

  • int(3) - Truncate towards zero and convert to integer

  • nint(3) - Nearest whole number

  • real(3) - 转换为实型

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

selected_char_kind#

名称#

selected_char_kind(3) - [KIND] Select character kind such as “Unicode”

Synopsis#

    result = selected_char_kind(name)
     integer function selected_char_kind(name)

      character(len=*),intent(in) :: name

Characteristics#

  • name is a default character scalar

  • the result is a default integer scalar

说明#

selected_char_kind(3) returns a kind parameter value for the character set named name.

If a name is not supported, -1 is returned. Otherwise the result is a value equal to that kind type parameter value.

The list of supported names is processor-dependent except for “DEFAULT”.

  • If name has the value “DEFAULT”, then the result has a value equal to that of the kind type parameter of default character. This name is always supported.

  • If name has the value “ASCII”, then the result has a value equal to that of the kind type parameter of ASCII character.

  • If name has the value “ISO_10646”, then the result has a value equal to that of the kind type parameter of the ISO 10646 character kind (corresponding to UCS-4 as specified in ISO/IEC 10646).

  • If name is a processor-defined name of some other character kind supported by the processor, then the result has a value equal to that kind type parameter value. Pre-defined names include “ASCII” and “ISO_10646”.

The NAME is interpreted without respect to case or trailing blanks.

选项#

  • name

    A name to query the processor-dependent kind value of, and/or to determine if supported. name, interpreted without respect to case or trailing blanks.

    Currently, supported character sets include “ASCII” and “DEFAULT” and “ISO_10646” (Universal Character Set, UCS-4) which is commonly known as “Unicode”. Supported names other than “DEFAULT” are processor dependent.

结果#

示例#

示例程序:

Linux
program demo_selected_char_kind
use iso_fortran_env
implicit none

intrinsic date_and_time,selected_char_kind

! set some aliases for common character kinds
! as the numbers can vary from platform to platform

integer, parameter :: default = selected_char_kind ("default")
integer, parameter :: ascii =   selected_char_kind ("ascii")
integer, parameter :: ucs4  =   selected_char_kind ('ISO_10646')
integer, parameter :: utf8  =   selected_char_kind ('utf-8')

! assuming ASCII and UCS4 are supported (ie. not equal to -1)
! define some string variables
character(len=26, kind=ascii ) :: alphabet
character(len=30, kind=ucs4  ) :: hello_world
character(len=30, kind=ucs4  ) :: string

   write(*,*)'ASCII     ',&
    & merge('Supported    ','Not Supported',ascii /= -1)
   write(*,*)'ISO_10646 ',&
    & merge('Supported    ','Not Supported',ucs4 /= -1)
   write(*,*)'UTF-8     ',&
    & merge('Supported    ','Not Supported',utf8 /= -1)

   if(default.eq.ascii)then
       write(*,*)'ASCII is the default on this processor'
   endif

  ! for constants the kind precedes the value, somewhat like a
  ! BOZ constant
   alphabet = ascii_"abcdefghijklmnopqrstuvwxyz"
   write (*,*) alphabet

   hello_world = ucs4_'Hello World and Ni Hao -- ' &
                 // char (int (z'4F60'), ucs4)     &
                 // char (int (z'597D'), ucs4)

  ! an encoding option is required on OPEN for non-default I/O
   if(ucs4 /= -1 )then
      open (output_unit, encoding='UTF-8')
      write (*,*) trim (hello_world)
   else
      write (*,*) 'cannot use utf-8'
   endif

   call create_date_string(string)
   write (*,*) trim (string)

contains

! The following produces a Japanese date stamp.
subroutine create_date_string(string)
intrinsic date_and_time,selected_char_kind
integer,parameter :: ucs4 = selected_char_kind("ISO_10646")
character(len=1,kind=ucs4),parameter :: &
       nen =   char(int( z'5e74' ),ucs4), & ! year
       gatsu = char(int( z'6708' ),ucs4), & ! month
       nichi = char(int( z'65e5' ),ucs4)    ! day
character(len= *, kind= ucs4) string
integer values(8)
   call date_and_time(values=values)
   write(string,101) values(1),nen,values(2),gatsu,values(3),nichi
 101 format(*(i0,a))
end subroutine create_date_string

end program demo_selected_char_kind

结果:

The results are very processor-dependent

 >  ASCII     Supported
 >  ISO_10646 Supported
 >  UTF-8     Not Supported
 >  ASCII is the default on this processor
 >  abcdefghijklmnopqrstuvwxyz
 >  Hello World and Ni Hao -- 你好
 >  2022年10月15日

标准#

Fortran 2003

See also#

selected_int_kind(3), selected_real_kind(3)

achar(3), char(3), ichar(3), iachar(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

selected_int_kind#

名称#

selected_int_kind(3) - [KIND] 选择整数种类

Synopsis#

    result = selected_int_kind(r)
    integer function selected_int_kind(r)

     integer(kind=KIND),intent(in) :: r

Characteristics#

  • r is an integer scalar.

  • the result is an default integer scalar.

说明#

selected_int_kind(3) return the kind value of the smallest integer type that can represent all values ranging from -10**r (exclusive) to 10**r (exclusive). If there is no integer kind that accommodates this range, selected_int_kind returns -1.

选项#

  • r

    The value specifies the required range of powers of ten that need supported by the kind type being returned.

结果#

The result has a value equal to the value of the kind type parameter of an integer type that represents all values in the requested range.

if no such kind type parameter is available on the processor, the result is -1.

If more than one kind type parameter meets the criterion, the value returned is the one with the smallest decimal exponent range, unless there are several such values, in which case the smallest of these kind values is returned.

示例#

示例程序:

program demo_selected_int_kind
implicit none
integer,parameter :: k5 = selected_int_kind(5)
integer,parameter :: k15 = selected_int_kind(15)
integer(kind=k5) :: i5
integer(kind=k15) :: i15

    print *, huge(i5), huge(i15)

    ! the following inequalities are always true
    print *, huge(i5) >= 10_k5**5-1
    print *, huge(i15) >= 10_k15**15-1
end program demo_selected_int_kind

结果:

  >   2147483647  9223372036854775807
  >  T
  >  T

标准#

Fortran 95

另见#

aint(3), anint(3), int(3), nint(3), ceiling(3), floor(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

selected_real_kind#

名称#

selected_real_kind(3) - [KIND] 选择实数种类

Synopsis#

    result = selected_real_kind([p] [,r] [,radix] )
    integer function selected_int_kind(r)

     real(kind=KIND),intent(in),optional :: p
     real(kind=KIND),intent(in),optional :: r
     real(kind=KIND),intent(in),optional :: radix

Characteristics#

  • p is an integer scalar

  • r is an integer scalar

  • radix is an integer scalar

  • the result is an default integer scalar

说明#

selected_real_kind(3) return the kind value of a real data type with decimal precision of at least p digits, exponent range of at least r, and with a radix of radix. That is, if such a kind exists

+ it has the decimal precision as returned by **precision**(3) of at
  least **p** digits.
+ a decimal exponent range, as returned by the function **range**(3)
  of at least **r**
+ a radix, as returned by the function **radix**(3) , of **radix**,

If the requested kind does not exist, -1 is returned.

At least one argument shall be present.

选项#

  • p

    the requested precision

  • r

    the requested range

  • radix

    the desired radix

    Fortran 2008 之前,至少应存在参数 rp 之一;从 Fortran 2008 开始,如果不存在,则假定它们为零。

结果#

selected_real_kind returns the value of the kind type parameter of a real data type with decimal precision of at least p digits, a decimal exponent range of at least R, and with the requested radix.

If p or r is absent, the result value is the same as if it were present with the value zero.

If the radix parameter is absent, there is no requirement on the radix of the selected kind and real kinds with any radix can be returned.

If more than one real data type meet the criteria, the kind of the data type with the smallest decimal precision is returned. If no real data type matches the criteria, the result is

  • -1

    if the processor does not support a real data type with a precision greater than or equal to p, but the r and radix requirements can be fulfilled

  • -2

    if the processor does not support a real type with an exponent range greater than or equal to r, but p and radix are fulfillable

  • -3

    if radix but not p and r requirements are fulfillable

  • -4

    if radix and either p or r requirements are fulfillable

  • -5

    if there is no real type with the given radix

示例#

示例程序:

program demo_selected_real_kind
implicit none
integer,parameter :: p6 = selected_real_kind(6)
integer,parameter :: p10r100 = selected_real_kind(10,100)
integer,parameter :: r400 = selected_real_kind(r=400)
real(kind=p6) :: x
real(kind=p10r100) :: y
real(kind=r400) :: z

   print *, precision(x), range(x)
   print *, precision(y), range(y)
   print *, precision(z), range(z)
end program demo_selected_real_kind

结果:

  >            6          37
  >           15         307
  >           18        4931

标准#

Fortran 95 ; with RADIX - Fortran 2008

另见#

precision(3), range(3), radix(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost