MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
MpiMessageBuilder.f90
Go to the documentation of this file.
2  use kindmodule, only: i4b, lgp
7  use mpi
8  implicit none
9  private
10 
11  type, public :: vdcheadertype
12  integer(I4B) :: id
13  integer(I4B) :: container_type
14  integer(I4B), dimension(NR_VDC_ELEMENT_MAPS) :: map_sizes
15  end type
16 
17  type, public :: vdcreceivermapstype
18  type(vdcelementmaptype), dimension(NR_VDC_ELEMENT_MAPS) :: el_maps
19  contains
20  procedure :: create
21  procedure :: destroy
22  end type
23 
24  type, public :: mpimessagebuildertype
25  type(vdcptrtype), dimension(:), pointer :: vdc_models => null() !< the models to be build the message for
26  type(vdcptrtype), dimension(:), pointer :: vdc_exchanges => null() !< the exchanges to be build the message for
27  integer(I4B) :: imon !< the output file unit, set from outside
28  contains
29  procedure :: init
30  procedure :: attach_data
31  procedure :: release_data
32  procedure :: create_header_snd
33  procedure :: create_header_rcv
34  procedure :: create_map_snd
35  procedure :: create_map_rcv
36  procedure :: create_body_rcv
37  procedure :: create_body_snd
38  procedure :: set_monitor
39  ! private
40  procedure, private :: get_vdc_from_hdr
41  procedure, private :: create_vdc_snd_hdr
42  procedure, private :: create_vdc_snd_map
43  procedure, private :: create_vdc_snd_body
44  procedure, private :: create_vdc_rcv_body
45  end type
46 
47 contains
48 
49  subroutine create(this, map_sizes)
50  class(vdcreceivermapstype) :: this
51  integer(I4B), dimension(NR_VDC_ELEMENT_MAPS) :: map_sizes
52  ! local
53  integer(I4B) :: i
54 
55  do i = 1, nr_vdc_element_maps
56  this%el_maps(i)%nr_virt_elems = map_sizes(i)
57  allocate (this%el_maps(i)%remote_elem_shift(map_sizes(i)))
58  end do
59 
60  end subroutine create
61 
62  subroutine destroy(this)
63  class(vdcreceivermapstype) :: this
64  ! local
65  integer(I4B) :: i
66 
67  do i = 1, nr_vdc_element_maps
68  if (associated(this%el_maps(i)%remote_elem_shift)) then
69  deallocate (this%el_maps(i)%remote_elem_shift)
70  end if
71  end do
72 
73  end subroutine destroy
74 
75  subroutine init(this)
76  class(mpimessagebuildertype) :: this
77 
78  this%imon = -1
79 
80  end subroutine init
81 
82  subroutine attach_data(this, vdc_models, vdc_exchanges)
83  class(mpimessagebuildertype) :: this
84  type(vdcptrtype), dimension(:), pointer :: vdc_models
85  type(vdcptrtype), dimension(:), pointer :: vdc_exchanges
86 
87  this%vdc_models => vdc_models
88  this%vdc_exchanges => vdc_exchanges
89 
90  end subroutine attach_data
91 
92  subroutine release_data(this)
93  class(mpimessagebuildertype) :: this
94 
95  this%vdc_models => null()
96  this%vdc_exchanges => null()
97 
98  end subroutine release_data
99 
100  subroutine set_monitor(this, imon)
101  class(mpimessagebuildertype) :: this
102  integer(I4B) :: imon
103 
104  this%imon = imon
105 
106  end subroutine set_monitor
107 
108  !> @brief Create the header data type to send to
109  !! the remote process for this particular stage.
110  !! From these data, the receiver can construct the
111  !< body to send back to us.
112  subroutine create_header_snd(this, rank, stage, hdrs_snd_type)
113  class(mpimessagebuildertype) :: this
114  integer(I4B) :: rank
115  integer(I4B) :: stage
116  integer, intent(out) :: hdrs_snd_type
117  ! local
118  integer(I4B) :: i, offset, nr_types
119  class(virtualdatacontainertype), pointer :: vdc
120  integer :: ierr
121  type(stlvecint) :: model_idxs, exg_idxs
122  integer, dimension(:), allocatable :: blk_cnts, types
123  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
124 
125  call model_idxs%init()
126  call exg_idxs%init()
127 
128  ! determine which containers to include
129  do i = 1, size(this%vdc_models)
130  vdc => this%vdc_models(i)%ptr
131  if (vdc%is_active .and. vdc%orig_rank == rank) then
132  call model_idxs%push_back(i)
133  end if
134  end do
135  do i = 1, size(this%vdc_exchanges)
136  vdc => this%vdc_exchanges(i)%ptr
137  if (vdc%is_active .and. vdc%orig_rank == rank) then
138  call exg_idxs%push_back(i)
139  end if
140  end do
141 
142  nr_types = model_idxs%size + exg_idxs%size
143  allocate (blk_cnts(nr_types))
144  allocate (types(nr_types))
145  allocate (displs(nr_types))
146 
147  if (this%imon > 0) then
148  write (this%imon, '(6x,a,*(i3))') "create headers for models: ", &
149  model_idxs%get_values()
150  write (this%imon, '(6x,a,*(i3))') "create headers for exchange: ", &
151  exg_idxs%get_values()
152  end if
153 
154  ! loop over containers
155  do i = 1, model_idxs%size
156  vdc => this%vdc_models(model_idxs%at(i))%ptr
157  call mpi_get_address(vdc%id, displs(i), ierr)
158  blk_cnts(i) = 1
159  types(i) = this%create_vdc_snd_hdr(vdc, stage)
160  end do
161  offset = model_idxs%size
162  do i = 1, exg_idxs%size
163  vdc => this%vdc_exchanges(exg_idxs%at(i))%ptr
164  call mpi_get_address(vdc%id, displs(i + offset), ierr)
165  blk_cnts(i + offset) = 1
166  types(i + offset) = this%create_vdc_snd_hdr(vdc, stage)
167  end do
168 
169  ! create a MPI data type for the headers to send
170  call mpi_type_create_struct(nr_types, blk_cnts, displs, types, &
171  hdrs_snd_type, ierr)
172  call mpi_type_commit(hdrs_snd_type, ierr)
173  do i = 1, nr_types
174  call mpi_type_free(types(i), ierr)
175  end do
176 
177  call model_idxs%destroy()
178  call exg_idxs%destroy()
179 
180  deallocate (blk_cnts)
181  deallocate (types)
182  deallocate (displs)
183 
184  end subroutine create_header_snd
185 
186  subroutine create_header_rcv(this, hdr_rcv_type)
187  class(mpimessagebuildertype) :: this
188  integer, intent(out) :: hdr_rcv_type
189  ! local
190  integer :: ierr
191 
192  ! this will be for one data container, the mpi recv
193  ! call will accept an array of them, no need to create
194  ! an overarching contiguous type...
195  call mpi_type_contiguous(nr_vdc_element_maps + 2, mpi_integer, &
196  hdr_rcv_type, ierr)
197  call mpi_type_commit(hdr_rcv_type, ierr)
198 
199  end subroutine create_header_rcv
200 
201  subroutine create_map_snd(this, rank, stage, map_snd_type)
202  class(mpimessagebuildertype) :: this
203  integer(I4B) :: rank
204  integer(I4B) :: stage
205  integer, intent(out) :: map_snd_type
206  ! local
207  integer(I4B) :: i, offset, nr_types
208  class(virtualdatacontainertype), pointer :: vdc
209  integer :: ierr
210  type(stlvecint) :: model_idxs, exg_idxs
211  integer, dimension(:), allocatable :: blk_cnts, types
212  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
213 
214  call model_idxs%init()
215  call exg_idxs%init()
216 
217  ! determine which containers to include,
218  ! currently models + exchanges
219  do i = 1, size(this%vdc_models)
220  vdc => this%vdc_models(i)%ptr
221  if (vdc%is_active .and. vdc%orig_rank == rank) then
222  call model_idxs%push_back(i)
223  end if
224  end do
225  do i = 1, size(this%vdc_exchanges)
226  vdc => this%vdc_exchanges(i)%ptr
227  if (vdc%is_active .and. vdc%orig_rank == rank) then
228  call exg_idxs%push_back(i)
229  end if
230  end do
231 
232  nr_types = model_idxs%size + exg_idxs%size
233  allocate (blk_cnts(nr_types))
234  allocate (types(nr_types))
235  allocate (displs(nr_types))
236 
237  if (this%imon > 0) then
238  write (this%imon, '(6x,a,*(i3))') "create maps for models: ", &
239  model_idxs%get_values()
240  write (this%imon, '(6x,a,*(i3))') "create maps for exchange: ", &
241  exg_idxs%get_values()
242  end if
243 
244  ! loop over containers
245  do i = 1, model_idxs%size
246  vdc => this%vdc_models(model_idxs%at(i))%ptr
247  call mpi_get_address(vdc%id, displs(i), ierr)
248  blk_cnts(i) = 1
249  types(i) = this%create_vdc_snd_map(vdc, stage)
250  end do
251  offset = model_idxs%size
252  do i = 1, exg_idxs%size
253  vdc => this%vdc_exchanges(exg_idxs%at(i))%ptr
254  call mpi_get_address(vdc%id, displs(i + offset), ierr)
255  blk_cnts(i + offset) = 1
256  types(i + offset) = this%create_vdc_snd_map(vdc, stage)
257  end do
258 
259  ! create a compound MPI data type for the maps
260  call mpi_type_create_struct(nr_types, blk_cnts, displs, types, &
261  map_snd_type, ierr)
262  call mpi_type_commit(map_snd_type, ierr)
263 
264  ! free the subtypes
265  do i = 1, nr_types
266  call mpi_type_free(types(i), ierr)
267  end do
268 
269  call model_idxs%destroy()
270  call exg_idxs%destroy()
271 
272  deallocate (blk_cnts)
273  deallocate (types)
274  deallocate (displs)
275 
276  end subroutine create_map_snd
277 
278  subroutine create_map_rcv(this, rcv_map, nr_headers, map_rcv_type)
279  class(mpimessagebuildertype) :: this
280  type(vdcreceivermapstype), dimension(:) :: rcv_map
281  integer(I4B) :: nr_headers
282  integer, intent(out) :: map_rcv_type
283  ! local
284  integer(I4B) :: i, j, nr_elems, type_cnt
285  integer :: ierr, max_nr_maps
286  integer, dimension(:), allocatable :: types
287  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
288  integer, dimension(:), allocatable :: blk_cnts
289 
290  max_nr_maps = nr_headers * nr_vdc_element_maps
291  allocate (types(max_nr_maps))
292  allocate (displs(max_nr_maps))
293  allocate (blk_cnts(max_nr_maps))
294 
295  type_cnt = 0
296  do i = 1, nr_headers
297  do j = 1, nr_vdc_element_maps
298  nr_elems = rcv_map(i)%el_maps(j)%nr_virt_elems
299  if (nr_elems == 0) cycle
300 
301  type_cnt = type_cnt + 1
302  call mpi_get_address(rcv_map(i)%el_maps(j)%remote_elem_shift, &
303  displs(type_cnt), ierr)
304  call mpi_type_contiguous(nr_elems, mpi_integer, types(type_cnt), ierr)
305  blk_cnts(type_cnt) = 1
306  end do
307  end do
308 
309  call mpi_type_create_struct(type_cnt, blk_cnts, displs, types, &
310  map_rcv_type, ierr)
311  call mpi_type_commit(map_rcv_type, ierr)
312 
313  deallocate (types)
314  deallocate (displs)
315  deallocate (blk_cnts)
316 
317  end subroutine create_map_rcv
318 
319  !> @brief Create the body to receive based on the headers
320  !< that have been sent
321  subroutine create_body_rcv(this, rank, stage, body_rcv_type)
322  class(mpimessagebuildertype) :: this
323  integer(I4B) :: rank
324  integer(I4B) :: stage
325  integer, intent(out) :: body_rcv_type
326  ! local
327  integer(I4B) :: i, nr_types, offset
328  class(virtualdatacontainertype), pointer :: vdc
329  type(stlvecint) :: model_idxs, exg_idxs
330  integer :: ierr
331  integer, dimension(:), allocatable :: types
332  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
333  integer, dimension(:), allocatable :: blk_cnts
334 
335  call model_idxs%init()
336  call exg_idxs%init()
337 
338  ! gather all containers from this rank
339  do i = 1, size(this%vdc_models)
340  vdc => this%vdc_models(i)%ptr
341  if (vdc%is_active .and. vdc%orig_rank == rank) then
342  if (this%imon > 0) then
343  write (this%imon, '(6x,a,i0)') "expecting model ", vdc%id
344  end if
345  call model_idxs%push_back(i)
346  end if
347  end do
348  do i = 1, size(this%vdc_exchanges)
349  vdc => this%vdc_exchanges(i)%ptr
350  if (vdc%is_active .and. vdc%orig_rank == rank) then
351  if (this%imon > 0) then
352  write (this%imon, '(6x,a,i0)') "expecting exchange ", vdc%id
353  end if
354  call exg_idxs%push_back(i)
355  end if
356  end do
357 
358  nr_types = model_idxs%size + exg_idxs%size
359  allocate (types(nr_types))
360  allocate (displs(nr_types))
361  allocate (blk_cnts(nr_types))
362 
363  ! loop over included containers
364  do i = 1, model_idxs%size
365  vdc => this%vdc_models(model_idxs%at(i))%ptr
366  call mpi_get_address(vdc%id, displs(i), ierr)
367  types(i) = this%create_vdc_rcv_body(vdc, rank, stage)
368  blk_cnts(i) = 1
369  end do
370  offset = model_idxs%size
371  do i = 1, exg_idxs%size
372  vdc => this%vdc_exchanges(exg_idxs%at(i))%ptr
373  call mpi_get_address(vdc%id, displs(i + offset), ierr)
374  blk_cnts(i + offset) = 1
375  types(i + offset) = this%create_vdc_rcv_body(vdc, rank, stage)
376  end do
377 
378  ! create a MPI data type for the virtual data containers to receive
379  call mpi_type_create_struct(nr_types, blk_cnts, displs, types, &
380  body_rcv_type, ierr)
381  call mpi_type_commit(body_rcv_type, ierr)
382  do i = 1, nr_types
383  call mpi_type_free(types(i), ierr)
384  end do
385 
386  call model_idxs%destroy()
387  call exg_idxs%destroy()
388  deallocate (types)
389  deallocate (displs)
390  deallocate (blk_cnts)
391 
392  end subroutine create_body_rcv
393 
394  !> @brief Create the body to send based on the received headers
395  !<
396  subroutine create_body_snd(this, rank, stage, headers, maps, body_snd_type)
397  class(mpimessagebuildertype) :: this
398  integer(I4B) :: rank
399  integer(I4B) :: stage
400  type(vdcheadertype), dimension(:) :: headers
401  type(vdcreceivermapstype), dimension(:) :: maps
402  integer, intent(out) :: body_snd_type
403  ! local
404  integer(I4B) :: i, nr_headers
405  class(virtualdatacontainertype), pointer :: vdc
406  integer :: ierr
407  integer, dimension(:), allocatable :: types
408  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
409  integer, dimension(:), allocatable :: blk_cnts
410 
411  nr_headers = size(headers)
412  allocate (types(nr_headers))
413  allocate (displs(nr_headers))
414  allocate (blk_cnts(nr_headers))
415 
416  do i = 1, nr_headers
417  vdc => this%get_vdc_from_hdr(headers(i))
418  call mpi_get_address(vdc%id, displs(i), ierr)
419  types(i) = this%create_vdc_snd_body(vdc, maps(i)%el_maps, rank, stage)
420  blk_cnts(i) = 1
421  end do
422 
423  ! create the list of virtual data containers to receive
424  call mpi_type_create_struct(nr_headers, blk_cnts, displs, &
425  types, body_snd_type, ierr)
426  call mpi_type_commit(body_snd_type, ierr)
427  do i = 1, nr_headers
428  call mpi_type_free(types(i), ierr)
429  end do
430 
431  deallocate (types)
432  deallocate (displs)
433  deallocate (blk_cnts)
434 
435  end subroutine create_body_snd
436 
437  !> @brief Create send header for virtual data container, relative
438  !< to the field ...%id
439  function create_vdc_snd_hdr(this, vdc, stage) result(new_type)
440  class(mpimessagebuildertype) :: this
441  class(virtualdatacontainertype) :: vdc
442  integer(I4B) :: stage
443  integer :: new_type ! the created MPI datatype, uncommitted
444  ! local
445  integer :: i, ierr
446  integer, dimension(NR_VDC_ELEMENT_MAPS + 2) :: blk_cnts
447  integer(kind=MPI_ADDRESS_KIND), dimension(NR_VDC_ELEMENT_MAPS + 2) :: displs
448  integer, dimension(NR_VDC_ELEMENT_MAPS + 2) :: types
449 
450  call mpi_get_address(vdc%id, displs(1), ierr)
451  types(1) = mpi_integer
452  blk_cnts(1) = 1
453  call mpi_get_address(vdc%container_type, displs(2), ierr)
454  types(2) = mpi_integer
455  blk_cnts(2) = 1
456  do i = 1, nr_vdc_element_maps
457  call mpi_get_address(vdc%element_maps(i)%nr_virt_elems, displs(i + 2), ierr)
458  types(i + 2) = mpi_integer
459  blk_cnts(i + 2) = 1
460  end do
461 
462  ! rebase to id field
463  displs = displs - displs(1)
464  call mpi_type_create_struct(nr_vdc_element_maps + 2, blk_cnts, &
465  displs, types, new_type, ierr)
466  call mpi_type_commit(new_type, ierr)
467 
468  end function create_vdc_snd_hdr
469 
470  !> @brief Create a MPI datatype for sending the maps
471  !< with the type relative to the id field
472  function create_vdc_snd_map(this, vdc, stage) result(new_type)
473  class(mpimessagebuildertype) :: this
474  class(virtualdatacontainertype), pointer :: vdc
475  integer(I4B) :: stage
476  integer :: new_type
477  ! local
478  integer(I4B) :: i, type_cnt
479  integer :: n_elems, ierr
480  integer(kind=MPI_ADDRESS_KIND) :: offset
481  integer, dimension(:), allocatable :: types
482  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
483  integer, dimension(:), allocatable :: blk_cnts
484 
485  allocate (types(nr_vdc_element_maps))
486  allocate (displs(nr_vdc_element_maps))
487  allocate (blk_cnts(nr_vdc_element_maps))
488 
489  ! displ relative to id field
490  call mpi_get_address(vdc%id, offset, ierr)
491 
492  type_cnt = 0
493  do i = 1, nr_vdc_element_maps
494  n_elems = vdc%element_maps(i)%nr_virt_elems
495  if (n_elems == 0) cycle ! only non-empty maps are sent
496 
497  type_cnt = type_cnt + 1
498  call mpi_get_address(vdc%element_maps(i)%remote_elem_shift, &
499  displs(type_cnt), ierr)
500  call mpi_type_contiguous(n_elems, mpi_integer, types(type_cnt), ierr)
501  call mpi_type_commit(types(type_cnt), ierr)
502  blk_cnts(type_cnt) = 1
503  displs(type_cnt) = displs(type_cnt) - offset
504  end do
505 
506  call mpi_type_create_struct(type_cnt, blk_cnts, displs, types, &
507  new_type, ierr)
508  call mpi_type_commit(new_type, ierr)
509 
510  do i = 1, type_cnt
511  call mpi_type_free(types(i), ierr)
512  end do
513 
514  deallocate (types)
515  deallocate (displs)
516  deallocate (blk_cnts)
517 
518  end function create_vdc_snd_map
519 
520  function create_vdc_rcv_body(this, vdc, rank, stage) result(new_type)
521  class(mpimessagebuildertype) :: this
522  class(virtualdatacontainertype), pointer :: vdc
523  integer(I4B) :: rank
524  integer(I4B) :: stage
525  integer :: new_type
526  ! local
527  type(stlvecint) :: items
528  integer :: ierr
529  integer(kind=MPI_ADDRESS_KIND) :: offset
530  integer, dimension(:), allocatable :: types
531  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
532  integer, dimension(:), allocatable :: blk_cnts
533  integer(I4B) :: i
534  class(virtualdatatype), pointer :: vd
535 
536  call items%init()
537  call vdc%get_recv_items(stage, rank, items)
538  !if (this%imon > 0) call vdc%print_items(this%imon, items)
539 
540  allocate (types(items%size))
541  allocate (displs(items%size))
542  allocate (blk_cnts(items%size))
543 
544  call mpi_get_address(vdc%id, offset, ierr)
545 
546  do i = 1, items%size
547  vd => get_virtual_data_from_list(vdc%virtual_data_list, items%at(i))
548  call get_mpi_datatype(this, vd, displs(i), types(i))
549  blk_cnts(i) = 1
550  ! rebase w.r.t. id field
551  displs(i) = displs(i) - offset
552  end do
553 
554  call mpi_type_create_struct(items%size, blk_cnts, displs, &
555  types, new_type, ierr)
556  call mpi_type_commit(new_type, ierr)
557 
558  do i = 1, items%size
559  vd => get_virtual_data_from_list(vdc%virtual_data_list, items%at(i))
560  call free_mpi_datatype(vd, types(i))
561  end do
562 
563  deallocate (types)
564  deallocate (displs)
565  deallocate (blk_cnts)
566 
567  call items%destroy()
568 
569  end function create_vdc_rcv_body
570 
571  function create_vdc_snd_body(this, vdc, vdc_maps, rank, stage) result(new_type)
572  class(mpimessagebuildertype) :: this
573  class(virtualdatacontainertype), pointer :: vdc
574  type(vdcelementmaptype), dimension(:) :: vdc_maps
575  integer(I4B) :: rank
576  integer(I4B) :: stage
577  integer :: new_type
578  ! local
579  type(stlvecint) :: items
580  integer :: ierr
581  integer(kind=MPI_ADDRESS_KIND) :: offset
582  integer, dimension(:), allocatable :: types
583  integer(kind=MPI_ADDRESS_KIND), dimension(:), allocatable :: displs
584  integer, dimension(:), allocatable :: blk_cnts
585  integer(I4B) :: i
586  class(virtualdatatype), pointer :: vd
587  integer(I4B), dimension(:), pointer, contiguous :: el_map
588 
589  call items%init()
590  call vdc%get_send_items(stage, rank, items)
591  !if (this%imon > 0) call vdc%print_items(this%imon, items)
592 
593  allocate (types(items%size))
594  allocate (displs(items%size))
595  allocate (blk_cnts(items%size))
596 
597  call mpi_get_address(vdc%id, offset, ierr)
598 
599  do i = 1, items%size
600  vd => get_virtual_data_from_list(vdc%virtual_data_list, items%at(i))
601  if (vd%map_type > 0) then
602  el_map => vdc_maps(vd%map_type)%remote_elem_shift
603  else
604  el_map => null()
605  end if
606  call get_mpi_datatype(this, vd, displs(i), types(i), el_map)
607  blk_cnts(i) = 1
608  ! rebase w.r.t. id field
609  displs(i) = displs(i) - offset
610  end do
611 
612  call mpi_type_create_struct(items%size, blk_cnts, displs, &
613  types, new_type, ierr)
614  call mpi_type_commit(new_type, ierr)
615 
616  do i = 1, items%size
617  vd => get_virtual_data_from_list(vdc%virtual_data_list, items%at(i))
618  call free_mpi_datatype(vd, types(i))
619  end do
620 
621  deallocate (types)
622  deallocate (displs)
623  deallocate (blk_cnts)
624 
625  call items%destroy()
626 
627  end function create_vdc_snd_body
628 
629  function get_vdc_from_hdr(this, header) result(vdc)
630  class(mpimessagebuildertype) :: this
631  type(vdcheadertype) :: header
632  class(virtualdatacontainertype), pointer :: vdc
633  ! local
634  integer(I4B) :: i
635 
636  vdc => null()
637  if (header%container_type == vdc_gwfmodel_type .or. &
638  header%container_type == vdc_gwtmodel_type .or. &
639  header%container_type == vdc_gwemodel_type) then
640  do i = 1, size(this%vdc_models)
641  vdc => this%vdc_models(i)%ptr
642  if (vdc%id == header%id) return
643  vdc => null()
644  end do
645  else if (header%container_type == vdc_gwfexg_type .or. &
646  header%container_type == vdc_gwtexg_type .or. &
647  header%container_type == vdc_gweexg_type) then
648  do i = 1, size(this%vdc_exchanges)
649  vdc => this%vdc_exchanges(i)%ptr
650  if (vdc%id == header%id) return
651  vdc => null()
652  end do
653  end if
654 
655  end function get_vdc_from_hdr
656 
657  !> @brief Local routine to get elemental mpi data types representing
658  !! the virtual data items. Types are automatically committed unless
659  !< they are primitives (e.g. MPI_INTEGER)
660  subroutine get_mpi_datatype(this, virtual_data, el_displ, el_type, el_map_opt)
661  use simmodule, only: ustop
662  class(mpimessagebuildertype) :: this
663  class(virtualdatatype), pointer :: virtual_data
664  integer(kind=MPI_ADDRESS_KIND) :: el_displ
665  integer :: el_type
666  integer(I4B), dimension(:), pointer, contiguous, optional :: el_map_opt !< optional, and can be null
667  ! local
668  type(memorytype), pointer :: mt
669  integer(I4B), dimension(:), pointer, contiguous :: el_map
670 
671  el_map => null()
672  if (present(el_map_opt)) el_map => el_map_opt
673 
674  if (this%imon > 0) then
675  if (.not. associated(el_map)) then
676  write (this%imon, '(8x,2a,i0)') virtual_data%var_name, ' all ', &
677  virtual_data%virtual_mt%isize
678  else
679  write (this%imon, '(8x,2a,i0)') virtual_data%var_name, &
680  ' with map size ', size(el_map)
681  end if
682  end if
683 
684  mt => virtual_data%virtual_mt
685 
686  if (associated(mt%intsclr)) then
687  call get_mpitype_for_int(mt, el_displ, el_type)
688  else if (associated(mt%aint1d)) then
689  call get_mpitype_for_int1d(mt, el_displ, el_type, el_map)
690  else if (associated(mt%dblsclr)) then
691  call get_mpitype_for_dbl(mt, el_displ, el_type)
692  else if (associated(mt%adbl1d)) then
693  call get_mpitype_for_dbl1d(mt, el_displ, el_type, el_map)
694  else if (associated(mt%adbl2d)) then
695  call get_mpitype_for_dbl2d(mt, el_displ, el_type, el_map)
696  else
697  write (*, *) 'unsupported datatype in MPI messaging for ', &
698  virtual_data%var_name, virtual_data%mem_path
699  call ustop()
700  end if
701 
702  end subroutine get_mpi_datatype
703 
704  !> @brief Local routine to free elemental mpi data types representing
705  !! the virtual data items. This can't be done generally, because some
706  !< (scalar) types are primitive and freeing them causes nasty errors...
707  subroutine free_mpi_datatype(virtual_data, el_type)
708  class(virtualdatatype), pointer :: virtual_data
709  integer :: el_type
710  ! local
711  type(memorytype), pointer :: mt
712  integer :: ierr
713 
714  mt => virtual_data%virtual_mt
715  if (associated(mt%intsclr)) then
716  ! type is MPI_INTEGER, don't free this!
717  return
718  else if (associated(mt%dblsclr)) then
719  ! type is MPI_DOUBLE_PRECISION, don't free this!
720  return
721  else if (associated(mt%logicalsclr)) then
722  ! type is MPI_LOGICAL, don't free this!
723  return
724  else
725  ! all other types are freed here
726  call mpi_type_free(el_type, ierr)
727  return
728  end if
729 
730  end subroutine free_mpi_datatype
731 
732  subroutine get_mpitype_for_int(mem, el_displ, el_type)
733  type(memorytype), pointer :: mem
734  integer(kind=MPI_ADDRESS_KIND) :: el_displ
735  integer :: el_type
736  ! local
737  integer :: ierr
738 
739  call mpi_get_address(mem%intsclr, el_displ, ierr)
740  el_type = mpi_integer
741  ! no need to commit primitive type
742 
743  end subroutine get_mpitype_for_int
744 
745  subroutine get_mpitype_for_int1d(mem, el_displ, el_type, el_map)
746  type(memorytype), pointer :: mem
747  integer(kind=MPI_ADDRESS_KIND) :: el_displ
748  integer :: el_type
749  integer, dimension(:), pointer :: el_map
750  ! local
751  integer :: ierr
752 
753  call mpi_get_address(mem%aint1d, el_displ, ierr)
754  if (associated(el_map)) then
755  call mpi_type_create_indexed_block( &
756  size(el_map), 1, el_map, mpi_integer, el_type, ierr)
757  else
758  call mpi_type_contiguous(mem%isize, mpi_integer, el_type, ierr)
759  end if
760  call mpi_type_commit(el_type, ierr)
761 
762  end subroutine get_mpitype_for_int1d
763 
764  subroutine get_mpitype_for_dbl(mem, el_displ, el_type)
765  type(memorytype), pointer :: mem
766  integer(kind=MPI_ADDRESS_KIND) :: el_displ
767  integer :: el_type
768  ! local
769  integer :: ierr
770 
771  call mpi_get_address(mem%dblsclr, el_displ, ierr)
772  el_type = mpi_double_precision
773  ! no need to commit primitive type
774 
775  end subroutine get_mpitype_for_dbl
776 
777  subroutine get_mpitype_for_dbl1d(mem, el_displ, el_type, el_map)
778  type(memorytype), pointer :: mem
779  integer(kind=MPI_ADDRESS_KIND) :: el_displ
780  integer :: el_type
781  integer, dimension(:), pointer :: el_map
782  ! local
783  integer :: ierr
784 
785  call mpi_get_address(mem%adbl1d, el_displ, ierr)
786  if (associated(el_map)) then
787  call mpi_type_create_indexed_block( &
788  size(el_map), 1, el_map, mpi_double_precision, el_type, ierr)
789  else
790  call mpi_type_contiguous(mem%isize, mpi_double_precision, el_type, ierr)
791  end if
792  call mpi_type_commit(el_type, ierr)
793 
794  end subroutine get_mpitype_for_dbl1d
795 
796  subroutine get_mpitype_for_dbl2d(mem, el_displ, el_type, el_map)
797  type(memorytype), pointer :: mem
798  integer(kind=MPI_ADDRESS_KIND) :: el_displ
799  integer :: el_type
800  integer, dimension(:), pointer :: el_map
801  ! local
802  integer :: ierr
803  integer :: entry_type
804 
805  call mpi_get_address(mem%adbl2d, el_displ, ierr)
806  if (associated(el_map)) then
807  call mpi_type_contiguous( &
808  size(mem%adbl2d, dim=1), mpi_double_precision, entry_type, ierr)
809  call mpi_type_create_indexed_block( &
810  size(el_map), 1, el_map, entry_type, el_type, ierr)
811  else
812  call mpi_type_contiguous(mem%isize, mpi_double_precision, el_type, ierr)
813  end if
814  call mpi_type_commit(el_type, ierr)
815 
816  end subroutine get_mpitype_for_dbl2d
817 
818 end module mpimessagebuildermodule
This module defines variable data types.
Definition: kind.f90:8
subroutine get_mpitype_for_dbl2d(mem, el_displ, el_type, el_map)
subroutine set_monitor(this, imon)
subroutine release_data(this)
integer function create_vdc_snd_body(this, vdc, vdc_maps, rank, stage)
subroutine get_mpitype_for_int(mem, el_displ, el_type)
integer function create_vdc_snd_hdr(this, vdc, stage)
Create send header for virtual data container, relative.
subroutine get_mpitype_for_dbl(mem, el_displ, el_type)
subroutine get_mpi_datatype(this, virtual_data, el_displ, el_type, el_map_opt)
Local routine to get elemental mpi data types representing the virtual data items....
subroutine attach_data(this, vdc_models, vdc_exchanges)
subroutine create(this, map_sizes)
subroutine create_map_snd(this, rank, stage, map_snd_type)
subroutine create_body_rcv(this, rank, stage, body_rcv_type)
Create the body to receive based on the headers.
integer function create_vdc_snd_map(this, vdc, stage)
Create a MPI datatype for sending the maps.
subroutine create_map_rcv(this, rcv_map, nr_headers, map_rcv_type)
subroutine get_mpitype_for_dbl1d(mem, el_displ, el_type, el_map)
subroutine free_mpi_datatype(virtual_data, el_type)
Local routine to free elemental mpi data types representing the virtual data items....
subroutine create_body_snd(this, rank, stage, headers, maps, body_snd_type)
Create the body to send based on the received headers.
integer function create_vdc_rcv_body(this, vdc, rank, stage)
subroutine create_header_rcv(this, hdr_rcv_type)
subroutine create_header_snd(this, rank, stage, hdrs_snd_type)
Create the header data type to send to the remote process for this particular stage....
class(virtualdatacontainertype) function, pointer get_vdc_from_hdr(this, header)
subroutine get_mpitype_for_int1d(mem, el_displ, el_type, el_map)
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public ustop(stopmess, ioutlocal)
Stop the simulation.
Definition: Sim.f90:315
class(virtualdatatype) function, pointer, public get_virtual_data_from_list(list, idx)
integer(i4b), parameter, public nr_vdc_element_maps
Definition: VirtualBase.f90:16
integer(i4b), parameter, public vdc_gwtmodel_type
integer(i4b), parameter, public vdc_gwemodel_type
integer(i4b), parameter, public vdc_gwfmodel_type
integer(i4b), parameter, public vdc_gwtexg_type
integer(i4b), parameter, public vdc_gwfexg_type
integer(i4b), parameter, public vdc_gweexg_type
This is a generic data structure to virtualize pieces of memory in 2 distinct ways:
Definition: VirtualBase.f90:35
Wrapper for virtual data containers.