MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
VirtualDataContainer.f90
Go to the documentation of this file.
3  use simmodule, only: ustop
4  use listmodule
5  use kindmodule, only: i4b, lgp
10  implicit none
11  private
12 
13  public :: get_vdc_from_list
14  public :: vdc_type_to_str
15 
16  integer(I4B), public, parameter :: vdc_unknown_type = 0
17  integer(I4B), public, parameter :: vdc_gwfmodel_type = 1
18  integer(I4B), public, parameter :: vdc_gwtmodel_type = 2
19  integer(I4B), public, parameter :: vdc_gwemodel_type = 3
20  integer(I4B), public, parameter :: vdc_gwfexg_type = 4
21  integer(I4B), public, parameter :: vdc_gwtexg_type = 5
22  integer(I4B), public, parameter :: vdc_gweexg_type = 6
23  integer(I4B), public, parameter :: vdc_gwfmvr_type = 7
24  integer(I4B), public, parameter :: vdc_gwtmvt_type = 8
25  integer(I4B), public, parameter :: vdc_gwemve_type = 9
26 
27  !> @brief Wrapper for virtual data containers
28  !!
29  !! We can't have an array of pointers in Fortran, so we use
30  !! this trick where we wrap the pointer and have an array
31  !< of VdcPtrType instead.
32  type, public :: vdcptrtype
33  class(virtualdatacontainertype), pointer :: ptr => null()
34  end type vdcptrtype
35 
36  type, public :: vdcelementmaptype
37  integer(I4B) :: nr_virt_elems !< nr. of virtualized elements
38  integer(I4B), dimension(:), pointer, contiguous :: remote_elem_shift => null() !< array with 0-based remote indexes
39  end type vdcelementmaptype
40 
42  integer(I4B) :: max_remote_idx !< max. remote index, also size of the lookup table
43  integer(I4B), dimension(:), pointer, contiguous :: remote_to_virtual => null() !< (sparse) array with local indexes
44  end type vdcelementluttype
45 
46  !> @brief Container (list) of virtual data items.
47  !!
48  !! A virtual model or exchange derives from this base
49  !! and can add the component-specific items to the list
50  !! of virtual data items. As far as synchronization
51  !! of virtual objects is concerned, all that is needed
52  !< is the list of virtual data items in this container.
53  type, public :: virtualdatacontainertype
54  integer(I4B) :: id !< unique identifier matching with the real counterpart
55  integer(I4B) :: container_type !< to identify the actual type of this container
56  character(LENCOMPONENTNAME) :: name !< container name (model, exchange, ...) used in the memory path
57  character(LENCONTEXTNAME) :: vmem_ctx !< prefixes virtual memory located on remote processes
58  logical(LGP) :: is_local !< when true, the physical object resides on the same process. However,
59  !! some of its variables can still be remote
60  logical(LGP) :: is_active !< when true, this container is being synchronized
61  integer(I4B) :: orig_rank !< the global rank of the process which holds the physical data for this container
62  type(stlvecint) :: rcv_ranks !< the ranks of processes, other than orig_rank, having this container active
63  !< (only guaranteed to be complete after synchronization)
64 
65  type(listtype) :: virtual_data_list !< a list with all virtual data items for this container
66  type(vdcelementmaptype), dimension(NR_VDC_ELEMENT_MAPS) :: element_maps !< a list with all element maps
67  type(vdcelementluttype), dimension(NR_VDC_ELEMENT_MAPS) :: element_luts !< lookup tables from remote index to local index
68  contains
69  procedure :: vdc_create
70  generic :: map => map_scalar, map_array1d, map_array2d
71  procedure :: prepare_stage => vdc_prepare_stage
72  procedure :: link_items => vdc_link_items
73  procedure :: set_element_map => vdc_set_element_map
74  procedure :: get_vrt_mem_path => vdc_get_vrt_mem_path
75  procedure :: destroy => vdc_destroy
76  procedure :: set_orig_rank => vdc_set_orig_rank
77  procedure :: get_send_items => vdc_get_send_items
78  procedure :: get_recv_items => vdc_get_recv_items
79  procedure :: get_virtual_data => vdc_get_virtual_data
80  procedure :: print_items
81  ! protected
82  procedure :: set
83  ! private
84  procedure, private :: add_to_list
85  procedure, private :: map_scalar
86  procedure, private :: map_array1d
87  procedure, private :: map_array2d
88  procedure, private :: map_internal
89  procedure, private :: vdc_get_virtual_data
90  procedure, private :: get_items_for_stage
92 
93 contains
94 
95  subroutine vdc_create(this, name, id, is_local)
96  class(virtualdatacontainertype) :: this
97  character(len=*) :: name
98  integer(I4B) :: id
99  logical(LGP) :: is_local
100  ! local
101  integer(I4B) :: i
102 
103  this%name = name
104  this%id = id
105  this%is_local = is_local
106  this%vmem_ctx = 'undefined'
107  this%orig_rank = 0
108  this%is_active = .true.
109  this%container_type = vdc_unknown_type
110 
111  do i = 1, size(this%element_maps)
112  this%element_maps(i)%nr_virt_elems = 0
113  this%element_maps(i)%remote_elem_shift => null()
114  end do
115  do i = 1, size(this%element_luts)
116  this%element_luts(i)%max_remote_idx = 0
117  this%element_luts(i)%remote_to_virtual => null()
118  end do
119 
120  call this%rcv_ranks%init()
121 
122  end subroutine vdc_create
123 
124  !> @brief Init virtual data item, without allocation,
125  !< and store it in this container.
126  subroutine set(this, field, var_name, subcmp_name, map_id, is_local)
127  class(virtualdatacontainertype) :: this
128  class(virtualdatatype), pointer :: field
129  character(len=*) :: var_name
130  character(len=*) :: subcmp_name
131  integer(I4B) :: map_id
132  logical(LGP), optional :: is_local
133 
134  field%is_remote = .not. this%is_local
135  field%map_type = map_id
136  if (present(is_local)) field%is_remote = .not. is_local
137  field%var_name = var_name
138  field%subcmp_name = subcmp_name
139  if (subcmp_name == '') then
140  field%mem_path = create_mem_path(this%name)
141  else
142  field%mem_path = create_mem_path(this%name, subcmp_name)
143  end if
144  field%is_reduced = (field%is_remote .and. field%map_type > 0)
145  field%remote_elem_shift => null()
146  field%remote_to_virtual => null()
147  field%virtual_mt => null()
148  call this%add_to_list(field)
149 
150  end subroutine set
151 
152  subroutine add_to_list(this, virtual_data)
153  class(virtualdatacontainertype) :: this
154  class(virtualdatatype), pointer :: virtual_data
155  ! local
156  class(*), pointer :: vdata_ptr
157 
158  vdata_ptr => virtual_data
159  call this%virtual_data_list%Add(vdata_ptr)
160 
161  end subroutine add_to_list
162 
163  subroutine vdc_prepare_stage(this, stage)
164  use simmodule, only: ustop
165  class(virtualdatacontainertype) :: this
166  integer(I4B) :: stage
167 
168  write (*, *) 'Error: prepare_stage should be overridden'
169  call ustop()
170 
171  end subroutine vdc_prepare_stage
172 
173  !> @brief Link all local data items to memory
174  !<
175  subroutine vdc_link_items(this, stage)
176  class(virtualdatacontainertype) :: this
177  integer(I4B) :: stage
178  ! local
179  integer(I4B) :: i
180  class(*), pointer :: vdi
181 
182  do i = 1, this%virtual_data_list%Count()
183  vdi => this%virtual_data_list%GetItem(i)
184  select type (vdi)
185  class is (virtualdatatype)
186  if (vdi%is_remote) cycle
187  if (vdi%check_stage(stage)) call vdi%link()
188  end select
189  end do
190 
191  end subroutine vdc_link_items
192 
193  !> @brief Add the source indexes associated with map_id
194  !! as a element map to this container, such that
195  !< src_indexes(1:n) = (i_orig_1 - 1, ..., i_orig_n - 1)
196  subroutine vdc_set_element_map(this, src_indexes, map_id)
197  class(virtualdatacontainertype) :: this
198  integer(I4B), dimension(:), pointer, contiguous :: src_indexes
199  integer(I4B) :: map_id
200  ! local
201  integer(I4B) :: i, idx_remote, max_remote_idx
202 
203  if (this%element_maps(map_id)%nr_virt_elems > 0) then
204  write (*, *) "Error, VDC element map already set"
205  call ustop()
206  end if
207 
208  this%element_maps(map_id)%nr_virt_elems = size(src_indexes)
209  allocate (this%element_maps(map_id)%remote_elem_shift(size(src_indexes)))
210  do i = 1, size(src_indexes)
211  this%element_maps(map_id)%remote_elem_shift(i) = src_indexes(i) - 1
212  end do
213 
214  max_remote_idx = maxval(src_indexes)
215  this%element_luts(map_id)%max_remote_idx = max_remote_idx
216  allocate (this%element_luts(map_id)%remote_to_virtual(max_remote_idx))
217  do i = 1, max_remote_idx
218  this%element_luts(map_id)%remote_to_virtual(i) = -1
219  end do
220  do i = 1, size(src_indexes)
221  idx_remote = src_indexes(i)
222  this%element_luts(map_id)%remote_to_virtual(idx_remote) = i
223  end do
224 
225  end subroutine vdc_set_element_map
226 
227  subroutine map_scalar(this, vd, stages)
228  class(virtualdatacontainertype) :: this
229  class(virtualdatatype), pointer :: vd
230  integer(I4B), dimension(:) :: stages
231 
232  call this%map_internal(vd, (/0/), stages)
233 
234  end subroutine map_scalar
235 
236  subroutine map_array1d(this, vd, nrow, stages)
237  class(virtualdatacontainertype) :: this
238  class(virtualdatatype), pointer :: vd
239  integer(I4B) :: nrow
240  integer(I4B), dimension(:) :: stages
241 
242  call this%map_internal(vd, (/nrow/), stages)
243 
244  end subroutine map_array1d
245 
246  subroutine map_array2d(this, vd, ncol, nrow, stages)
247  class(virtualdatacontainertype) :: this
248  class(virtualdatatype), pointer :: vd
249  integer(I4B) :: ncol
250  integer(I4B) :: nrow
251  integer(I4B), dimension(:) :: stages
252 
253  call this%map_internal(vd, (/ncol, nrow/), stages)
254 
255  end subroutine map_array2d
256 
257  subroutine map_internal(this, vd, shape, stages)
258  class(virtualdatacontainertype) :: this
259  class(virtualdatatype), pointer :: vd
260  integer(I4B), dimension(:) :: shape
261  integer(I4B), dimension(:) :: stages
262  ! local
263  character(len=LENMEMPATH) :: vm_pth
264  logical(LGP) :: found
265 
266  vd%sync_stages = stages
267  if (vd%is_remote) then
268  ! create new virtual memory item
269  vm_pth = this%get_vrt_mem_path(vd%var_name, vd%subcmp_name)
270  call vd%vm_allocate(vd%var_name, vm_pth, shape)
271  call get_from_memorylist(vd%var_name, vm_pth, vd%virtual_mt, found)
272  if (vd%map_type > 0) then
273  vd%remote_to_virtual => this%element_luts(vd%map_type)%remote_to_virtual
274  vd%remote_elem_shift => this%element_maps(vd%map_type)%remote_elem_shift
275  end if
276  end if
277 
278  end subroutine map_internal
279 
280  !> @brief Get indexes of virtual data items to be
281  !< sent for a given stage and rank
282  subroutine vdc_get_send_items(this, stage, rank, virtual_items)
283  class(virtualdatacontainertype) :: this
284  integer(I4B) :: stage
285  integer(I4B) :: rank
286  type(stlvecint) :: virtual_items
287 
288  call this%get_items_for_stage(stage, virtual_items)
289 
290  end subroutine vdc_get_send_items
291 
292  !> @brief Get indexes of virtual data items to be
293  !< received for a given stage and rank
294  subroutine vdc_get_recv_items(this, stage, rank, virtual_items)
295  class(virtualdatacontainertype) :: this
296  integer(I4B) :: stage
297  integer(I4B) :: rank
298  type(stlvecint) :: virtual_items
299 
300  call this%get_items_for_stage(stage, virtual_items)
301 
302  end subroutine vdc_get_recv_items
303 
304  subroutine get_items_for_stage(this, stage, virtual_items)
305  class(virtualdatacontainertype) :: this
306  integer(I4B) :: stage
307  type(stlvecint) :: virtual_items
308  ! local
309  integer(I4B) :: i
310  class(*), pointer :: obj_ptr
311 
312  do i = 1, this%virtual_data_list%Count()
313  obj_ptr => this%virtual_data_list%GetItem(i)
314  select type (obj_ptr)
315  class is (virtualdatatype)
316  if (.not. obj_ptr%check_stage(stage)) cycle
317  call virtual_items%push_back(i)
318  end select
319  end do
320 
321  end subroutine get_items_for_stage
322 
323  subroutine print_items(this, imon, items)
324  class(virtualdatacontainertype) :: this
325  integer(I4B) :: imon
326  type(stlvecint) :: items
327  ! local
328  integer(I4B) :: i
329  class(virtualdatatype), pointer :: vdi
330 
331  write (imon, *) "=====> items"
332  do i = 1, items%size
333  vdi => get_virtual_data_from_list(this%virtual_data_list, items%at(i))
334  write (imon, *) vdi%var_name, ":", vdi%mem_path
335  end do
336  if (items%size == 0) then
337  write (imon, *) "... empty ...", this%name
338  end if
339  write (imon, *) "<===== items"
340 
341  end subroutine print_items
342 
343  !> @brief Get virtual memory path for a certain variable
344  !<
345  function vdc_get_vrt_mem_path(this, var_name, subcomp_name) result(vrt_path)
346  class(virtualdatacontainertype) :: this
347  character(len=*) :: var_name
348  character(len=*) :: subcomp_name
349  character(len=LENMEMPATH) :: vrt_path
350  ! local
351  class(virtualdatatype), pointer :: vdi
352 
353  vdi => this%vdc_get_virtual_data(var_name, subcomp_name)
354  if (vdi%is_remote) then
355  if (subcomp_name == '') then
356  vrt_path = create_mem_path(this%name, context=this%vmem_ctx)
357  else
358  vrt_path = create_mem_path(this%name, subcomp_name, context=this%vmem_ctx)
359  end if
360  else
361  if (subcomp_name == '') then
362  vrt_path = create_mem_path(this%name)
363  else
364  vrt_path = create_mem_path(this%name, subcomp_name)
365  end if
366  end if
367 
368  end function vdc_get_vrt_mem_path
369 
370  function vdc_get_virtual_data(this, var_name, subcomp_name) result(virtual_data)
371  use simmodule, only: ustop
372  class(virtualdatacontainertype) :: this
373  character(len=*) :: var_name
374  character(len=*) :: subcomp_name
375  class(virtualdatatype), pointer :: virtual_data
376  ! local
377  integer(I4B) :: i
378  class(virtualdatatype), pointer :: vd
379 
380  virtual_data => null()
381  do i = 1, this%virtual_data_list%Count()
382  vd => get_virtual_data_from_list(this%virtual_data_list, i)
383  if (vd%var_name == var_name .and. &
384  vd%subcmp_name == subcomp_name) then
385  virtual_data => vd
386  return
387  end if
388  end do
389 
390  write (*, *) 'Error: unknown virtual variable ', var_name, ' ', subcomp_name
391  call ustop()
392 
393  end function vdc_get_virtual_data
394 
395  subroutine vdc_destroy(this)
396  class(virtualdatacontainertype) :: this
397  ! local
398  integer(I4B) :: i
399  class(*), pointer :: obj
400 
401  call this%rcv_ranks%destroy()
402 
403  do i = 1, size(this%element_maps)
404  if (associated(this%element_maps(i)%remote_elem_shift)) then
405  deallocate (this%element_maps(i)%remote_elem_shift)
406  end if
407  end do
408  do i = 1, size(this%element_luts)
409  if (associated(this%element_luts(i)%remote_to_virtual)) then
410  deallocate (this%element_luts(i)%remote_to_virtual)
411  end if
412  end do
413 
414  do i = 1, this%virtual_data_list%Count()
415  obj => this%virtual_data_list%GetItem(i)
416  select type (obj)
417  class is (virtualdatatype)
418  if (associated(obj%virtual_mt)) then
419  call obj%vm_deallocate()
420  end if
421  end select
422  end do
423  call this%virtual_data_list%Clear()
424 
425  end subroutine vdc_destroy
426 
427  subroutine vdc_set_orig_rank(this, rank)
428  class(virtualdatacontainertype) :: this
429  integer(I4B) :: rank
430 
431  this%orig_rank = rank
432  write (this%vmem_ctx, '(a,i0,a)') '__P', rank, '__'
433 
434  end subroutine vdc_set_orig_rank
435 
436  function get_vdc_from_list(list, idx) result(vdc)
437  type(listtype) :: list
438  integer(I4B) :: idx
439  class(virtualdatacontainertype), pointer :: vdc
440  ! local
441  class(*), pointer :: obj_ptr
442 
443  vdc => null()
444  obj_ptr => list%GetItem(idx)
445  select type (obj_ptr)
446  class is (virtualdatacontainertype)
447  vdc => obj_ptr
448  end select
449 
450  end function get_vdc_from_list
451 
452  !> @ Converts a virtual container type to its string representation
453  !<
454  function vdc_type_to_str(cntr_type) result(cntr_str)
455  integer(I4B) :: cntr_type
456  character(len=24) :: cntr_str
457 
458  if (cntr_type == vdc_unknown_type) then; cntr_str = "unknown"
459  else if (cntr_type == vdc_gwfmodel_type) then; cntr_str = "GWF Model"
460  else if (cntr_type == vdc_gwtmodel_type) then; cntr_str = "GWT Model"
461  else if (cntr_type == vdc_gwemodel_type) then; cntr_str = "GWE Model"
462  else if (cntr_type == vdc_gwfexg_type) then; cntr_str = "GWF Exchange"
463  else if (cntr_type == vdc_gwtexg_type) then; cntr_str = "GWT Exchange"
464  else if (cntr_type == vdc_gweexg_type) then; cntr_str = "GWE Exchange"
465  else if (cntr_type == vdc_gwfmvr_type) then; cntr_str = "GWF Mover"
466  else if (cntr_type == vdc_gwtmvt_type) then; cntr_str = "GWT Mover"
467  else if (cntr_type == vdc_gwemve_type) then; cntr_str = "GWE Mover"
468  else; cntr_str = "Undefined"
469  end if
470 
471  end function vdc_type_to_str
472 
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lencomponentname
maximum length of a component name
Definition: Constants.f90:18
integer(i4b), parameter lencontextname
maximum length of a memory manager context
Definition: Constants.f90:19
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:26
This module defines variable data types.
Definition: kind.f90:8
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine, public get_from_memorylist(name, mem_path, mt, found, check)
@ brief Get a memory type entry from the memory list
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public ustop(stopmess, ioutlocal)
Stop the simulation.
Definition: Sim.f90:315
subroutine destroy(this)
Definition: STLVecInt.f90:170
class(virtualdatatype) function, pointer, public get_virtual_data_from_list(list, idx)
class(virtualdatatype) function, pointer vdc_get_virtual_data(this, var_name, subcomp_name)
integer(i4b), parameter, public vdc_gwtmodel_type
subroutine vdc_create(this, name, id, is_local)
integer(i4b), parameter, public vdc_gwtmvt_type
subroutine vdc_get_recv_items(this, stage, rank, virtual_items)
Get indexes of virtual data items to be.
subroutine map_internal(this, vd, shape, stages)
subroutine set(this, field, var_name, subcmp_name, map_id, is_local)
Init virtual data item, without allocation,.
integer(i4b), parameter, public vdc_gwemodel_type
character(len=24) function, public vdc_type_to_str(cntr_type)
@ Converts a virtual container type to its string representation
subroutine map_array2d(this, vd, ncol, nrow, stages)
subroutine vdc_link_items(this, stage)
Link all local data items to memory.
subroutine map_scalar(this, vd, stages)
subroutine vdc_set_element_map(this, src_indexes, map_id)
Add the source indexes associated with map_id as a element map to this container, such that.
subroutine vdc_get_send_items(this, stage, rank, virtual_items)
Get indexes of virtual data items to be.
subroutine add_to_list(this, virtual_data)
integer(i4b), parameter, public vdc_gwfmvr_type
integer(i4b), parameter, public vdc_unknown_type
character(len=lenmempath) function vdc_get_vrt_mem_path(this, var_name, subcomp_name)
Get virtual memory path for a certain variable.
subroutine vdc_set_orig_rank(this, rank)
integer(i4b), parameter, public vdc_gwemve_type
of VdcPtrType instead.
subroutine vdc_prepare_stage(this, stage)
integer(i4b), parameter, public vdc_gwfmodel_type
subroutine print_items(this, imon, items)
integer(i4b), parameter, public vdc_gwtexg_type
class(virtualdatacontainertype) function, pointer, public get_vdc_from_list(list, idx)
subroutine map_array1d(this, vd, nrow, stages)
integer(i4b), parameter, public vdc_gwfexg_type
integer(i4b), parameter, public vdc_gweexg_type
subroutine get_items_for_stage(this, stage, virtual_items)
A generic heterogeneous doubly-linked list.
Definition: List.f90:10
This is a generic data structure to virtualize pieces of memory in 2 distinct ways:
Definition: VirtualBase.f90:35
Wrapper for virtual data containers.