使用协数组和协索引数组进行并行编程#
co_broadcast#
名称#
co_broadcast(3) - [集体操作] 将值复制到当前图像集的所有图像
摘要#
call co_broadcast(a, source_image [,stat] [,errmsg] )
特性#
描述#
co_broadcast(3) 将图像索引为 source_image 的图像上参数 a 的值复制到当前团队中的所有图像。a 就像通过内在赋值一样被定义。如果执行成功且 stat 存在,则将其赋值为零。如果执行失败,则 stat 被赋值为非零值,并且如果存在,则 errmsg 被赋值为描述发生的错误的值。
选项#
- 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 内在函数描述
co_lbound#
名称#
co_lbound(3) - [集体操作] 数组的较低协维度边界
摘要#
result = co_lbound( coarray [,dim] [,kind] )
特性#
描述#
co_lbound(3) 返回协数组的较低边界,或沿 dim 协维度的一个较低协边界。
选项#
- array
应为任何类型的协数组。
- dim
(可选) 应为标量整数。
- kind
(可选) 指示结果的种类参数的整数初始化表达式。
结果#
返回值的类型为整数,种类为 kind。如果 kind 缺失,则返回值为默认整数种类。如果 dim 缺失,则结果为coarray的较低协边界的数组。如果 dim 存在,则结果为对应于该协维度上数组的较低协边界的标量。
标准#
Fortran 2008
另请参阅#
fortran-lang 内在函数描述
co_max#
名称#
co_max(3) - [集体操作] 当前图像集上的最大值
摘要#
call co_max(a, result_image [,stat] [,errmsg] )
特性#
描述#
co_max(3) 在当前团队的所有图像上逐元素确定 a 的最大值。如果 result_image 存在,则最大值仅在指定的图像上的 a 中返回,并且其他图像上的 a 的值变为未定义。如果 result_image 不存在,则在所有图像上返回该值。如果执行成功且 stat 存在,则将其赋值为零。如果执行失败,则 stat 被赋值为非零值,并且如果存在,则 errmsg 被赋值为描述发生的错误的值。
选项#
- 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 内在函数描述
co_min#
名称#
co_min(3) - [集体操作] 当前图像集上的最小值
摘要#
call co_min(a, result_image [,stat] [,errmsg] )
特性#
描述#
co_min(3) 在当前团队的所有图像上逐元素确定 a 的最小值。如果 result_image 存在,则最小值仅在指定的图像上的 a 中返回,并且其他图像上的 a 的值变为未定义。如果 result_image 不存在,则在所有图像上返回该值。如果执行成功且 stat 存在,则将其赋值为零。如果执行失败,则 stat 被赋值为非零值,并且如果存在,则 errmsg 被赋值为描述发生的错误的值。
选项#
- 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 内在函数描述
co_reduce#
名称#
co_reduce(3) - [集体操作] 当前图像集上值的规约
摘要#
call co_reduce(a, operation, result_image [,stat] [,errmsg] )
特性#
描述#
co_reduce(3) 在当前团队的所有图像上逐元素确定 a 的值的规约。作为 operation 传递的纯函数用于通过将不同图像的 a 的值或此类规约的结果值作为参数传递来成对规约 a 的值。如果 a 是数组,则规约将逐元素进行。如果 result_image 存在,则结果值仅在指定的图像上的 a 中返回,并且其他图像上的 a 的值变为未定义。如果 result_image 不存在,则在所有图像上返回该值。如果执行成功且 stat 存在,则将其赋值为零。如果执行失败,则 stat 被赋值为非零值,并且如果存在,则 errmsg 被赋值为描述发生的错误的值。
选项#
- a
是intent(inout)参数,并且应是非多态的。如果它是可分配的,则应已分配;如果它是指针,则应已关联。a在团队的所有镜像上应具有相同类型和类型参数;如果它是数组,则在所有镜像上应具有相同的形状。
- 操作
具有两个标量不可分配参数的纯函数,这些参数应是非多态的,并与a具有相同类型和类型参数。该函数应返回与a具有相同类型和类型参数的不可分配标量。该函数在所有镜像上应相同,并且关于参数在数学上是可交换的和结合的。请注意,除非OPERATION是内在函数,否则它可能不是元素级的。
- 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
注意#
虽然原则上规则允许使用内在函数,但标准中的任何内在函数都不满足具有特定函数的标准,该函数接受两个相同类型的参数并返回该类型作为结果。
标准#
TS 18508
另请参见#
co_min(3),co_max(3),co_sum(3),co_broadcast(3)
fortran-lang 内在函数描述
co_sum#
名称#
co_sum(3) - [集体] 当前一组镜像上的值的总和
概要#
call co_sum(a, result_image [,stat] [,errmsg] )
特征#
描述#
co_sum(3) 将当前团队所有镜像上a的每个元素的值加起来。
如果存在result_image,则仅在指定的镜像上将求和后的值返回到a中,并且其他镜像上a的值将变得未定义。
如果不存在result_image,则在所有镜像上返回该值。如果执行成功并且存在stat,则将其赋值为零。如果执行失败,则stat将被赋值为非零值,并且如果存在,errmsg将被赋值为描述发生的错误的值。
选项#
- 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 内在函数描述
co_ubound#
名称#
co_ubound(3) - [集体] 数组的上共维边界
概要#
result = co_ubound(coarray [,dim] [,kind] )
特征#
描述#
co_ubound(3) 返回共数组的上共边界,或沿着dim共维的单个上共边界。
选项#
- array
应为任何类型的协数组。
- dim
(可选) 应为标量整数。
- kind
(可选) 指示结果的种类参数的整数初始化表达式。
结果#
返回值的类型为整数,种类为 kind。如果 kind 缺失,则返回值为默认整数种类。如果 dim 缺失,则结果为coarray的较低协边界的数组。如果 dim 存在,则结果为对应于该协维度上数组的较低协边界的标量。
标准#
Fortran 2008
另请参见#
co_lbound(3),lbound(3),ubound(3)
fortran-lang 内在函数描述
event_query#
名称#
event_query(3) - [集体] 查询共数组事件是否已发生
概要#
call event_query(event, count [,stat] )
特征#
描述#
event_query(3) 将已发布到event变量但尚未通过调用event_wait删除的事件数量分配给count。当stat存在且调用成功时,将其赋值为0。如果它存在且调用失败,则将其赋值为正值,并且count将被赋值为-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
另请参见#
fortran-lang 内在函数描述
image_index#
名称#
image_index(3) - [集体] 共下标到镜像索引的转换
概要#
result = image_index(coarray, sub)
特征#
描述#
image_index(3) 返回属于共下标的镜像索引。
选项#
- coarray
任何类型的共数组。
- sub
大小等于coarray的共秩的默认整数秩1数组。
结果#
默认整数标量,其值为对应于共下标的镜像索引。对于无效的共下标,结果为零。
示例#
示例程序
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
另请参见#
fortran-lang 内在函数描述
num_images#
名称#
num_images(3) - [集体] 镜像数量
概要#
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
特征#
team和team_number的使用是互斥的
team是来自内在模块ISO_FORTRAN_ENV的TEAM_TYPE类型的标量。
team_number是integer标量。
结果是默认integer标量。
描述#
num_images(3) 返回镜像的数量。
选项#
- team
应为来自内在模块ISO_FORTRAN_ENV的TEAM_TYPE类型的标量,其值为标识当前团队或祖先团队的值。
- team_number
标识初始团队或其父级与当前团队相同的团队。
结果#
指定团队中镜像的数量,或者如果未指定团队,则为当前团队中的镜像数量。
示例#
示例程序
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。使用DISTANCE或FAILED参数,TS 18508
另请参见#
fortran-lang 内在描述(许可证:MIT)@urbanjost
this_image#
名称#
this_image(3) - [集体] 此镜像的共下标索引
概要#
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
特征#
指定为**的类型可以是该类型支持的任何类型
coarray可以是任何类型。如果存在dim,则需要它。
distance不允许与coarray一起使用
如果存在dim,则需要coarray。
描述#
this_image(3) 返回此镜像的共下标。
选项#
- distance
非负标量integer(不允许与coarray一起使用)。
- coarray
如果存在dim,则需要它。
- dim
如果存在,dim应在1到coarray的共秩之间。
结果#
默认整数。如果不存在coarray,则它是标量;如果不存在distance或其值为0,则其值为调用镜像上当前团队的镜像索引,对于小于或等于初始团队距离的值,它返回祖先团队上的镜像索引,该祖先团队与调用团队的距离为distance。如果distance大于到初始团队的距离,则返回初始团队的镜像索引。否则,当存在coarray时,如果不存在dim,则返回一个秩为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。使用DISTANCE参数,TS 18508
另请参见#
fortran-lang 内在函数描述
atomic_and#
名称#
atomic_and(3) - [ATOMIC:BIT MANIPULATION] 原子位与运算
概要#
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
特征#
atom 是一个标量共数组或共索引变量,其整数类型具有 atomic_int_kind 种类。
value 是与 atom 类型相同的标量。如果种类不同,则将值转换为 atom 的种类。
stat 是一个标量默认种类整数变量。
描述#
atomic_and(3) 原子地将 atom 定义为 atom 和 value 值之间的按位与运算结果。当 stat 存在且调用成功时,它被赋值为 0。如果它存在且调用失败,则它被赋值为一个正值;特别是对于共索引 atom,如果远程映像已停止,则它被赋值为 iso_fortran_env 的 stat_stopped_image 值,如果远程映像已失败,则被赋值为 stat_failed_image 值。
选项#
- atom
具有 atomic_int_kind 种类的整数类型的标量共数组或共索引变量。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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 内在函数描述
atomic_fetch_and#
名称#
atomic_fetch_and(3) - [ATOMIC:BIT MANIPULATION] 具有先验获取的原子位与运算
概要#
call atomic_fetch_and(atom, value, old [,stat] )
subroutine atomic_fetch_and(atom, value, old, stat)
特征#
描述#
atomic_fetch_and(3) 原子地将 atom 的值存储到 old 中,并将 atom 定义为 atom 和 value 值之间的按位与运算结果。当 stat 存在且调用成功时,它被赋值为 0。如果它存在且调用失败,则它被赋值为一个正值;特别是对于共索引 atom,如果远程映像已停止,则它被赋值为 iso_fortran_env 的 stat_stopped_image 值,如果远程映像已失败,则被赋值为 stat_failed_image 值。
选项#
- atom
具有 atomic_int_kind 种类的整数类型的标量共数组或共索引变量。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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),
fortran-lang 内在函数描述
atomic_fetch_or#
名称#
atomic_fetch_or(3) - [ATOMIC:BIT MANIPULATION] 具有先验获取的原子位或运算
概要#
call atomic_fetch_or(atom, value, old [,stat] )
subroutine atomic_fetch_or(atom, value, old, stat)
特征#
描述#
atomic_fetch_or(3) 原子地将 atom 的值存储到 old 中,并将 atom 定义为 atom 和 value 值之间的按位或运算结果。当 stat 存在且调用成功时,它被赋值为 0。如果它存在且调用失败,则它被赋值为一个正值;特别是对于共索引 atom,如果远程映像已停止,则它被赋值为 iso_fortran_env 的 stat_stopped_image 值,如果远程映像已失败,则被赋值为 stat_failed_image 值。
选项#
- atom
具有 atomic_int_kind 种类的整数类型的标量共数组或共索引变量。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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),
fortran-lang 内在函数描述
atomic_fetch_xor#
名称#
atomic_fetch_xor(3) - [ATOMIC:BIT MANIPULATION] 具有先验获取的原子位异或运算
概要#
call atomic_fetch_xor (atom, value, old [,stat] )
subroutine atomic_fetch_xor (atom, value, old, stat)
特征#
描述#
atomic_fetch_xor(3) 原子地将 atom 的值存储到 old 中,并将 atom 定义为 atom 和 value 值之间的按位异或运算结果。当 stat 存在且调用成功时,它被赋值为 0。如果它存在且调用失败,则它被赋值为一个正值;特别是对于共索引 atom,如果远程映像已停止,则它被赋值为 iso_fortran_env 的 stat_stopped_image 值,如果远程映像已失败,则被赋值为 stat_failed_image 值。
选项#
- atom
具有 atomic_int_kind 种类的整数类型的标量共数组或共索引变量。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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),
fortran-lang 内在函数描述
atomic_or#
名称#
atomic_or(3) - [ATOMIC:BIT MANIPULATION] 原子位或运算
概要#
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
特征#
atom 是一个标量共数组或共索引变量,其整数类型具有 atomic_int_kind 种类。
value 是与 atom 类型相同的标量。如果种类不同,则将值转换为 atom 的种类。
stat 是一个标量默认种类整数变量。
描述#
atomic_or(3) 原子地将 atom 定义为 atom 和 value 值之间的按位或运算结果。当 stat 存在且调用成功时,它被赋值为 0。如果它存在且调用失败,则它被赋值为一个正值;特别是对于共索引 atom,如果远程映像已停止,则它被赋值为 iso_fortran_env 的 stat_stopped_image 值,如果远程映像已失败,则被赋值为 stat_failed_image 值。
选项#
- atom
具有 atomic_int_kind 种类的整数类型的标量共数组或共索引变量。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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),
fortran-lang 内在函数描述
atomic_xor#
名称#
atomic_xor(3) - [ATOMIC:BIT MANIPULATION] 原子位异或运算
概要#
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
特征#
atom 是一个标量共数组或共索引变量,其整数类型具有 atomic_int_kind 种类。
value 是与 atom 类型相同的标量。如果种类不同,则将值转换为 atom 的种类。
stat 是一个标量默认种类整数变量。
特征#
描述#
atomic_xor(3) 原子地将 atom 定义为 atom 和 value 值之间的按位异或运算结果。当 stat 存在且调用成功时,它被赋值为 0。如果它存在且调用失败,则它被赋值为一个正值;特别是对于共索引 atom,如果远程映像已停止,则它被赋值为 iso_fortran_env 的 stat_stopped_image 值,如果远程映像已失败,则被赋值为 stat_failed_image 值。
选项#
- atom
具有 atomic_int_kind 种类的整数类型的标量共数组或共索引变量。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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 内在函数描述
atomic_add#
名称#
atomic_add(3) - [ATOMIC] 原子加法运算
概要#
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
特征#
atom 是一个标量共数组或共索引变量,其整数类型具有 atomic_int_kind 种类。
value 是与 atom 类型相同的标量。如果种类不同,则将值转换为 atom 的种类。
stat 是一个标量默认种类整数变量。
描述#
atomic_add(3) 原子地将 VAR 的值加到变量 atom 上。当 stat 存在且调用成功时,它被赋值为 0。如果它存在且调用失败,则它被赋值为一个正值;特别是对于共索引 ATOM,如果远程映像已停止,则它被赋值为 iso_fortran_env 的 STAT_STOPPED_IMAGE 值,如果远程映像已失败,则被赋值为 STAT_FAILED_IMAGE 值。
选项#
- atom
具有 atomic_int_kind 种类的整数类型的标量共数组或共索引变量。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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 内在函数描述
atomic_cas#
名称#
atomic_cas(3) - [ATOMIC] 原子比较并交换
概要#
call atomic_cas (atom, old, compare, new [,stat] )
subroutine atomic_cas (atom, old, compare, new, stat)
特性#
描述#
atomic_cas(3) 将变量atom与compare的值进行比较;如果值相同,则将atom设置为new的值。此外,old将设置为用于比较的atom的值。当stat存在且调用成功时,它被赋予值0。如果它存在且调用失败,则被赋予一个正值;特别是,对于一个共索引的atom,如果远程映像已停止,则被赋予iso_fortran_env的stat_stopped_image的值,如果远程映像已失败,则被赋予stat_failed_image的值。
选项#
- atom
标量共数组或共索引变量,其类型为具有atomic_int_kind类型的整数类型或具有atomic_logical_kind类型的逻辑类型。
- 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 内在函数描述
atomic_define#
名称#
atomic_define(3) - [ATOMIC] 原子地设置变量
概要#
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
特性#
- atom
标量共数组或共索引变量,其类型为具有atomic_int_kind类型的整数类型或具有atomic_logical_kind类型的逻辑类型。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 atom 的种类。
- stat
(可选) 标量默认种类整数变量。
描述#
atomic_define(3) 原子地将变量atom定义为value的值。
选项#
- atom
标量共数组或共索引变量,用于原子地将值value赋予它。种类。
- value
要赋予atom的值
- stat
当stat存在且调用成功时,它被赋予值0。如果它存在且调用失败,则被赋予一个正值;特别是,对于一个共索引的atom,如果远程映像已停止,则被赋予iso_fortran_env的stat_stopped_image的值,如果远程映像已失败,则被赋予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;带有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 内在函数描述
atomic_fetch_add#
名称#
atomic_fetch_add(3) - [ATOMIC] 具有先验获取的原子ADD操作
概要#
call atomic_fetch_add(atom, value, old [,stat] )
subroutine atomic_fetch_add(atom, value, old, stat)
特性#
描述#
atomic_fetch_add(3) 原子地将atom的值存储在old中,并将var的值添加到变量atom中。当stat存在且调用成功时,它被赋予值0。如果它存在且调用失败,则被赋予一个正值;特别是,对于一个共索引的atom,如果远程映像已停止,则被赋予iso_fortran_env的stat_stopped_image的值,如果远程映像已失败,则被赋予stat_failed_image的值。
选项#
- atom
标量共数组或共索引变量,其类型为具有atomic_int_kind类型的整数类型。atomic_logical_kind种类。
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 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),
fortran-lang 内在函数描述
atomic_ref#
名称#
atomic_ref(3) - [ATOMIC] 原子地获取变量的值
概要#
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
特性#
atom是标量共数组或共索引变量,其类型为具有atomic_int_kind类型的整数类型或具有atomic_logical_kind类型的逻辑类型。
value 是与 atom 类型相同的标量。如果种类不同,则将值转换为 atom 的种类。
stat 是一个标量默认种类整数变量。
描述#
atomic_ref(3) 原子地将变量atom的值赋予value。当stat存在且调用成功时,它被赋予值0。如果它存在且调用失败,则被赋予一个正值;特别是,对于一个共索引的atom,如果远程映像已停止,则被赋予iso_fortran_env的stat_stopped_image的值,如果远程映像已失败,则被赋予stat_failed_image的值。
选项#
- value
与 atom 类型相同的标量。如果种类不同,则将值转换为 atom 的种类。
- atom
标量共数组或共索引变量,其类型为具有atomic_int_kind类型的整数类型或具有atomic_logical_kind类型的逻辑类型。
- 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;带有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 内在函数描述