使用 co_arrays 和 co_indexed 数组进行并行编程#

co_broadcast#

名称#

co_broadcast(3) - [COLLECTIVE] 将值从当前镜像复制到所有镜像

Synopsis#

    call co_broadcast(a, source_image [,stat] [,errmsg] )

Characteristics#

说明#

co_broadcast(3) copies the value of argument a on the image with image index source_image to all images in the current team. a becomes defined as if by intrinsic assignment. If the execution was successful and stat is present, it is assigned the value zero. If the execution failed, stat gets assigned a nonzero value and, if present, errmsg gets assigned a value describing the occurred error.

选项#

  • a

    intent(inout) 参数;在当前组的所有镜像上应具有相同的动态类型和类型参数。如果它是一个数组,它应该在所有镜像上具有相同的形状。

  • source_image

    一个标量整数表达式。它在所有镜像上应具有相同的值,并引用当前组的镜像。

  • stat

    (可选)标量整数变量

  • errmsg

    (可选)一个标量字符变量

示例#

示例程序:

program demo_co_broadcast
implicit none
integer :: val(3)
   if (this_image() == 1) then
      val = [1, 5, 3]
   endif
   call co_broadcast (val, source_image=1)
   print *, this_image(), ":", val
end program demo_co_broadcast

标准#

Fortran xx

另见#

co_max(3), co_min(3), co_sum(3), co_reduce(3)

fortran-lang intrinsic descriptions

co_lbound#

名称#

co_lbound(3) - [COLLECTIVE] 数组的下维数边界

Synopsis#

     result = co_lbound( coarray [,dim] [,kind] )

Characteristics#

说明#

co_lbound(3) returns the lower bounds of a coarray, or a single lower cobound along the dim codimension.

选项#

  • 数组

    应为任何类型的coarray。

  • 暗淡

    (可选)应为标量 _ 整数 _。

  • 种类

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

结果#

返回值的类型为_integer_,种类为kind。如果没有指定kind,则返回值为默认的整型。如果没有指定dim,则结果是corray的下限数组。如果指定了dim,则结果是对应于数组沿该维的下限的标量。

标准#

Fortran 2008

另见#

co_ubound(3)lbound(3)

fortran-lang intrinsic descriptions

co_max#

名称#

co_max(3) - [集合] 当前镜像集上的最大值

Synopsis#

     call co_max(a, result_image [,stat] [,errmsg] )

Characteristics#

说明#

co_max(3) determines element-wise the maximal value of a on all images of the current team. If result_image is present, the maximum values are returned in a on the specified image only and the value of a on the other images become undefined. If result_image is not present, the value is returned on all images. If the execution was successful and stat is present, it is assigned the value zero. If the execution failed, stat gets assigned a nonzero value and, if present, errmsg gets assigned a value describing the occurred error.

选项#

  • a

    应为整数,实数或字符变量,在并行的所有镜像上具有相同的类型和类型参数。

  • result_image

    (可选)一个标量整型表达式;如果存在,则在所有镜像上具有相同的值并指为并行中的一个镜像。

  • stat

    (可选)标量整数变量

  • errmsg

    (可选)一个标量字符变量

示例#

示例程序:

program demo_co_max
implicit none
integer :: val
   val = this_image()
   call co_max(val, result_image=1)
   if (this_image() == 1) then
     write(*,*) "Maximal value", val  ! prints num_images()
   endif
end program demo_co_max

结果:

    Maximal value           2

标准#

TS 18508

另见#

co_min(3), co_sum(3), co_reduce(3), co_broadcast(3)

fortran-lang intrinsic descriptions

co_min#

名称#

co_min(3) - [集合]当前镜像集上的最小值

Synopsis#

     call co_min(a, result_image [,stat] [,errmsg] )

Characteristics#

说明#

co_min(3) determines element-wise the minimal value of a on all images of the current team. If result_image is present, the minimal values are returned in a on the specified image only and the value of a on the other images become undefined. If result_image is not present, the value is returned on all images. If the execution was successful and stat is present, it is assigned the value zero. If the execution failed, stat gets assigned a nonzero value and, if present, errmsg gets assigned a value describing the occurred error.

选项#

  • a

    应为整数,实数或字符变量,在并行的所有镜像上具有相同的类型和类型参数。

  • result_image

    (可选)一个标量整型表达式;如果存在,则在所有镜像上具有相同的值并指为并行中的一个镜像。

  • stat

    (可选)标量整数变量

  • errmsg

    (可选)一个标量字符变量

