mp_iscatterv_lv Subroutine

private subroutine mp_iscatterv_lv(msg_scatter, sendcounts, displs, msg, recvcount, root, gid, request)

Scatters data from one processes to all others

MPI mapping mpi_scatter

Arguments

Type IntentOptional Attributes Name
integer(kind=int_8), intent(in), CONTIGUOUS :: msg_scatter(:)

Data to scatter (for root process)

integer, intent(in), CONTIGUOUS :: sendcounts(:)
integer, intent(in), CONTIGUOUS :: displs(:)
integer(kind=int_8), intent(inout), CONTIGUOUS :: msg(:)
integer, intent(in) :: recvcount

Process which scatters data

integer, intent(in) :: root

Process which scatters data

type(mp_comm_type), intent(in) :: gid

Message passing environment identifier

type(mp_request_type), intent(inout) :: request

Source Code

      SUBROUTINE mp_iscatterv_lv(msg_scatter, sendcounts, displs, msg, recvcount, root, gid, request)
      !! Scatters data from one processes to all others
      !!
      !! MPI mapping
      !! mpi_scatter

         INTEGER(KIND=int_8), CONTIGUOUS, INTENT(IN)        :: msg_scatter(:)
         !! Data to scatter (for root process)
         INTEGER, CONTIGUOUS, INTENT(IN)          :: sendcounts(:), displs(:)
         INTEGER(KIND=int_8), CONTIGUOUS, INTENT(INOUT)     :: msg(:)
         INTEGER, INTENT(IN)                      :: recvcount, root
         !! Process which scatters data
         TYPE(mp_comm_type), INTENT(IN)           :: gid
         !! Message passing environment identifier
         TYPE(mp_request_type), INTENT(INOUT)                   :: request

         CHARACTER(LEN=*), PARAMETER :: routineN = 'mp_iscatterv_lv'

         INTEGER                                  :: handle, ierr

         ierr = 0
         CALL timeset(routineN, handle)

#if defined(__parallel)
         CALL mpi_iscatterv(msg_scatter, sendcounts, displs, MPI_INTEGER8, msg, &
                            recvcount, MPI_INTEGER8, root, gid%handle, request%handle, ierr)
         IF (ierr /= 0) CALL mp_stop(ierr, "mpi_iscatterv @ "//routineN)
         CALL add_perf(perf_id=24, msg_size=1*int_8_size)
#else
         MARK_USED(sendcounts)
         MARK_USED(displs)
         MARK_USED(recvcount)
         MARK_USED(root)
         MARK_USED(gid)
         msg(1:recvcount) = msg_scatter(1 + displs(1):1 + displs(1) + sendcounts(1))
         request = mp_request_null
#endif
         CALL timestop(handle)
      END SUBROUTINE mp_iscatterv_lv