rma_transfer Subroutine

private subroutine rma_transfer(recv_vproc, nimages, size_layers3D, displ_layers3D, buffer, meta_win, data_win, data_get, data_type_byte, buffer_win, layer3D, nlayers3D)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: recv_vproc
integer, intent(in) :: nimages
integer, intent(in), DIMENSION(:) :: size_layers3D
integer, intent(in), DIMENSION(:) :: displ_layers3D
type(dbcsr_buffer), intent(inout) :: buffer
type(mp_win_type), intent(in) :: meta_win
type(mp_win_type), intent(in) :: data_win
type(dbcsr_data_obj), intent(inout) :: data_get
integer, intent(in) :: data_type_byte
type(dbcsr_buffer), intent(in) :: buffer_win
integer, intent(in) :: layer3D
integer, intent(in) :: nlayers3D

Source Code

   SUBROUTINE rma_transfer(recv_vproc, nimages, &
                           size_layers3D, displ_layers3D, &
                           buffer, &
                           meta_win, data_win, &
                           data_get, data_type_byte, &
                           buffer_win, layer3D, nlayers3D)
      INTEGER, INTENT(IN)                                :: recv_vproc, nimages
      INTEGER, DIMENSION(:), INTENT(IN)                  :: size_layers3D, displ_layers3D
      TYPE(dbcsr_buffer), INTENT(INOUT)                  :: buffer
      TYPE(mp_win_type), INTENT(IN)                      :: meta_win, data_win
      TYPE(dbcsr_data_obj), INTENT(INOUT)                :: data_get
      INTEGER, INTENT(IN)                                :: data_type_byte
      TYPE(dbcsr_buffer), INTENT(IN)                     :: buffer_win
      INTEGER, INTENT(IN)                                :: layer3D, nlayers3D

      INTEGER                                            :: recv_proc
      INTEGER, DIMENSION(:), POINTER, CONTIGUOUS         :: meta_get

      buffer%is_comm = .TRUE.
      buffer%get_requests(:) = mp_request_null
      recv_proc = (recv_vproc/nimages)*nlayers3D + layer3D - 1
      !
      meta_get => buffer%meta(dbcsr_num_slots + 1:dbcsr_num_slots + size_layers3D(imeta))
      buffer%meta_size = size_layers3D(imeta)
      CALL mp_rget(meta_get, recv_proc, &
                   meta_win, &
                   buffer_win%meta, &
                   buffer_win%myproc, &
                   disp=displ_layers3D(imeta), &
                   request=buffer%get_requests(1))
      CALL dbcsr_data_set_pointer( &
         area=data_get, &
         rsize=size_layers3D(idata), &
         csize=1, &
         pointee=buffer%data, &
         source_lb=1)
      CALL dbcsr_rget_any(data_get, recv_proc, &
                          data_win, &
                          buffer_win%data, &
                          buffer_win%myproc, &
                          disp=displ_layers3D(idata), &
                          request=buffer%get_requests(2))
      CALL count_mpi_statistics(dbcsr_mpi_statistics%data_size(1, :), &
                                size_layers3D(idata), &
                                data_type_byte, &
                                dbcsr_mpi_statistics%data_size_breakdown(:, :, 1))
      dbcsr_mpi_statistics%nexchanged = dbcsr_mpi_statistics%nexchanged + 1
      !
      ! Set the referenced sizes to the actual data moved via MPI
      CALL dbcsr_data_set_size_referenced(buffer%data, size_layers3D(idata))
      buffer%matrix%valid = .FALSE.
   END SUBROUTINE rma_transfer