示例#

示例程序:

program demo_co_min
implicit none
integer :: val
   val = this_image()
   call co_min(val, result_image=1)
   if (this_image() == 1) then
     write(*,*) "Minimal value", val  ! prints 1
   endif
end program demo_co_min

标准#

TS 18508

另见#

co_max(3), co_sum(3), co_reduce(3), co_broadcast(3)

fortran-lang intrinsic descriptions

co_reduce#

名称#

co_reduce(3) - [集合] 缩减当前镜像集上的值

Synopsis#

    call co_reduce(a, operation, result_image [,stat] [,errmsg] )

Characteristics#

说明#

co_reduce(3) determines element-wise the reduction of the value of a on all images of the current team. The pure function passed as operation is used to pairwise reduce the values of a by passing either the value of a of different images or the result values of such a reduction as argument. If a is an array, the reduction is done element wise. If result_image is present, the result values are returned in a on the specified image only and the value of a on the other images become undefined. If result_image is not present, the value is returned on all images. If the execution was successful and stat is present, it is assigned the value zero. If the execution failed, stat gets assigned a nonzero value and, if present, errmsg gets assigned a value describing the occurred error.

选项#

  • a

    是**intent(inout)**参数,并且应该是非多态的。如果是动态数组,则应该已经分配;如果是指针,则应该已经关联。a在并行的所有镜像上应具有相同的类型和类型参数;如果是数组,则在所有镜像上应具有相同的维度。

  • operation

    具有两个标量不可分配参数的纯函数应该是非多态的并且具有与 a 相同的类型和类型参数。该函数应返回与 a 相同类型和类型参数的不可分配标量。该函数在所有镜像上以及在数学上关于自变量的可交换性和关联性方面应相同。请注意,操作可能不是基元的,除非它是内置函数。

  • result_image

    (可选)一个标量整型表达式;如果存在,则在所有镜像上具有相同的值并指为并行中的一个镜像。

  • stat

    (可选)标量整数变量

  • errmsg

    (可选)一个标量字符变量

示例#

示例程序:

program demo_co_reduce
implicit none
integer :: val

   val = this_image()
   call co_reduce(val, myprod, 1)
   if (this_image() == 1) then
      write(*,*) "Product value", val  ! prints num_images() factorial
   endif

contains

pure function myprod(a, b)
   integer, value :: a, b
   integer :: myprod
   myprod = a * b
end function myprod

end program demo_co_reduce

Note#

虽然规则原则上允许使用内部函数,但标准的内部函数都不满足具有特定函数的标准,该特定函数接受相同类型的两个参数并返回该类型。

标准#

TS 18508

另见#

co_min(3), co_max(3), co_sum(3), co_broadcast(3)

fortran-lang intrinsic descriptions

co_sum#

名称#

co_sum(3) - [集合] 当前镜像集上的值之和

Synopsis#

    call co_sum(a, result_image [,stat] [,errmsg] )

Characteristics#

说明#

co_sum(3) sums up the values of each element of a on all images of the current team.

If result_image is present, the summed-up values are returned in a on the specified image only and the value of a on the other images become undefined.

If result_image is not present, the value is returned on all images. If the execution was successful and stat is present, it is assigned the value zero. If the execution failed, stat gets assigned a nonzero value and, if present, errmsg gets assigned a value describing the occurred error.

选项#

  • a

    应为整数、实数或复数变量,在编队的所有镜像上具有相同的类型和种类参数。

  • result_image

    (可选)一个标量整型表达式;如果存在,则在所有镜像上具有相同的值并指为并行中的一个镜像。

  • stat

    (可选)标量整数变量

  • errmsg

    (可选)一个标量字符变量

示例#

示例程序:

program demo_co_sum
implicit none
integer :: val
   val = this_image()
   call co_sum(val, result_image=1)
   if (this_image() == 1) then
      ! prints (n**2 + n)/2, with n = num_images()
      write(*,*) "The sum is ", val
   endif
end program demo_co_sum

结果:

    The sum is            1

标准#

TS 18508

另见#

co_max(3), co_min(3), co_reduce(3), co_broadcast(3)

fortran-lang intrinsic descriptions

co_ubound#

名称#

co_ubound(3) - [集合] co_array的上界

Synopsis#

    result = co_ubound(coarray [,dim] [,kind] )

Characteristics#

说明#

