MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
VirtualExchange.f90
Go to the documentation of this file.
5  use kindmodule, only: i4b, lgp
6  use listmodule, only: listtype
10  implicit none
11  private
12 
13  public :: get_virtual_exchange
15  private :: cast_as_virtual_exchange
16 
17  !> The Virtual Exchange is based on two Virtual Models
18  !! and is therefore not always strictly local or remote.
19  !! We have to consider three different cases:
20  !!
21  !! 1) both virtual models are local
22  !!
23  !! RECV: In this case this virtual data container will have
24  !! no data items to receive from other processes.
25  !! SEND: Whenever it is called to send its virtual data items
26  !! to other processes, it simply sends everything.
27  !!
28  !! 2) one model is local, one model is remote
29  !!
30  !! Consequently, there is another exchange which
31  !! has the reverse, we call this our _dual_ exchange.
32  !!
33  !! RECV: The sender is our dual exchange, and we have all data
34  !! except its list of reduced model node numbers, either
35  !! this%nodem1 or this%nodem2. We receive the missing
36  !! array. Receiving from a sender that is not the dual
37  !! exchange cannot occur.
38  !!
39  !! SEND: here we have to consider two cases
40  !! a) The receiver is our dual exchange, we return the favor
41  !! and send the list of model node numbers that is present
42  !! on this process, this
43  !! would be either this%nodem1 or this%nodem2
44  !! b) The receiver is not the dual exchange. And here we will
45  !! send everything.
46  !!
47  !! 3) both models are remote
48  !!
49  !! RECV: we will receive everything. In case the source
50  !! exchange is fully local, i.e. type 1) above, we get
51  !! all the data at the first attempt. Otherwise, it will
52  !! take a second attempt before all the data is in.
53  !! (To allow for two attempts, the nodem1 and nodem2
54  !! arrays are registered to be synchronized at two
55  !! consecutive stages)
56  !!
57  !! SEND: nothing to be sent.
58  !!
59  !! Exchange mover data follows the pattern described above for nodem1/m2
60  !! except that when both models are remote, none of the mover data is
61  !! will be synchronized.
62  !!
63  !! This behavior is different from the general VirtualDataContainer,
64  !! so the get_send_items and get_recv_items subroutines are
65  !! overridden accordingly.
66  !! Additionally, for case 2) the container will have a mix of
67  !< local and remote virtual data items.
69  class(virtualmodeltype), pointer :: v_model1 => null()
70  class(virtualmodeltype), pointer :: v_model2 => null()
71  ! scalars
72  type(virtualinttype), pointer :: nexg => null()
73  type(virtualinttype), pointer :: naux => null()
74  type(virtualinttype), pointer :: ianglex => null()
75  ! arrays
76  type(virtualint1dtype), pointer :: nodem1 => null()
77  type(virtualint1dtype), pointer :: nodem2 => null()
78  type(virtualint1dtype), pointer :: ihc => null()
79  type(virtualdbl1dtype), pointer :: cl1 => null()
80  type(virtualdbl1dtype), pointer :: cl2 => null()
81  type(virtualdbl1dtype), pointer :: hwva => null()
82  type(virtualdbl2dtype), pointer :: auxvar => null()
83  contains
84  procedure :: create => vx_create
85  procedure :: prepare_stage => vx_prepare_stage
86  procedure :: get_send_items => vx_get_send_items
87  procedure :: get_recv_items => vx_get_recv_items
88  procedure :: has_mover => vx_has_mover
89  procedure :: destroy => vx_destroy
90  ! protected
91  procedure :: add_vdi_for_stage
92  ! private
93  procedure, private :: init_virtual_data
94  procedure, private :: allocate_data
95  procedure, private :: deallocate_data
96  end type virtualexchangetype
97 
98 contains
99 
100  !> @brief Create the virtual exchange base
101  !<
102  subroutine vx_create(this, name, exg_id, m1_id, m2_id)
103  class(virtualexchangetype) :: this
104  character(len=*) :: name
105  integer(I4B) :: exg_id
106  integer(I4B) :: m1_id
107  integer(I4B) :: m2_id
108  ! local
109  logical(LGP) :: is_local
110 
111  this%v_model1 => get_virtual_model(m1_id)
112  this%v_model2 => get_virtual_model(m2_id)
113 
114  ! 1) both models local: is_local = true
115  ! 2) only one of them: is_local = true
116  ! 3) both models remote: is_local = false
117  is_local = this%v_model1%is_local .or. this%v_model2%is_local
118  call this%VirtualDataContainerType%vdc_create(name, exg_id, is_local)
119 
120  call this%allocate_data()
121  call this%init_virtual_data()
122 
123  end subroutine vx_create
124 
125  subroutine init_virtual_data(this)
126  class(virtualexchangetype) :: this
127  ! local
128  logical(LGP) :: is_nodem1_local
129  logical(LGP) :: is_nodem2_local
130 
131  ! exchanges can be hybrid with both local and remote
132  ! fields, nodem1/2 array only local when corresponding
133  ! model sits on the same process
134  is_nodem1_local = this%v_model1%is_local
135  is_nodem2_local = this%v_model2%is_local
136  call this%set(this%nexg%base(), 'NEXG', '', map_all_type)
137  call this%set(this%naux%base(), 'NAUX', '', map_all_type)
138  call this%set(this%ianglex%base(), 'IANGLEX', '', map_all_type)
139  call this%set(this%nodem1%base(), 'NODEM1', '', &
140  map_all_type, is_nodem1_local)
141  call this%set(this%nodem2%base(), 'NODEM2', '', &
142  map_all_type, is_nodem2_local)
143  call this%set(this%ihc%base(), 'IHC', '', map_all_type)
144  call this%set(this%cl1%base(), 'CL1', '', map_all_type)
145  call this%set(this%cl2%base(), 'CL2', '', map_all_type)
146  call this%set(this%hwva%base(), 'HWVA', '', map_all_type)
147  call this%set(this%auxvar%base(), 'AUXVAR', '', map_all_type)
148 
149  end subroutine init_virtual_data
150 
151  subroutine vx_prepare_stage(this, stage)
152  class(virtualexchangetype) :: this
153  integer(I4B) :: stage
154  ! local
155  integer(I4B) :: nexg, naux
156 
157  if (stage == stg_aft_exg_df) then
158 
159  call this%map(this%nexg%base(), (/stg_aft_exg_df/))
160  call this%map(this%naux%base(), (/stg_aft_exg_df/))
161  call this%map(this%ianglex%base(), (/stg_aft_exg_df/))
162 
163  else if (stage == stg_aft_con_cr) then
164 
165  nexg = this%nexg%get()
166  naux = this%naux%get()
167  call this%map(this%nodem1%base(), nexg, (/stg_aft_con_cr, &
168  stg_bfr_con_df/))
169  call this%map(this%nodem2%base(), nexg, (/stg_aft_con_cr, &
170  stg_bfr_con_df/))
171  call this%map(this%ihc%base(), nexg, (/stg_aft_con_cr/))
172  call this%map(this%cl1%base(), nexg, (/stg_aft_con_cr/))
173  call this%map(this%cl2%base(), nexg, (/stg_aft_con_cr/))
174  call this%map(this%hwva%base(), nexg, (/stg_aft_con_cr/))
175  call this%map(this%auxvar%base(), naux, nexg, (/stg_aft_con_cr/))
176 
177  end if
178 
179  end subroutine vx_prepare_stage
180 
181  subroutine vx_get_recv_items(this, stg, rank, vi)
182  class(virtualexchangetype) :: this
183  integer(I4B) :: stg
184  integer(I4B) :: rank
185  type(stlvecint) :: vi
186 
187  if (this%is_local .and. rank == this%orig_rank) then
188  ! treat the primary exchange case independently, we
189  ! have all data available except for nodem1 or nodem2
190  if (stg < stg_bfr_con_df) then
191  if (this%nodem1%is_remote) then
192  call this%add_vdi_for_stage(this%nodem1%base(), stg, vi)
193  end if
194  if (this%nodem2%is_remote) then
195  call this%add_vdi_for_stage(this%nodem2%base(), stg, vi)
196  end if
197  end if
198  else
199  ! send/receive all
200  call this%add_vdi_for_stage(this%nexg%base(), stg, vi)
201  call this%add_vdi_for_stage(this%naux%base(), stg, vi)
202  call this%add_vdi_for_stage(this%ianglex%base(), stg, vi)
203  call this%add_vdi_for_stage(this%nodem1%base(), stg, vi)
204  call this%add_vdi_for_stage(this%nodem2%base(), stg, vi)
205  call this%add_vdi_for_stage(this%ihc%base(), stg, vi)
206  call this%add_vdi_for_stage(this%cl1%base(), stg, vi)
207  call this%add_vdi_for_stage(this%cl2%base(), stg, vi)
208  call this%add_vdi_for_stage(this%hwva%base(), stg, vi)
209  call this%add_vdi_for_stage(this%auxvar%base(), stg, vi)
210  end if
211 
212  end subroutine vx_get_recv_items
213 
214  subroutine vx_get_send_items(this, stg, rank, vi)
215  class(virtualexchangetype) :: this
216  integer(I4B) :: stg
217  integer(I4B) :: rank
218  type(stlvecint) :: vi
219 
220  if (this%is_local .and. rank == this%orig_rank) then
221  ! this is a primary exchange, all we need to send are
222  ! the node numbers nodem1 or nodem2
223  if (stg < stg_bfr_con_df) then
224  if (.not. this%nodem1%is_remote) then
225  call this%add_vdi_for_stage(this%nodem1%base(), stg, vi)
226  end if
227  if (.not. this%nodem2%is_remote) then
228  call this%add_vdi_for_stage(this%nodem2%base(), stg, vi)
229  end if
230  end if
231  else
232  ! send/receive all
233  call this%add_vdi_for_stage(this%nexg%base(), stg, vi)
234  call this%add_vdi_for_stage(this%naux%base(), stg, vi)
235  call this%add_vdi_for_stage(this%ianglex%base(), stg, vi)
236  call this%add_vdi_for_stage(this%nodem1%base(), stg, vi)
237  call this%add_vdi_for_stage(this%nodem2%base(), stg, vi)
238  call this%add_vdi_for_stage(this%ihc%base(), stg, vi)
239  call this%add_vdi_for_stage(this%cl1%base(), stg, vi)
240  call this%add_vdi_for_stage(this%cl2%base(), stg, vi)
241  call this%add_vdi_for_stage(this%hwva%base(), stg, vi)
242  call this%add_vdi_for_stage(this%auxvar%base(), stg, vi)
243  end if
244 
245  end subroutine vx_get_send_items
246 
247  !> @brief Convenience routine to add virtual data item to a list
248  !< after checking the stage
249  subroutine add_vdi_for_stage(this, vdata_item, stage, virtual_items)
250  class(virtualexchangetype) :: this
251  class(virtualdatatype), pointer :: vdata_item
252  integer(I4B) :: stage
253  type(stlvecint) :: virtual_items
254  ! local
255  class(*), pointer :: vdi
256  integer(I4B) :: idx
257 
258  vdi => vdata_item
259  idx = this%virtual_data_list%GetIndex(vdi)
260  if (vdata_item%check_stage(stage)) then
261  call virtual_items%push_back(idx)
262  end if
263 
264  end subroutine add_vdi_for_stage
265 
266  !> @brief Checks if there is an active mover in the exchange
267  !<
268  function vx_has_mover(this) result(has_mover)
269  class(virtualexchangetype) :: this
270  logical(LGP) :: has_mover
271 
272  has_mover = .false.
273 
274  end function vx_has_mover
275 
276  subroutine vx_destroy(this)
277  class(virtualexchangetype) :: this
278 
279  call this%VirtualDataContainerType%destroy()
280  call this%deallocate_data()
281 
282  end subroutine vx_destroy
283 
284  subroutine allocate_data(this)
285  class(virtualexchangetype) :: this
286 
287  allocate (this%nexg)
288  allocate (this%naux)
289  allocate (this%ianglex)
290  allocate (this%nodem1)
291  allocate (this%nodem2)
292  allocate (this%ihc)
293  allocate (this%cl1)
294  allocate (this%cl2)
295  allocate (this%hwva)
296  allocate (this%auxvar)
297 
298  end subroutine allocate_data
299 
300  subroutine deallocate_data(this)
301  class(virtualexchangetype) :: this
302 
303  deallocate (this%nexg)
304  deallocate (this%naux)
305  deallocate (this%ianglex)
306  deallocate (this%nodem1)
307  deallocate (this%nodem2)
308  deallocate (this%ihc)
309  deallocate (this%cl1)
310  deallocate (this%cl2)
311  deallocate (this%hwva)
312  deallocate (this%auxvar)
313 
314  end subroutine deallocate_data
315 
316  !> @brief Returns a virtual exchange with the specified id
317  !< from the global list
318  function get_virtual_exchange(exg_id) result(virtual_exg)
320  integer(I4B) :: exg_id
321  class(virtualexchangetype), pointer :: virtual_exg
322  ! local
323  integer(I4B) :: i
324  class(*), pointer :: ve
325 
326  virtual_exg => null()
327  do i = 1, virtual_exchange_list%Count()
328  ve => virtual_exchange_list%GetItem(i)
329  select type (ve)
330  class is (virtualexchangetype)
331  if (ve%id == exg_id) then
332  virtual_exg => ve
333  return
334  end if
335  end select
336  end do
337 
338  end function get_virtual_exchange
339 
340  function get_virtual_exchange_from_list(list, idx) result(virtual_exg)
341  type(listtype) :: list
342  integer(I4B) :: idx
343  class(virtualexchangetype), pointer :: virtual_exg
344  ! local
345  class(*), pointer :: obj_ptr
346 
347  obj_ptr => list%GetItem(idx)
348  virtual_exg => cast_as_virtual_exchange(obj_ptr)
349 
350  end function get_virtual_exchange_from_list
351 
352  function cast_as_virtual_exchange(obj_ptr) result(virtual_exg)
353  class(*), pointer :: obj_ptr
354  class(virtualexchangetype), pointer :: virtual_exg
355 
356  virtual_exg => null()
357  select type (obj_ptr)
358  class is (virtualexchangetype)
359  virtual_exg => obj_ptr
360  end select
361 
362  end function cast_as_virtual_exchange
363 
364 end module virtualexchangemodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenexchangename
maximum length of the exchange name
Definition: Constants.f90:24
This module defines variable data types.
Definition: kind.f90:8
integer(i4b), parameter, public stg_aft_exg_df
after exchange define
Definition: SimStages.f90:12
integer(i4b), parameter, public stg_aft_con_cr
after connection create
Definition: SimStages.f90:13
integer(i4b), parameter, public stg_bfr_con_df
before connection define
Definition: SimStages.f90:14
subroutine destroy(this)
Definition: STLVecInt.f90:183
integer(i4b), parameter, public map_all_type
Definition: VirtualBase.f90:13
type(listtype), public virtual_exchange_list
subroutine deallocate_data(this)
subroutine init_virtual_data(this)
logical(lgp) function vx_has_mover(this)
Checks if there is an active mover in the exchange.
subroutine allocate_data(this)
subroutine add_vdi_for_stage(this, vdata_item, stage, virtual_items)
Convenience routine to add virtual data item to a list.
class(virtualexchangetype) function, pointer, private cast_as_virtual_exchange(obj_ptr)
subroutine vx_get_recv_items(this, stg, rank, vi)
class(virtualexchangetype) function, pointer, public get_virtual_exchange_from_list(list, idx)
subroutine vx_create(this, name, exg_id, m1_id, m2_id)
Create the virtual exchange base.
class(virtualexchangetype) function, pointer, public get_virtual_exchange(exg_id)
Returns a virtual exchange with the specified id.
subroutine vx_prepare_stage(this, stage)
subroutine vx_get_send_items(this, stg, rank, vi)
subroutine vx_destroy(this)
A generic heterogeneous doubly-linked list.
Definition: List.f90:14
This is a generic data structure to virtualize pieces of memory in 2 distinct ways:
Definition: VirtualBase.f90:35
The Virtual Exchange is based on two Virtual Models and is therefore not always strictly local or rem...