source: codes/icosagcm/trunk/src/parallel/transfert_mpi.f90 @ 1016

Last change on this file since 1016 was 1004, checked in by adurocher, 4 years ago

transfert_mpi : Send only necessary messages + overlap HtoH

File size: 33.9 KB
Line 
1! Module for MPI communication of field halos
2! This module uses Fortran 2003 features : move_alloc intrinsic, pointer bounds remapping, allocatable type fields
3module transfert_mpi_mod
4  use abort_mod, only : dynamico_abort, abort_acc
5  use profiling_mod, only : enter_profile, exit_profile, register_id
6  use domain_mod, only : ndomain, ndomain_glo, domain, domain_glo, domloc_glo_ind, domglo_rank, domglo_loc_ind
7  use field_mod, only : t_field, field_T, field_U, field_Z
8  use transfert_request_mod
9  implicit none
10  private
11
12  ! Describes how to pack/unpack a message from a local domain to another
13  type t_local_submessage
14    integer :: src_ind_loc, dest_ind_loc ! index of local and remote domain
15    integer :: npoints ! Number of cells to transfer (dim12)
16    integer, allocatable :: displ_src(:) ! List of indexes to copy from domain src_ind_loc
17    integer, allocatable :: displ_dest(:) ! List of indexes to copy to domain dest_ind_loc
18    integer, allocatable :: sign(:) ! Sign change to be applied for vector requests
19  end type
20
21  ! Describes how to pack/unpack a message from a domain to another, and contains MPI buffer
22  type t_submessage
23    integer :: ind_loc, remote_ind_glo, remote_rank ! index of local and remote domain
24    integer :: npoints ! Number of cells to transfer (dim12)
25    integer, allocatable :: displs(:) ! List of indexes to copy from field to buffer for each level
26    integer, allocatable :: sign(:) ! Sign change to be applied for vector requests
27    integer :: mpi_buffer_displ = -1
28  end type
29 
30  type t_compact_submessages
31    integer :: npoints
32    integer, allocatable, dimension(:) :: field_ind, field_displ, sign, remote_rank, mpi_displ, level_offset
33  end type
34 
35  type t_compact_local_submessages
36    integer :: npoints
37    integer, allocatable, dimension(:) :: field_ind_src, field_displ_src, sign, field_ind_dest, field_displ_dest
38  end type
39 
40  type mpi_buffer_t
41    integer :: n
42    real, allocatable :: buff(:)
43  end type
44
45  ! Describes how to exchange data for a field.
46  type t_message
47    type (t_field), pointer :: field(:) => null() ! Field to exchange
48    type (t_request), pointer :: request(:) => null() ! Type of message to send
49    type (t_local_submessage), pointer :: message_local(:) ! Local halo copies
50    type (t_submessage), pointer :: message_in(:) ! Messages to recieve from remote ranks and to copy back to the field
51    type (t_submessage), pointer :: message_out(:) ! Halos to copy to MPI buffer and to send to remote ranks
52    type (mpi_buffer_t), pointer :: mpi_buffer_in(:)
53    type (mpi_buffer_t), pointer :: mpi_buffer_out(:)
54    type (t_compact_submessages), pointer :: message_in_compact
55    type (t_compact_submessages), pointer :: message_out_compact
56    type (t_compact_local_submessages), pointer  :: message_local_compact   
57    integer, pointer :: mpi_requests_in(:) ! MPI requests used for message_in.
58    integer, pointer :: mpi_requests_out(:) ! MPI requests used for message_out.
59    ! NOTE : requests are persistant requests initialized in init_message. MPI_Start and MPI_Wait are then used to initiate and complete communications.
60    ! ex : Give mpi_requests_in(i) to MPI_Start to send the buffer contained in message_in(i)
61    integer :: send_seq ! Sequence number : send_seq is incremented each time send_message is called
62    integer :: wait_seq ! Sequence number : wait_seq is incremented each time wait_message is called
63    logical :: ondevice ! Ready to transfer ondevice field
64  end type t_message
65
66  public :: t_message, t_request, &
67    req_i1, req_e1_scal, req_e1_vect, &
68    req_i0, req_e0_scal, req_e0_vect, &
69    req_z1_scal, &
70    init_transfert, &
71    init_message, &
72    finalize_message, &
73    send_message, &
74    wait_message, &
75    test_message
76
77  ! ---- Private variables ----
78  ! Profiling id for mpi
79  integer :: profile_mpi, profile_mpi_copies, profile_mpi_waitall, profile_mpi_barrier
80contains
81  ! Initialize transfert : must be called before any other transfert_mpi routines
82  subroutine init_transfert
83    use mpi_mod, only : MPI_THREAD_SINGLE, MPI_THREAD_FUNNELED
84    use mpipara, only : mpi_threading_mode
85    use profiling_mod, only : register_id
86    logical, parameter :: profile_mpi_detail = .true.
87
88    !$omp master
89    ! Check requested threads support
90    if( mpi_threading_mode /= MPI_THREAD_SINGLE .and. mpi_threading_mode /= MPI_THREAD_FUNNELED ) call dynamico_abort("Only single and funneled threading mode are supported.")
91
92    ! Register profiling ids
93    call register_id("MPI", profile_mpi)
94    if( profile_mpi_detail ) then
95      call register_id("MPI_copies", profile_mpi_copies)
96      call register_id("MPI_waitall", profile_mpi_waitall)
97      call register_id("MPI_omp_barrier", profile_mpi_barrier)
98    else
99      profile_mpi_copies = profile_mpi
100      profile_mpi_waitall = profile_mpi
101      profile_mpi_barrier = profile_mpi
102    endif
103
104    ! Initialize requests
105    call init_all_requests()
106    !$omp end master
107    !$omp barrier
108  end subroutine
109
110  subroutine init_message(field, request, message, name)
111    use mpi_mod
112    use mpipara
113    type(t_field), pointer, intent(in) :: field(:)
114    type(t_request),pointer, intent(in) :: request(:)
115    type(t_message), target, intent(out) :: message ! Needs intent out for call to finalize_message
116    character(len=*), intent(in),optional :: name
117    integer, parameter :: INITIAL_ALLOC_SIZE = 10, GROW_FACTOR = 2
118
119    type(t_submessage) :: submessage_in, submessage_out
120    type(t_local_submessage) :: submessage_local
121    integer :: dim3, dim4, npoints, last_point
122    integer :: ind, ind_loc, remote_ind_glo, loc_ind_glo, i, k, remote_rank
123    integer :: message_in_size, message_out_size, message_local_size, buffer_in_size, buffer_out_size
124    type(t_local_submessage), allocatable :: message_local_tmp(:)
125    type(t_submessage), allocatable :: message_in_tmp(:), message_out_tmp(:)
126    integer :: field_type
127
128    !$omp barrier
129    !$omp master
130    !init off-device
131    message%ondevice=.false.
132    message%send_seq = 0
133    message%wait_seq = 0
134
135    if( request(1)%field_type /= field(1)%field_type ) call dynamico_abort( "init_message : field_type/request mismatch" )
136    field_type = request(1)%field_type
137
138    ! Set field%rval4d pointer to always use 4d array
139    do ind = 1, ndomain
140      if( field(ind)%ndim == 2 ) field(ind)%rval4d(1:size(field(ind)%rval2d,1),1:1,1:1) => field(ind)%rval2d
141      ! This is Fortran 2008 : can be avoided by using a subroutine with rval3d as a 1D dummy argument
142      ! (/!\ : using a subroutine might generate a temporary contiguous array)
143      if( field(ind)%ndim == 3 ) field(ind)%rval4d(1:size(field(ind)%rval3d,1), &
144        1:size(field(ind)%rval3d,2), 1:1) => field(ind)%rval3d
145    end do
146    dim3 = size(field(1)%rval4d,2)
147    dim4 = size(field(1)%rval4d,3)
148    message%field => field
149    message%request => request
150    ! Create list of inbound/outbound/local messages
151    allocate(message_in_tmp(INITIAL_ALLOC_SIZE))
152    message_in_size=0
153    allocate(message_out_tmp(INITIAL_ALLOC_SIZE))
154    message_out_size=0
155    allocate(message_local_tmp(INITIAL_ALLOC_SIZE))
156    message_local_size=0
157    do loc_ind_glo = 1, ndomain_glo
158      do remote_ind_glo = 1, ndomain_glo
159        if(domglo_rank(loc_ind_glo) == mpi_rank) then
160          ind_loc = domglo_loc_ind(loc_ind_glo)
161          if( domglo_rank(remote_ind_glo) == mpi_rank ) then ! If sending to local domain
162            if(request(ind_loc)%points_HtoB(remote_ind_glo)%npoints > 0 ) then ! Add only non-empty messages
163              ! Add local message ind_loc -> remote_ind_glo, aggregarting submessage_in and submessage_out into submessage_local
164              submessage_out = make_submessage( field_type, request(ind_loc)%points_HtoB(remote_ind_glo), &
165                                                ind_loc, remote_ind_glo, dim3, dim4, request(1)%vector )
166              submessage_in = make_submessage( field_type, request(domglo_loc_ind(remote_ind_glo))%points_BtoH(domloc_glo_ind(ind_loc)), &
167                                              domglo_loc_ind(remote_ind_glo), domloc_glo_ind(ind_loc), dim3, dim4, request(1)%vector)
168              submessage_local%src_ind_loc = ind_loc
169              submessage_local%dest_ind_loc = domglo_loc_ind(remote_ind_glo)
170              submessage_local%npoints = submessage_out%npoints
171              submessage_local%displ_src = submessage_out%displs
172              submessage_local%displ_dest = submessage_in%displs
173              submessage_local%sign = submessage_in%sign
174              ! Add to local message list
175              call array_append_local_submessage( message_local_tmp, message_local_size, submessage_local)
176            endif
177          else ! If remote domain
178            ! When data to send to remote_domain, add submessage in message%message_out
179            if( request(ind_loc)%points_HtoB(remote_ind_glo)%npoints > 0 ) then
180              submessage_out = make_submessage( field_type, request(ind_loc)%points_HtoB(remote_ind_glo), &
181                                                ind_loc, remote_ind_glo, dim3, dim4, request(1)%vector )
182              call array_append_submessage( message_out_tmp, message_out_size, submessage_out )
183            end if         
184          end if
185        end if
186      end do
187    end do
188    ! Recv and Send submessages are transposed to recieve and send in same order
189    ! We iterate over global domain index to match sends with recieves (local domains are not ordered like global domains)
190    do remote_ind_glo = 1, ndomain_glo
191      do loc_ind_glo = 1, ndomain_glo
192        if( (domglo_rank(loc_ind_glo) == mpi_rank) .and. (domglo_rank(remote_ind_glo) /= mpi_rank) ) then
193          ind_loc = domglo_loc_ind(loc_ind_glo)
194          if( request(ind_loc)%points_BtoH(remote_ind_glo)%npoints > 0 ) then
195            submessage_in = make_submessage( field_type, request(ind_loc)%points_BtoH(remote_ind_glo), &
196                                             ind_loc, remote_ind_glo, dim3, dim4, request(1)%vector )
197            call array_append_submessage( message_in_tmp, message_in_size, submessage_in )
198          end if
199        end if
200      end do
201    end do
202   
203   
204    ! Trim message_xx_tmp and put it in message%message_xx
205    allocate(message%message_in(message_in_size)); message%message_in(:) = message_in_tmp(:message_in_size)
206    allocate(message%message_out(message_out_size)); message%message_out(:) = message_out_tmp(:message_out_size)
207    allocate(message%message_local(message_local_size)); message%message_local(:) = message_local_tmp(:message_local_size)
208
209    ! Allocate MPI buffers
210    allocate( message%mpi_buffer_in(0:mpi_size-1) )
211    allocate( message%mpi_buffer_out(0:mpi_size-1) )
212    do i = 0, mpi_size-1
213      buffer_in_size = dim3*dim4*sum( message%message_in(:)%npoints, message%message_in(:)%remote_rank == i )
214      buffer_out_size = dim3*dim4*sum( message%message_out(:)%npoints, message%message_out(:)%remote_rank == i )
215      !TODO : what if size == 0 ?
216      allocate( message%mpi_buffer_in(i)%buff( buffer_in_size ) )
217      allocate( message%mpi_buffer_out(i)%buff( buffer_out_size ) )
218      message%mpi_buffer_in(i)%n=0
219      message%mpi_buffer_out(i)%n=0
220    end do
221    ! Set offsets in submessages
222    do i=1, size(message%message_out)
223      remote_rank = message%message_out(i)%remote_rank
224      message%message_out(i)%mpi_buffer_displ = message%mpi_buffer_out(remote_rank)%n
225      message%mpi_buffer_out(remote_rank)%n = message%mpi_buffer_out(remote_rank)%n + message%message_out(i)%npoints*dim3*dim4
226    end do
227    do i=1, size(message%message_in)
228      remote_rank = message%message_in(i)%remote_rank
229      message%message_in(i)%mpi_buffer_displ = message%mpi_buffer_in(remote_rank)%n
230      message%mpi_buffer_in(remote_rank)%n = message%mpi_buffer_in(remote_rank)%n + message%message_in(i)%npoints*dim3*dim4
231    end do
232    ! Create persistant MPI requests
233    allocate( message%mpi_requests_in(0:mpi_size-1) )
234    allocate( message%mpi_requests_out(0:mpi_size-1) )
235    message%mpi_requests_in(0:mpi_size-1) = MPI_REQUEST_NULL
236    message%mpi_requests_out(0:mpi_size-1) = MPI_REQUEST_NULL
237    do i = 0, mpi_size-1
238      if(  size(message%mpi_buffer_in(i)%buff) /= message%mpi_buffer_in(i)%n &
239      .or. size(message%mpi_buffer_out(i)%buff) /= message%mpi_buffer_out(i)%n)&
240        call dynamico_abort("Internal error in transfert_mpi : mpi buffer size different than expected")
241      if( message%mpi_buffer_out(i)%n > 0) then
242        call MPI_Send_Init( message%mpi_buffer_out(i)%buff, message%mpi_buffer_out(i)%n, MPI_REAL8, i,&
243                            100, comm_icosa, message%mpi_requests_out(i), ierr )
244      endif
245      if( message%mpi_buffer_in(i)%n > 0) then
246        call MPI_Recv_Init( message%mpi_buffer_in(i)%buff, message%mpi_buffer_in(i)%n, MPI_REAL8, i,&
247                            100, comm_icosa, message%mpi_requests_in(i), ierr )
248      endif
249    end do
250   
251    allocate(message%message_in_compact)   
252    message%message_in_compact%npoints = sum(message%message_in(:)%npoints)
253    npoints = message%message_in_compact%npoints
254    allocate(message%message_in_compact%field_ind(npoints))
255    allocate(message%message_in_compact%field_displ(npoints))
256    allocate(message%message_in_compact%sign(npoints))
257    allocate(message%message_in_compact%remote_rank(npoints))
258    allocate(message%message_in_compact%mpi_displ(npoints))
259    allocate(message%message_in_compact%level_offset(npoints))
260
261    last_point=0
262    do i = 1, size( message%message_in )
263      do k = 1, message%message_in(i)%npoints
264        last_point = last_point+1
265        message%message_in_compact%field_ind(last_point)   = message%message_in(i)%ind_loc
266        message%message_in_compact%field_displ(last_point) = message%message_in(i)%displs(k)
267        message%message_in_compact%sign(last_point)        = message%message_in(i)%sign(k)
268        message%message_in_compact%remote_rank(last_point) = message%message_in(i)%remote_rank
269        message%message_in_compact%mpi_displ(last_point)   = message%message_in(i)%mpi_buffer_displ + k
270        message%message_in_compact%level_offset(last_point)= message%message_in(i)%npoints
271      end do
272    end do
273   
274    allocate(message%message_out_compact) 
275    message%message_out_compact%npoints = sum(message%message_out(:)%npoints)
276    npoints = message%message_out_compact%npoints
277    allocate(message%message_out_compact%field_ind(npoints))
278    allocate(message%message_out_compact%field_displ(npoints))
279    allocate(message%message_out_compact%sign(npoints))
280    allocate(message%message_out_compact%remote_rank(npoints))
281    allocate(message%message_out_compact%mpi_displ(npoints))
282    allocate(message%message_out_compact%level_offset(npoints))
283
284    last_point=0
285    do i = 1, size( message%message_out )
286      do k = 1, message%message_out(i)%npoints
287        last_point = last_point+1
288        message%message_out_compact%field_ind(last_point)   = message%message_out(i)%ind_loc
289        message%message_out_compact%field_displ(last_point) = message%message_out(i)%displs(k)
290        message%message_out_compact%sign(last_point)        = message%message_out(i)%sign(k)
291        message%message_out_compact%remote_rank(last_point) = message%message_out(i)%remote_rank
292        message%message_out_compact%mpi_displ(last_point)   = message%message_out(i)%mpi_buffer_displ + k
293        message%message_out_compact%level_offset(last_point)= message%message_out(i)%npoints
294      end do
295    end do
296   
297    allocate(message%message_local_compact) 
298    message%message_local_compact%npoints = sum(message%message_local(:)%npoints)
299    npoints = message%message_local_compact%npoints
300    allocate(message%message_local_compact%field_ind_src(npoints))
301    allocate(message%message_local_compact%field_displ_src(npoints))
302    allocate(message%message_local_compact%sign(npoints))
303    allocate(message%message_local_compact%field_ind_dest(npoints))
304    allocate(message%message_local_compact%field_displ_dest(npoints))
305
306    last_point=0
307    do i = 1, size( message%message_local )
308      do k = 1, message%message_local(i)%npoints
309        last_point = last_point+1
310        message%message_local_compact%field_ind_src(last_point)   = message%message_local(i)%src_ind_loc
311        message%message_local_compact%field_displ_src(last_point) = message%message_local(i)%displ_src(k)
312        message%message_local_compact%sign(last_point)            = message%message_local(i)%sign(k)
313        message%message_local_compact%field_ind_dest(last_point)  = message%message_local(i)%dest_ind_loc
314        message%message_local_compact%field_displ_dest(last_point)= message%message_local(i)%displ_dest(k)
315      end do
316    end do 
317   
318    !$omp end master
319    !$omp barrier
320  contains
321    ! Generate submessage from points
322    function make_submessage(field_type, points, ind_loc, remote_ind_glo, dim3, dim4, vector) result(submessage)
323      use dimensions, only : swap_dimensions, iim, u_pos, z_pos
324      integer, intent(in) :: field_type
325      type(t_points), intent(in) :: points
326      integer, intent(in) :: ind_loc, remote_ind_glo, dim3, dim4
327      logical, intent(in) :: vector
328      integer :: k
329      type(t_submessage) :: submessage
330
331      call swap_dimensions(ind_loc)
332      submessage%ind_loc = ind_loc
333      submessage%remote_ind_glo = remote_ind_glo
334      submessage%remote_rank = domglo_rank(remote_ind_glo)
335      submessage%npoints = points%npoints
336      submessage%mpi_buffer_displ = -1 ! Buffers not allocated yet
337      allocate( submessage%displs( points%npoints ) )
338      submessage%displs(:) = points%i + (points%j-1)*iim
339      if(field_type == field_U) submessage%displs = submessage%displs + u_pos( points%elt )
340      if(field_type == field_Z) submessage%displs = submessage%displs + z_pos( points%elt )
341      allocate(submessage%sign( points%npoints ))
342      if( vector ) then ! For U fields only
343        submessage%sign(:) = (/( domain(ind_loc)%edge_assign_sign(points%elt(k)-1, points%i(k), points%j(k)) ,k=1,points%npoints)/)
344      else
345        submessage%sign(:) = 1
346      endif
347    end function
348
349    ! Add element to array, and reallocate if necessary
350    subroutine array_append_submessage( a, a_size, elt )
351      type(t_submessage), allocatable, intent(inout) :: a(:)
352      integer, intent(inout) :: a_size
353      type(t_submessage), intent(in) :: elt
354      type(t_submessage), allocatable :: a_tmp(:)
355      integer, parameter :: GROW_FACTOR = 2
356
357      if( size( a ) <= a_size ) then
358        allocate( a_tmp ( a_size * GROW_FACTOR ) )
359        a_tmp(1:a_size) = a(1:a_size)
360        call move_alloc(a_tmp, a)
361      end if
362      a_size = a_size + 1
363      a(a_size) = elt;
364    end subroutine
365    ! Add element to array, and reallocate if necessary
366    subroutine array_append_local_submessage( a, a_size, elt )
367      type(t_local_submessage), allocatable, intent(inout) :: a(:)
368      integer, intent(inout) :: a_size
369      type(t_local_submessage), intent(in) :: elt
370      type(t_local_submessage), allocatable :: a_tmp(:)
371      integer, parameter :: GROW_FACTOR = 2
372
373      if( size( a ) <= a_size ) then
374        allocate( a_tmp ( a_size * GROW_FACTOR ) )
375        a_tmp(1:a_size) = a(1:a_size)
376        call move_alloc(a_tmp, a)
377      end if
378      a_size = a_size + 1
379      a(a_size) = elt;
380    end subroutine
381    ! Je demande pardon au dieu du copier-coller car j'ai péché
382  end subroutine
383
384  subroutine message_create_ondevice(message)
385    use mpi_mod
386    use mpipara, only : mpi_size, comm_icosa
387    type(t_message), intent(inout) :: message
388    integer :: i, ierr
389
390    if( message%ondevice ) call dynamico_abort("Message already on device")
391
392    !$acc enter data copyin(message) async
393    !$acc enter data copyin(message%mpi_buffer_in(:)) async
394    !$acc enter data copyin(message%mpi_buffer_out(:)) async
395    do i = 0, mpi_size-1
396      !$acc enter data copyin(message%mpi_buffer_in(i)%buff(:)) async
397      !$acc enter data copyin(message%mpi_buffer_out(i)%buff(:)) async
398    end do
399    !!$acc enter data copyin(message%message_in(:)) async
400    !do i = 1, size( message%message_in )
401    !  !$acc enter data copyin(message%message_in(i)%displs(:)) async
402    !  !$acc enter data copyin(message%message_in(i)%sign(:)) async
403    !end do
404    !!$acc enter data copyin(message%message_out(:)) async
405    !do i = 1, size( message%message_out )
406    !  !$acc enter data copyin(message%message_out(i)%displs(:)) async
407      !!$acc enter data copyin(message%message_out(i)%sign(:)) async
408    !end do
409    !!$acc enter data copyin(message%message_local(:)) async
410    !do i = 1, size( message%message_local )
411    !  !$acc enter data copyin(message%message_local(i)%displ_src(:)) async
412    !  !$acc enter data copyin(message%message_local(i)%displ_dest(:)) async
413    !  !$acc enter data copyin(message%message_local(i)%sign(:)) async
414    !end do
415    !$acc enter data copyin(message%field(:)) async
416    do i = 1, ndomain
417      !$acc enter data copyin(message%field(i)%rval4d(:,:,:)) async
418    end do
419   
420    !$acc enter data copyin(message%message_in_compact) async
421    !$acc enter data copyin(message%message_in_compact%field_ind(:)) async
422    !$acc enter data copyin(message%message_in_compact%field_displ(:)) async
423    !$acc enter data copyin(message%message_in_compact%sign(:)) async
424    !$acc enter data copyin(message%message_in_compact%remote_rank(:)) async
425    !$acc enter data copyin(message%message_in_compact%mpi_displ(:)) async
426    !$acc enter data copyin(message%message_in_compact%level_offset(:)) async
427   
428    !$acc enter data copyin(message%message_out_compact) async
429    !$acc enter data copyin(message%message_out_compact%field_ind(:)) async
430    !$acc enter data copyin(message%message_out_compact%field_displ(:)) async
431    !$acc enter data copyin(message%message_out_compact%sign(:)) async
432    !$acc enter data copyin(message%message_out_compact%remote_rank(:)) async
433    !$acc enter data copyin(message%message_out_compact%mpi_displ(:)) async
434    !$acc enter data copyin(message%message_out_compact%level_offset(:)) async
435   
436    !$acc enter data copyin(message%message_local_compact) async
437    !$acc enter data copyin(message%message_local_compact%field_ind_src(:)) async
438    !$acc enter data copyin(message%message_local_compact%field_displ_src(:)) async
439    !$acc enter data copyin(message%message_local_compact%sign(:)) async
440    !$acc enter data copyin(message%message_local_compact%field_ind_dest(:)) async
441    !$acc enter data copyin(message%message_local_compact%field_displ_dest(:)) async
442
443    !$acc wait
444    do i = 0, mpi_size-1
445      if( message%mpi_requests_out(i) /= MPI_REQUEST_NULL ) then
446        call MPI_Request_free(message%mpi_requests_out(i), ierr)
447        !$acc host_data use_device(message%mpi_buffer_out(i)%buff)
448          ! /!\ buff(1) is important for PGI to avoid temporary array copy
449          call MPI_Send_Init( message%mpi_buffer_out(i)%buff(1), message%mpi_buffer_out(i)%n, MPI_REAL8, i,&
450                              0, comm_icosa, message%mpi_requests_out(i), ierr )
451        !$acc end host_data
452      end if
453      if( message%mpi_requests_in(i) /= MPI_REQUEST_NULL ) then
454        call MPI_Request_free(message%mpi_requests_in(i), ierr)
455        !$acc host_data use_device(message%mpi_buffer_in(i)%buff)
456          call MPI_Recv_Init( message%mpi_buffer_in(i)%buff(1), message%mpi_buffer_in(i)%n, MPI_REAL8, i,&
457                              0, comm_icosa, message%mpi_requests_in(i), ierr )
458        !$acc end host_data
459      endif
460    end do
461    message%ondevice=.true.
462    !!$acc update device(message%ondevice)
463  end subroutine
464
465  subroutine message_delete_ondevice(message)
466    use mpipara, only : mpi_size
467    type(t_message), intent(inout) :: message
468    integer :: i
469
470    if( .not. message%ondevice ) call dynamico_abort("Message not on device")
471
472    !do i = 1, size( message%message_in )
473    !  !$acc exit data delete(message%message_in(i)%displs(:)) async
474    !  !$acc exit data delete(message%message_in(i)%sign(:)) async
475    !end do
476    !!$acc exit data delete(message%message_in(:)) async
477    !do i = 1, size( message%message_out )
478    !  !$acc exit data delete(message%message_out(i)%displs(:)) async
479    !  !!$acc exit data delete(message%message_out(i)%sign(:)) async
480    !end do
481    !!$acc exit data delete(message%message_out(:)) async
482    !do i = 1, size( message%message_local )
483    !  !$acc exit data delete(message%message_local(i)%displ_src(:)) async
484    !  !$acc exit data delete(message%message_local(i)%displ_dest(:)) async
485    !  !$acc exit data delete(message%message_local(i)%sign(:)) async
486    !end do
487    !!$acc exit data delete(message%message_local(:)) async
488    do i = 0, mpi_size-1
489      !$acc exit data delete(message%mpi_buffer_in(i)%buff(:)) async
490      !$acc exit data delete(message%mpi_buffer_out(i)%buff(:)) async
491    end do
492    !$acc exit data delete(message%mpi_buffer_in(:)) async
493    !$acc exit data delete(message%mpi_buffer_out(:)) async
494    do i = 1, ndomain
495      !$acc exit data delete(message%field(i)%rval4d(:,:,:)) async
496    end do
497    !$acc exit data delete(message%field(:)) async
498    !$acc exit data delete(message) async
499   
500    !$acc exit data delete(message%message_in_compact%field_ind(:)) async
501    !$acc exit data delete(message%message_in_compact%field_displ(:)) async
502    !$acc exit data delete(message%message_in_compact%sign(:)) async
503    !$acc exit data delete(message%message_in_compact%remote_rank(:)) async
504    !$acc exit data delete(message%message_in_compact%mpi_displ(:)) async
505    !$acc exit data delete(message%message_in_compact%level_offset(:)) async
506    !$acc exit data delete(message%message_in_compact) async
507   
508    !$acc exit data delete(message%message_out_compact%field_ind(:)) async
509    !$acc exit data delete(message%message_out_compact%field_displ(:)) async
510    !$acc exit data delete(message%message_out_compact%sign(:)) async
511    !$acc exit data delete(message%message_out_compact%remote_rank(:)) async
512    !$acc exit data delete(message%message_out_compact%mpi_displ(:)) async
513    !$acc exit data delete(message%message_out_compact%level_offset(:)) async
514    !$acc exit data delete(message%message_out_compact) async
515   
516    !$acc exit data delete(message%message_local_compact%field_ind_src(:)) async
517    !$acc exit data delete(message%message_local_compact%field_displ_src(:)) async
518    !$acc exit data delete(message%message_local_compact%sign(:)) async
519    !$acc exit data delete(message%message_local_compact%field_ind_dest(:)) async
520    !$acc exit data delete(message%message_local_compact%field_displ_dest(:)) async
521    !$acc exit data delete(message%message_local_compact) async
522   
523    message%ondevice=.false.
524  end subroutine
525
526  subroutine finalize_message(message)
527    use mpi_mod   
528    use mpipara, only : mpi_size
529    type(t_message), intent(inout) :: message
530    integer :: i, ierr
531
532    !$omp barrier
533    !$omp master
534    if(message%send_seq /= message%wait_seq) call dynamico_abort("No matching wait_message before finalization")
535
536    if(message%ondevice) call message_delete_ondevice(message)
537    deallocate(message%message_in)
538    deallocate(message%message_out)
539    deallocate(message%message_local)
540    do i=0, mpi_size-1
541      if(message%mpi_requests_in(i) /= MPI_REQUEST_NULL) call MPI_Request_free(message%mpi_requests_in(i), ierr)
542      if(message%mpi_requests_out(i) /= MPI_REQUEST_NULL)call MPI_Request_free(message%mpi_requests_out(i), ierr)
543      deallocate(message%mpi_buffer_in(i)%buff)
544      deallocate(message%mpi_buffer_out(i)%buff)
545    end do
546    deallocate(message%mpi_buffer_in)
547    deallocate(message%mpi_buffer_out)
548    deallocate(message%mpi_requests_in)
549    deallocate(message%mpi_requests_out)
550    deallocate(message%message_in_compact)
551    deallocate(message%message_out_compact)
552    deallocate(message%message_local_compact)
553    !$omp end master
554    !$omp barrier
555  end subroutine
556
557  ! Halo to Buffer : copy outbound message to MPI buffers
558  subroutine copy_HtoB(message)
559    use domain_mod, only : assigned_domain
560    use omp_para, only : distrib_level
561    type(t_message), intent(inout) :: message
562    integer :: dim3, dim4, d3_begin, d3_end
563    integer :: k, d3, d4, i
564    integer :: local_displ
565
566    dim4 = size(message%field(1)%rval4d, 3)
567    dim3 = size(message%field(1)%rval4d, 2)
568    CALL distrib_level( 1, dim3, d3_begin, d3_end )
569   
570    !$acc parallel loop collapse(3) present(message) default(present) async if(message%ondevice)
571    do d4 = 1, dim4
572      do d3 = d3_begin, d3_end
573        do i=1, message%message_out_compact%npoints
574          message%mpi_buffer_out( message%message_out_compact%remote_rank(i) )%buff( message%message_out_compact%mpi_displ(i) + message%message_out_compact%level_offset(i)*( (d3-1) + dim3*(d4-1) ) ) &
575            = message%field(message%message_out_compact%field_ind(i))%rval4d( message%message_out_compact%field_displ(i), d3, d4 )
576        end do
577      end do
578    end do
579   
580  end subroutine
581
582  ! Halo to Halo : copy local messages from source field to destination field
583  subroutine copy_HtoH(message)
584    use domain_mod, only : assigned_domain
585    use omp_para, only : distrib_level
586    type(t_message), intent(inout) :: message
587    integer :: dim3, dim4, d3_begin, d3_end
588    integer :: k, d3, d4, i
589
590    dim4 = size(message%field(1)%rval4d, 3)
591    dim3 = size(message%field(1)%rval4d, 2)
592    CALL distrib_level( 1, dim3, d3_begin, d3_end )
593   
594    ! TODO : too many copies when tiles are distributed among threads
595    !$acc parallel loop collapse(3) present(message) default(present) async if(message%ondevice)
596    do d4 = 1, dim4
597      do d3 = d3_begin, d3_end
598        do i=1, message%message_local_compact%npoints
599          message%field(message%message_local_compact%field_ind_dest(i))%rval4d( message%message_local_compact%field_displ_dest(i), d3, d4 ) &
600            = message%message_local_compact%sign(i)*message%field(message%message_local_compact%field_ind_src(i))%rval4d( message%message_local_compact%field_displ_src(i), d3, d4 )
601        end do
602      end do
603    end do
604  end subroutine
605
606  ! Buffer to Halo : copy inbound message to field
607  subroutine copy_BtoH(message)
608    use domain_mod, only : assigned_domain
609    use omp_para, only : distrib_level
610    type(t_message), intent(inout) :: message
611    integer :: dim3, dim4, d3_begin, d3_end
612    integer :: k, d3, d4, i
613    integer :: last_point
614   
615    dim4 = size(message%field(1)%rval4d, 3)
616    dim3 = size(message%field(1)%rval4d, 2)
617    CALL distrib_level( 1, dim3, d3_begin, d3_end )
618   
619    !$acc parallel loop collapse(3) present(message) default(present) async if(message%ondevice)
620    do d4 = 1, dim4
621      do d3 = d3_begin, d3_end
622        do i=1, message%message_in_compact%npoints
623          message%field(message%message_in_compact%field_ind(i))%rval4d( message%message_in_compact%field_displ(i), d3, d4 ) &
624            = message%message_in_compact%sign(i)*message%mpi_buffer_in( message%message_in_compact%remote_rank(i) )%buff( message%message_in_compact%mpi_displ(i) + message%message_in_compact%level_offset(i)*( (d3-1) + dim3*(d4-1) ) ) 
625        end do
626      end do
627    end do
628
629  end subroutine
630   
631
632  subroutine send_message(field, message)
633    use mpi_mod
634    use mpipara , only : mpi_size
635    type(t_field),pointer :: field(:)
636    type(t_message), target :: message
637    integer :: ierr, i
638
639    call enter_profile(profile_mpi)
640
641    ! Needed because rval4d is set in init_message
642    if( .not. associated( message%field, field ) ) &
643      call dynamico_abort("send_message must be called with the same field used in init_message")
644
645    !Prepare 'message' for on-device copies if field is on device
646    !$omp master
647    if( field(1)%ondevice .and. .not. message%ondevice ) call message_create_ondevice(message)
648    if( field(1)%ondevice .neqv. message%ondevice ) call dynamico_abort("send_message : internal device/host memory synchronization error")
649    ! Check if previous message has been waited
650    if(message%send_seq /= message%wait_seq) &
651      call dynamico_abort("No matching wait_message before new send_message")
652    message%send_seq = message%send_seq + 1
653    !$omp end master
654
655    call enter_profile(profile_mpi_barrier)
656    !$omp barrier
657    call exit_profile(profile_mpi_barrier)
658
659    call enter_profile(profile_mpi_copies)
660    call copy_HtoB(message)
661    call exit_profile(profile_mpi_copies)
662
663    !$omp master
664    do i=0, mpi_size-1
665      if(message%mpi_requests_in(i) /= MPI_REQUEST_NULL) call MPI_Start( message%mpi_requests_in(i), ierr )
666    end do
667    !$omp end master
668
669    call enter_profile(profile_mpi_barrier)
670    !$acc wait
671    !$omp barrier
672    call exit_profile(profile_mpi_barrier)
673
674    !$omp master
675    do i=0, mpi_size-1
676      if(message%mpi_requests_out(i) /= MPI_REQUEST_NULL) call MPI_Start( message%mpi_requests_out(i), ierr )
677    end do
678    !$omp end master
679
680    call enter_profile(profile_mpi_copies)
681    call copy_HtoH(message)
682    call exit_profile(profile_mpi_copies)
683
684    call exit_profile(profile_mpi)
685  end subroutine
686
687  subroutine test_message(message)
688    use mpi_mod
689    type(t_message) :: message
690    integer :: ierr
691    logical :: completed
692
693    !!$omp master
694    !call MPI_Testall( size(message%mpi_requests_out), message%mpi_requests_out, completed, MPI_STATUSES_IGNORE, ierr )
695    !call MPI_Testall( size(message%mpi_requests_in), message%mpi_requests_in, completed, MPI_STATUSES_IGNORE, ierr )
696    !!$omp end master
697  end subroutine
698
699  subroutine wait_message(message)
700    use mpi_mod
701    type(t_message), target :: message
702    integer :: ierr
703
704    ! Check if message has been sent and not recieved yet
705    ! note : barrier needed between this and send_seq increment, and this and wait_seq increment
706    ! note : watch out for integer overflow a = b+1 doesn't imply a>b
707    if(message%send_seq /= message%wait_seq+1) then
708      print*, "WARNING : wait_message called multiple times for one send_message, skipping"
709      return ! Don't recieve message if already recieved
710    end if
711
712    call enter_profile(profile_mpi)
713
714    call enter_profile(profile_mpi_waitall)
715    !$omp master
716    call MPI_Waitall( size(message%mpi_requests_out), message%mpi_requests_out, MPI_STATUSES_IGNORE, ierr )
717    call MPI_Waitall( size(message%mpi_requests_in), message%mpi_requests_in, MPI_STATUSES_IGNORE, ierr )
718    !$omp end master
719    call exit_profile(profile_mpi_waitall)
720
721    call enter_profile(profile_mpi_barrier)
722    !$omp barrier
723    call exit_profile(profile_mpi_barrier)
724
725    call enter_profile(profile_mpi_copies) 
726    call copy_BtoH(message)
727    call exit_profile(profile_mpi_copies)
728
729    !$omp master
730    message%wait_seq = message%wait_seq + 1
731    !$omp end master
732
733    call enter_profile(profile_mpi_barrier)
734    !$omp barrier
735    call exit_profile(profile_mpi_barrier)
736
737    call exit_profile(profile_mpi)
738  end subroutine
739end module
Note: See TracBrowser for help on using the repository browser.