co_ubound(3) returns the upper cobounds of a coarray, or a single upper cobound along the dim codimension.

选项#

  • 数组

    应为任何类型的coarray。

  • 暗淡

    (可选)应为标量 _ 整数 _。

  • 种类

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

结果#

返回值的类型为_integer_,种类为kind。如果没有指定kind,则返回值为默认的整型。如果没有指定dim,则结果是corray的下限数组。如果指定了dim,则结果是对应于数组沿该维的下限的标量。

标准#

Fortran 2008

另见#

co_lbound(3), lbound(3), ubound(3)

fortran-lang intrinsic descriptions

event_query#

名称#

event_query(3) - [集合] 查询是否已发生coarray事件

Synopsis#

    call event_query(event, count [,stat] )

Characteristics#

说明#

event_query(3) assigns the number of events to count which have been posted to the event variable and not yet been removed by calling event_wait. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value and count is assigned the value -1.

选项#

  • event

    (intent(in)) 在iso_fortran_env中定义的 event_type类型的标量不应编入共索引。

  • count

    (intent(out)) 精度至少为默认 integer 的标量整数。

  • stat

    (可选) 默认种类 integer 标量变量.

示例#

示例程序:

program demo_event_query
use iso_fortran_env
implicit none
type(event_type) :: event_value_has_been_set[*]
integer :: cnt
   if (this_image() == 1) then
      call event_query(event_value_has_been_set, cnt)
      if (cnt > 0) write(*,*) "Value has been set"
   elseif (this_image() == 2) then
      event post(event_value_has_been_set[1])
   endif
end program demo_event_query

标准#

TS 18508

See also#

****(3)

fortran-lang intrinsic descriptions

image_index#

名称#

image_index(3) - [集合] 下标到镜像索引的转换

Synopsis#

    result = image_index(coarray, sub)

Characteristics#

说明#

image_index(3) returns the image index belonging to a cosubscript.

选项#

  • coarray

    任意类型的coarray.

  • sub

    默认为整数一维数组,大小等于coarray的维度。

结果#

标量默认整数,其镜像索引值与子下标相对应。对于无效的子下标,结果为零。

示例#

示例程序:

program demo image_index
implicit none
integer :: array[2,-1:4,8,*]
   ! Writes  28 (or 0 if there are fewer than 28 images)
   write (*,*) image_index(array, [2,0,3,1])
end demo image_index

标准#

Fortran 2008

另见#

this_image(3), num_images(3)

fortran-lang intrinsic descriptions

num_images#

名称#

num_images(3) - [集合] 镜像的数量

Synopsis#

    result = num_images([team|team_number])
     integer function num_images (team)

      type(TEAM_TYPE),intent(in),optional    :: team
      integer(kind=KIND),intent(in),optional :: team_number

Characteristics#

  • use of team and team_number is mutually exclusive

  • team is is a scalar of of type TEAM_TYPE from the intrinsic module ISO_FORTRAN_ENV.

  • team_number is an integer scalar.

  • the result is a default integer scalar.

说明#

num_images(3) Returns the number of images.

选项#

  • team

    shall be a scalar of type TEAM_TYPE from the intrinsic module ISO_FORTRAN_ENV, with a value that identifies the current or an ancestor team.

  • team_number

    identifies the initial team or a team whose parent is the same as that of the current team.

结果#

The number of images in the specified team, or in the current team if no team is specified.

示例#

示例程序:

program demo_num_images
implicit none
integer :: value[*]
real    :: p[*]
integer :: i

   value = this_image()
   sync all
   if (this_image() == 1) then
     do i = 1, num_images()
       write(*,'(2(a,i0))') 'value[', i, '] is ', value[i]
     end do
   endif

 ! The following code uses image 1 to read data and
 ! broadcast it to other images.
   if (this_image()==1) then
      p=1234.5678
      do i = 2, num_images()
         p[i] = p
      end do
   end if
   sync all

end program demo_num_images

标准#

Fortran 2008 . With DISTANCE or FAILED argument, TS 18508

另见#

this_image(3), image_index(3)

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

this_image#

名称#

this_image(3) - [COLLECTIVE] 此镜像的下标索引

Synopsis#

