Parallel programming using co_arrays and co_indexed arrays#

co_broadcast#

Name#

co_broadcast(3) - [COLLECTIVE] Copy a value to all images the current set of images

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • a

    intent(inout) argument; shall have the same dynamic type and type parameters on all images of the current team. If it is an array, it shall have the same shape on all images.

  • source_image

    a scalar integer expression. It shall have the same the same value on all images and refer to an image of the current team.

  • stat

    (optional) a scalar integer variable

  • errmsg

    (optional) a scalar character variable

Examples#

Sample program:

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

Standard#

Fortran xx

See Also#

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

fortran-lang intrinsic descriptions

co_lbound#

Name#

co_lbound(3) - [COLLECTIVE] Lower codimension bounds of an array

Synopsis#

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

Characteristics#

Description#

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

Options#

  • array

    Shall be an coarray, of any type.

  • dim

    (Optional) Shall be a scalar integer.

  • kind

    (Optional) An integer initialization expression indicating the kind parameter of the result.

Result#

The return value is of type integer and of kind kind. If kind is absent, the return value is of default integer kind. If dim is absent, the result is an array of the lower cobounds of coarray. If dim is present, the result is a scalar corresponding to the lower cobound of the array along that codimension.

Standard#

Fortran 2008

See Also#

co_ubound(3), lbound(3)

fortran-lang intrinsic descriptions

co_max#

Name#

co_max(3) - [COLLECTIVE] Maximal value on the current set of images

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • a

    shall be an integer, real or character variable, which has the same type and type parameters on all images of the team.

  • result_image

    (optional) a scalar integer expression; if present, it shall have the same the same value on all images and refer to an image of the current team.

  • stat

    (optional) a scalar integer variable

  • errmsg

    (optional) a scalar character variable

Examples#

Sample program:

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

Results:

    Maximal value           2

Standard#

TS 18508

See Also#

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

fortran-lang intrinsic descriptions

co_min#

Name#

co_min(3) - [COLLECTIVE] Minimal value on the current set of images

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • a

    shall be an integer, real or character variable, which has the same type and type parameters on all images of the team.

  • result_image

    (optional) a scalar integer expression; if present, it shall have the same the same value on all images and refer to an image of the current team.

  • stat

    (optional) a scalar integer variable

  • errmsg

    (optional) a scalar character variable

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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

fortran-lang intrinsic descriptions

co_reduce#

Name#

co_reduce(3) - [COLLECTIVE] Reduction of values on the current set of images

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • a

    is an intent(inout) argument and shall be nonpolymorphic. If it is allocatable, it shall be allocated; if it is a pointer, it shall be associated. a shall have the same type and type parameters on all images of the team; if it is an array, it shall have the same shape on all images.

  • operation

    pure function with two scalar nonallocatable arguments, which shall be nonpolymorphic and have the same type and type parameters as a. The function shall return a nonallocatable scalar of the same type and type parameters as a. The function shall be the same on all images and with regards to the arguments mathematically commutative and associative. Note that OPERATION may not be an elemental unless it is an intrinsic function.

  • result_image

    (optional) a scalar integer expression; if present, it shall have the same the same value on all images and refer to an image of the current team.

  • stat

    (optional) a scalar integer variable

  • errmsg

    (optional) a scalar character variable

Examples#

Sample program:

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#

While the rules permit in principle an intrinsic function, none of the intrinsics in the standard fulfill the criteria of having a specific function, which takes two arguments of the same type and returning that type as a result.

Standard#

TS 18508

See Also#

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

fortran-lang intrinsic descriptions

co_sum#

Name#

co_sum(3) - [COLLECTIVE] Sum of values on the current set of images

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • a

    shall be an integer, real or complex variable, which has the same type and type parameters on all images of the team.

  • result_image

    (optional) a scalar integer expression; if present, it shall have the same the same value on all images and refer to an image of the current team.

  • stat

    (optional) a scalar integer variable

  • errmsg

    (optional) a scalar character variable

Examples#

Sample program:

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

Results:

    The sum is            1

Standard#

TS 18508

See Also#

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

fortran-lang intrinsic descriptions

co_ubound#

Name#

co_ubound(3) - [COLLECTIVE] Upper codimension bounds of an array

Synopsis#

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

Characteristics#

Description#

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

Options#

  • array

    Shall be an coarray, of any type.

  • dim

    (Optional) Shall be a scalar integer.

  • kind

    (Optional) An integer initialization expression indicating the kind parameter of the result.

Result#

The return value is of type integer and of kind kind. If kind is absent, the return value is of default integer kind. If dim is absent, the result is an array of the lower cobounds of coarray. If dim is present, the result is a scalar corresponding to the lower cobound of the array along that codimension.

Standard#

Fortran 2008

See Also#

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

fortran-lang intrinsic descriptions

event_query#

Name#

event_query(3) - [COLLECTIVE] Query whether a coarray event has occurred

Synopsis#

    call event_query(event, count [,stat] )

Characteristics#

