Skip to content
Snippets Groups Projects
  • Lionel GUEZ's avatar
    9fb56f5f
    Complete `send_snapshot` and `recv_snapshot` · 9fb56f5f
    Lionel GUEZ authored
    Pass argument copy to `read_snapshot` rather than arguments periodic
    and `dist_lim`. Motivation: do not recompute copy at each call of
    `read_snapshot`. `read_snapshot` is going to be called many times in
    overlap program, with always the same value of copy. And we do not
    need the values of periodic and `dist_lim` separately in
    `read_snapshot`.
    
    Complete `send_snapshot` and `recv_snapshot` by sending and receiving
    an entire snapshot. So we need nlon, nlat and copy in `recv_snapshot`
    to allocate `extr_map`. It is better to pass arguments nlon, nlat and
    copy than sending and receiving the shape of `extr_map` with MPI, of
    course, since the shape is the same for all snapshots. In program
    `test_send_recv`, write the entire received snaphot.
    
    Bug fix in `Tests/CMakeLists.txt`: several targets missed
    `${netcdff_INCLUDE_DIR}`.
    
    Create procedure `write_snapshot` from code in main program
    `test_read_snapshot`, because we need to do this also in program
    `test_send_recv`. Note the dissymmetry with `read_snapshot`, which
    does not include the opening and closing of the shapefiles. That is
    because we anticipate calling `read_snapshot` several times with the
    same shapefiles in program overlap.
    
    Change order of dummy arguments of procedure `write_extr_map`. More
    convenient for calling it with keywords from `write_snapshot`.
    9fb56f5f
    History
    Complete `send_snapshot` and `recv_snapshot`
    Lionel GUEZ authored
    Pass argument copy to `read_snapshot` rather than arguments periodic
    and `dist_lim`. Motivation: do not recompute copy at each call of
    `read_snapshot`. `read_snapshot` is going to be called many times in
    overlap program, with always the same value of copy. And we do not
    need the values of periodic and `dist_lim` separately in
    `read_snapshot`.
    
    Complete `send_snapshot` and `recv_snapshot` by sending and receiving
    an entire snapshot. So we need nlon, nlat and copy in `recv_snapshot`
    to allocate `extr_map`. It is better to pass arguments nlon, nlat and
    copy than sending and receiving the shape of `extr_map` with MPI, of
    course, since the shape is the same for all snapshots. In program
    `test_send_recv`, write the entire received snaphot.
    
    Bug fix in `Tests/CMakeLists.txt`: several targets missed
    `${netcdff_INCLUDE_DIR}`.
    
    Create procedure `write_snapshot` from code in main program
    `test_read_snapshot`, because we need to do this also in program
    `test_send_recv`. Note the dissymmetry with `read_snapshot`, which
    does not include the opening and closing of the shapefiles. That is
    because we anticipate calling `read_snapshot` several times with the
    same shapefiles in program overlap.
    
    Change order of dummy arguments of procedure `write_extr_map`. More
    convenient for calling it with keywords from `write_snapshot`.
recv_snapshot.f90 2.36 KiB
module recv_snapshot_m

  implicit none

  private recv_ssh_contour

contains

  subroutine recv_snapshot(s, nlon, nlat, copy, source, tag)

    use ezmpi, only: ezmpi_recv
    use derived_types, only: snapshot

    type(snapshot), intent(out):: s
    
    integer, intent(in):: nlon, nlat
    ! size of ssh array in input NetCDF, assuming no repeated point if
    ! the grid is global

    integer, intent(in):: copy
    integer, intent(in):: source ! rank of sending MPI process
    integer, intent(in):: tag ! date index for received snapshot

    ! Local:
    integer i

    !-----------------------------------------------------------

    call ezmpi_recv(s%number_vis_extr, source, tag)
    allocate(s%list_vis(s%number_vis_extr))

    do i = 1, s%number_vis_extr
       call ezmpi_recv(s%list_vis(i)%coord_extr, source, tag)
       call ezmpi_recv(s%list_vis(i)%ssh_extr, source, tag)
       call ezmpi_recv(s%list_vis(i)%cyclone, source, tag)
       call recv_ssh_contour(s%list_vis(i)%out_cont, source, tag)
       call recv_ssh_contour(s%list_vis(i)%speed_cont, source, tag)
       call ezmpi_recv(s%list_vis(i)%max_speed, source, tag)
       call ezmpi_recv(s%list_vis(i)%valid, source, tag)
       call ezmpi_recv(s%list_vis(i)%interpolated, source, tag)
       call ezmpi_recv(s%list_vis(i)%delta_in, source, tag)
       call ezmpi_recv(s%list_vis(i)%delta_out, source, tag)
       call ezmpi_recv(s%list_vis(i)%radius4, source, tag)
    end do

    allocate(s%extr_map(1 - copy:nlon + copy, nlat))
    call ezmpi_recv(s%extr_map, source, tag)

    allocate(s%ind_extr(2, s%number_vis_extr))
    call ezmpi_recv(s%ind_extr, source, tag)

    call ezmpi_recv(s%number_eddies, source, tag)

  end subroutine recv_snapshot

  !*******************************************************************

  subroutine recv_ssh_contour(cont, source, tag)

    use ezmpi, only: ezmpi_recv
    use derived_types, only: ssh_contour

    type(ssh_contour), intent(out):: cont
    integer, intent(in):: source, tag

    !------------------------------------------------------------------

    call ezmpi_recv(cont%n_points, source, tag)
    call ezmpi_recv(cont%closed, source, tag)
    allocate(cont%points(2, cont%n_points))
    call ezmpi_recv(cont%points, source, tag)
    call ezmpi_recv(cont%ssh, source, tag)
    call ezmpi_recv(cont%area, source, tag)

  end subroutine recv_ssh_contour

end module recv_snapshot_m