result = this_image() | = this_image(distance) | = this_image(coarray,dim)
   integer function this_image( distance ,coarray, dim )

    type(TYPE(kind=**),optional :: coarray[*]
    integer,intent(in),optional :: distance
    integer,intent(in),optional :: dim

Characteristics#

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

  • coarray can be of any type. If dim is present it is required.

  • distance is not permitted together with coarray

  • if dim if present, coarray is required.

说明#

this_image(3) returns the cosubscript for this image.

选项#

  • distance

    Nonnegative scalar integer (not permitted together with coarray).

  • coarray

    if dim present, required).

  • 暗淡

    If present, dim shall be between one and the corank of coarray.

结果#

默认整数。如果 coarray 不存在,它是标量;如果 distance 不存在或值为 0,它的值是当前团队调用图像上的镜像索引,对于与初始团队的距离更小或相等的值,它返回镜像索引与调用团队距离距离的祖先团队。如果距离大于到初始团队的距离,则返回初始团队的镜像索引。否则,当 coarray 存在时,如果 dim 不存在,则返回具有 corank 元素的 rank-1 数组,其中包含指定调用镜像的 coarray 的共同下标。如果存在 dim,则返回一个标量,其中包含 this_image(coarray)dim 元素的值。

示例#

示例程序:

program demo_this_image
implicit none
integer :: value[*]
integer :: i
   value = this_image()
   sync all
   if (this_image() == 1) then
      do i = 1, num_images()
         write(*,'(2(a,i0))') 'value[', i, '] is ', value[i]
      end do
   endif
end program demo_this_image

结果:

   value[1] is 1

标准#

Fortran 2008. With DISTANCE argument, TS 18508

另见#

num_images(3), image_index(3)

fortran-lang intrinsic descriptions

atomic_and#

名称#

atomic_and(3) - [ATOMIC:BIT MANIPULATION] 原子按位与运算

Synopsis#

    call atomic_and(atom, value [,stat])
     subroutine atomic_and(atom,value,stat)

      integer(atomic_int_kind)            :: atom[*]
      integer(atomic_int_kind),intent(in) :: value
      integer,intent(out),intent(out)     :: stat

Characteristics#

  • atom is a scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value is a scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat is a Scalar default-kind integer variable.

说明#

atomic_and(3) atomically defines atom with the bitwise and between the values of atom and value. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_and
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*]
   call atomic_and(atom[1], int(b'10100011101'))
end program demo_atomic_and

标准#

TS 18508

另见#

atomic_fetch_and(3)atomic_define(3)atomic_ref(3)atomic_cas(3)iso_fortran_env(3),atomic_add(3)atomic_or(3)atomic_xor(3)

fortran-lang intrinsic descriptions

atomic_fetch_and#

名称#

atomic_fetch_and(3) - [ATOMIC:BIT MANIPULATION] 原子按位与操作与先前提取

Synopsis#

    call atomic_fetch_and(atom, value, old [,stat] )
     subroutine atomic_fetch_and(atom, value, old, stat)

Characteristics#

说明#

atomic_fetch_and(3) atomically stores the value of atom in old and defines atom with the bitwise AND between the values of atom and value. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • old

    atom 有相同类型和种类的标量.

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_fetch_and
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*], old
   call atomic_fetch_and (atom[1], int(b'10100011101'), old)
end program demo_atomic_fetch_and

标准#

TS 18508

另见#

atomic_define(3), atomic_and(3), iso_fortran_env(3),

atomic_fetch_add(3), atomic_fetch_or(3),

atomic_fetch_xor(3)

fortran-lang intrinsic descriptions

atomic_fetch_or#

名称#

atomic_fetch_or(3) - [ATOMIC:BIT MANIPULATION] 原子按位或操作与先前提取

Synopsis#

    call atomic_fetch_or(atom, value, old [,stat] )
     subroutine atomic_fetch_or(atom, value, old, stat)

Characteristics#

说明#

atomic_fetch_or(3) atomically stores the value of atom in old and defines atom with the bitwise OR between the values of atom and value. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • old

    atom 有相同类型和种类的标量.

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_fetch_or
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*], old
   call atomic_fetch_or(atom[1], int(b'10100011101'), old)
end program demo_atomic_fetch_or

标准#

TS 18508

另见#

atomic_define(3)atomic_or(3)iso_fortran_env(3)

atomic_fetch_add(3), atomic_fetch_and(3),

atomic_fetch_xor(3)

fortran-lang intrinsic descriptions

atomic_fetch_xor#

名称#

atomic_fetch_xor(3) - [ATOMIC:BIT MANIPULATION] 原子按位异或运算,先取

Synopsis#

    call atomic_fetch_xor (atom, value, old [,stat] )
     subroutine atomic_fetch_xor (atom, value, old, stat)