Description#

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.

Options#

  • event

    (intent(in)) Scalar of type event_type, defined in iso_fortran_env; shall not be coindexed.

  • count

    (intent(out))Scalar integer with at least the precision of default integer.

  • stat

    (OPTIONAL) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See also#

****(3)

fortran-lang intrinsic descriptions

image_index#

Name#

image_index(3) - [COLLECTIVE] Cosubscript to image index conversion

Synopsis#

    result = image_index(coarray, sub)

Characteristics#

Description#

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

Options#

  • coarray

    Coarray of any type.

  • sub

    default integer rank-1 array of a size equal to the corank of coarray.

Result#

Scalar default integer with the value of the image index which corresponds to the cosubscripts. For invalid cosubscripts the result is zero.

Examples#

Sample program:

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

Standard#

Fortran 2008

See Also#

this_image(3), num_images(3)

fortran-lang intrinsic descriptions

num_images#

Name#

num_images(3) - [COLLECTIVE] Number of images

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.

Description#

num_images(3) Returns the number of images.

Options#

  • 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.

Result#

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

Examples#

Sample program:

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

Standard#

Fortran 2008 . With DISTANCE or FAILED argument, TS 18508

See Also#

this_image(3), image_index(3)

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

this_image#

Name#

this_image(3) - [COLLECTIVE] Cosubscript index of this image

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.

Description#

this_image(3) returns the cosubscript for this image.

Options#

  • distance

    Nonnegative scalar integer (not permitted together with coarray).

  • coarray

    if dim present, required).

  • dim

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

Result#

Default integer. If coarray is not present, it is scalar; if distance is not present or has value 0, its value is the image index on the invoking image for the current team, for values smaller or equal distance to the initial team, it returns the image index on the ancestor team which has a distance of distance from the invoking team. If distance is larger than the distance to the initial team, the image index of the initial team is returned. Otherwise when the coarray is present, if dim is not present, a rank-1 array with corank elements is returned, containing the cosubscripts for coarray specifying the invoking image. If dim is present, a scalar is returned, with the value of the dim element of this_image(coarray).

Examples#

Sample program:

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

Results:

   value[1] is 1

Standard#

Fortran 2008. With DISTANCE argument, TS 18508

See Also#

num_images(3), image_index(3)

fortran-lang intrinsic descriptions

atomic_and#

Name#

atomic_and(3) - [ATOMIC:BIT MANIPULATION] Atomic bitwise AND operation

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.

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_fetch_and(3) - [ATOMIC:BIT MANIPULATION] Atomic bitwise AND operation with prior fetch

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • old

    Scalar of the same type and kind as atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_fetch_or(3) - [ATOMIC:BIT MANIPULATION] Atomic bitwise OR operation with prior fetch

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • old

    Scalar of the same type and kind as atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_fetch_xor(3) - [ATOMIC:BIT MANIPULATION] Atomic bitwise XOR operation with prior fetch

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • old

    Scalar of the same type and kind as atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_or(3) - [ATOMIC:BIT MANIPULATION] Atomic bitwise OR operation

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.

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_xor(3) - [ATOMIC:BIT MANIPULATION] Atomic bitwise OR operation

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#

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_add(3) - [ATOMIC] Atomic ADD operation

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.

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_cas(3) - [ATOMIC] Atomic compare and swap

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of either integer type with atomic_int_kind kind or logical type with atomic_logical_kind kind.

  • old

    Scalar of the same type and kind as atom.

  • compare

    Scalar variable of the same type and kind as atom.

  • new

    Scalar variable of the same type as atom. If kind is different, the value is converted to the kind of atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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

fortran-lang intrinsic descriptions

atomic_define#

Name#

atomic_define(3) - [ATOMIC] Setting a variable atomically

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

    Scalar coarray or coindexed variable of either integer type with atomic_int_kind kind or logical type with atomic_logical_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • stat

    (optional) Scalar default-kind integer variable.

Description#

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

Options#

  • 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.

Examples#

Sample program:

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

Standard#

Fortran 2008 ; with stat, TS 18508

See Also#

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#

Name#

atomic_fetch_add(3) - [ATOMIC] Atomic ADD operation with prior fetch

Synopsis#

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

Characteristics#

Description#

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.

Options#

  • atom

    Scalar coarray or coindexed variable of integer type with atomic_int_kind kind. atomic_logical_kind kind.

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • old

    Scalar of the same type and kind as atom.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

TS 18508

See Also#

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#

Name#

atomic_ref(3) - [ATOMIC] Obtaining the value of a variable atomically

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.

Description#

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.

Options#

  • value

    Scalar of the same type as atom. If the kind is different, the value is converted to the kind of atom.

  • atom

    Scalar coarray or coindexed variable of either integer type with atomic_int_kind kind or logical type with atomic_logical_kind kind.

  • stat

    (optional) Scalar default-kind integer variable.

Examples#

Sample program:

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

Standard#

Fortran 2008 ; with STAT, TS 18508

See Also#

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