-
Lionel GUEZ authored
Note that we then have to declare `d_init` before `ishape_last` in procedure `get_snapshot`.
Lionel GUEZ authoredNote that we then have to declare `d_init` before `ishape_last` in procedure `get_snapshot`.
get_snapshot.f90 1.58 KiB
module get_snapshot_m
implicit none
contains
subroutine get_snapshot(s, nlon, nlat, ishape_last, corner, step, copy, &
hshp, d_init, k, k_end, rank, n_proc, max_delta)
use derived_types, only: snapshot, shpc
use read_snapshot_m, only: read_snapshot
use recv_snapshot_m, only: recv_snapshot
type(snapshot), intent(out):: s
integer, intent(in):: nlon, nlat
integer, intent(in):: d_init ! first date in the collection of shapefiles
integer, intent(in):: ishape_last(d_init:)
! shape index (0-based) in the collection of shapefiles of the last
! shape at a given date index
real, intent(in):: corner(:) ! (2) longitude and latitude of the
! corner of the whole grid, in rad
real, intent(in):: step(:) ! (2) longitude and latitude steps, in rad
integer, intent(in):: copy
TYPE(shpc), intent(in):: hshp
integer, intent(in):: k ! date index
integer, intent(in):: k_end ! last date index analyzed by this MPI process
integer, intent(in):: rank ! of MPI process
integer, intent(in):: n_proc ! number of MPI processes
integer, intent(in):: max_delta
! maximum interval of date indices between which we look for
! overlapping of eddies
!--------------------------------------------------------------
if (rank == n_proc - 1 .or. k <= k_end - max_delta) then
call read_snapshot(s, hshp, nlon, nlat, d_init, k, corner, step, copy, &
ishape_last)
else
call recv_snapshot(s, nlon, nlat, copy, source = rank + 1, tag = k)
end if
end subroutine get_snapshot
end module get_snapshot_m