Characteristics#

说明#

atomic_fetch_xor(3) atomically stores the value of atom in old and defines atom with the bitwise xor between the values of atom and value. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • old

    atom 有相同类型和种类的标量.

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_fetch_xor
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*], old
   call atomic_fetch_xor (atom[1], int(b'10100011101'), old)
end program demo_atomic_fetch_xor

标准#

TS 18508

另见#

atomic_define(3)atomic_xor(3)iso_fortran_env(3)

atomic_fetch_add(3), atomic_fetch_and(3),

atomic_fetch_or(3)

fortran-lang intrinsic descriptions

atomic_or#

名称#

atomic_or(3) - [ATOMIC:BIT MANIPULATION] 原子按位或运算

Synopsis#

    call atomic_or(atom, value [,stat] )
     subroutine atomic_or(atom,value,stat)

      integer(atomic_int_kind)            :: atom[*]
      integer(atomic_int_kind),intent(in) :: value
      integer,intent(out),intent(out)     :: stat

Characteristics#

  • atom is a scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value is a scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat is a Scalar default-kind integer variable.

说明#

atomic_or(3) atomically defines atom with the bitwise or between the values of atom and value. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_or
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*]
   call atomic_or(atom[1], int(b'10100011101'))
end program demo_atomic_or

标准#

TS 18508

另见#

atomic_define(3), atomic_fetch_or(3),

iso_fortran_env(3), atomic_add(3), atomic_or(3),

atomic_xor(3)

fortran-lang intrinsic descriptions

atomic_xor#

名称#

atomic_xor(3) - [ATOMIC:BIT MANIPULATION] 原子按位或运算

Synopsis#

    call atomic_xor(atom, value [,stat] )
     subroutine atomic_xor(atom,value,stat)

      integer(atomic_int_kind)            :: atom[*]
      integer(atomic_int_kind),intent(in) :: value
      integer,intent(out),intent(out)     :: stat

Characteristics#

  • atom is a scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value is a scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat is a Scalar default-kind integer variable.

Characteristics#

说明#

atomic_xor(3) atomically defines atom with the bitwise xor between the values of atom and value. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_xor
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*]
   call atomic_xor(atom[1], int(b'10100011101'))
end program demo_atomic_xor

标准#

TS 18508

另见#

atomic_define(3)atomic_fetch_xor(3)iso_fortran_env(3)atomic_add(3)atomic_or(3)atomic_xor(3)

fortran-lang intrinsic descriptions

atomic_add#

名称#

atomic_add(3) - [ATOMIC] 原子级加操作

Synopsis#

    call atomic_add (atom, value [,stat] )
     subroutine atomic_add(atom,value,stat)

      integer(atomic_int_kind)            :: atom[*]
      integer(atomic_int_kind),intent(in) :: value
      integer,intent(out),intent(out)     :: stat

Characteristics#

  • atom is a scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value is a scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat is a Scalar default-kind integer variable.

说明#

atomic_add(3) atomically adds the value of VAR to the variable atom. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed ATOM, if the remote image has stopped, it is assigned the value of iso_fortran_env’s STAT_STOPPED_IMAGE and if the remote image has failed, the value STAT_FAILED_IMAGE.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_add
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*]
   call atomic_add (atom[1], this_image())
end program demo_atomic_add

标准#

TS 18508

另见#

atomic_define(3)atomic_fetch_add(3)atomic_and(3)atomic_or(3)atomic_xor(3) iso_fortran_env(3),

fortran-lang intrinsic descriptions

atomic_cas#

名称#

atomic_cas(3) - [ATOMIC] 原子级比较和交换

Synopsis#

    call atomic_cas (atom, old, compare, new [,stat] )
     subroutine atomic_cas (atom, old, compare, new, stat)

Characteristics#

说明#

atomic_cas(3) compares the variable atom with the value of compare; if the value is the same, atom is set to the value of new. Additionally, old is set to the value of atom that was used for the comparison. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型或具有 atomic_logical_kind 类型的逻辑类型的标量 coarray 或 coindexed 变量。

  • old

    atom 有相同类型和种类的标量.

  • compare

    atom有相同类型和种类的标量.

  • new

    atom类型相同的标量变量. 如果种类不同, 则转为与 atom相同的种类.

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_cas
use iso_fortran_env
implicit none
logical(atomic_logical_kind) :: atom[*], prev
   call atomic_cas(atom[1], prev, .false., .true.)
end program demo_atomic_cas

标准#

TS 18508

另见#

atomic_define(3), atomic_ref(3), iso_fortran_env(3)

fortran-lang intrinsic descriptions

atomic_define#

名称#

atomic_define(3) - [ATOMIC] 以原子方式设置变量

Synopsis#

    call atomic_define (atom, value [,stat] )
     subroutine atomic_define(atom, value, stat)

      TYPE(kind=atomic_KIND_kind) :: atom[*]
      TYPE(kind=KIND) :: value
      integer,intent(out),optional :: stat

Characteristics#

  • atom

    具有 atomic_int_kind 类型的整数类型或具有 atomic_logical_kind 类型的逻辑类型的标量 coarray 或 coindexed 变量。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • stat

    (可选)标量默认类型整数变量。

说明#

atomic_define(3) defines the variable atom with the value value atomically.

选项#

  • atom

    Scalar coarray or coindexed variable to atomically assign the value value to. kind.

  • value

    value to assign to atom

  • stat

    When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

示例#

示例程序:

program demo_atomic_define
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*]
    call atomic_define(atom[1], this_image())
end program demo_atomic_define

标准#

Fortran 2008 ; with stat, TS 18508

另见#

atomic_ref(3)atomic_cas(3)iso_fortran_env(3),atomic_add(3)atomic_and(3)atomic_or(3)atomic_xor(3)

fortran-lang intrinsic descriptions

atomic_fetch_add#

名称#

atomic_fetch_add(3) - [ATOMIC] 原子 ADD 操作与先前的 fetch

Synopsis#

    call atomic_fetch_add(atom, value, old [,stat] )
     subroutine atomic_fetch_add(atom, value, old, stat)

Characteristics#

说明#

atomic_fetch_add(3) atomically stores the value of atom in old and adds the value of var to the variable atom. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • atom

    具有 atomic_int_kind 类型的整数类型的标量 coarray 或 coindexed 变量。 atomic_logical_kind 种类。

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • old

    atom 有相同类型和种类的标量.

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_fetch_add
use iso_fortran_env
implicit none
integer(atomic_int_kind) :: atom[*], old
   call atomic_add(atom[1], this_image(), old)
end program demo_atomic_fetch_add

标准#

TS 18508

另见#

atomic_define(3)atomic_add(3)iso_fortran_env(3),

atomic_fetch_and(3)atomic_fetch_or(3)

atomic_fetch_xor(3)

fortran-lang intrinsic descriptions

atomic_ref#

名称#

atomic_ref(3) - [ATOMIC] 以原子方式获取变量的值

Synopsis#

    call atomic_ref(value, atom [,stat] )
     subroutine atomic_ref(value,atom,stat)

      integer(atomic_int_kind),intent(in) :: value
      integer(atomic_int_kind)            :: atom[*]
      integer,intent(out),intent(out)     :: stat

Characteristics#

  • atom is a scalar coarray or coindexed variable of either integer type with atomic_int_kind kind or logical type with atomic_logical_kind kind.

  • value is a scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat is a Scalar default-kind integer variable.

说明#

atomic_ref(3) atomically assigns the value of the variable atom to value. When stat is present and the invocation was successful, it is assigned the value 0. If it is present and the invocation has failed, it is assigned a positive value; in particular, for a coindexed atom, if the remote image has stopped, it is assigned the value of iso_fortran_env’s stat_stopped_image and if the remote image has failed, the value stat_failed_image.

选项#

  • value

    atom 类型相同的标量。如果种类不同,则将值转换为原子的种类。

  • atom

    具有 atomic_int_kind 类型的整数类型或具有 atomic_logical_kind 类型的逻辑类型的标量 coarray 或 coindexed 变量。

  • stat

    (可选)标量默认类型整数变量。

示例#

示例程序:

program demo_atomic_ref
use iso_fortran_env
implicit none
logical(atomic_logical_kind) :: atom[*]
logical :: val
   call atomic_ref( val, atom[1] )
   if (val) then
      print *, "Obtained"
   endif
end program demo_atomic_ref

标准#

Fortran 2008 ; with STAT, TS 18508

另见#

atomic_define(3)atomic_cas(3)iso_fortran_env(3)

atomic_fetch_add(3)atomic_fetch_and(3)

atomic_fetch_or(3)atomic_fetch_xor(3)

fortran-lang intrinsic descriptions