MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
GwfExchangeMover.f90
Go to the documentation of this file.
2  use kindmodule, only: i4b, dp, lgp
7  use basedismodule
8  use gwfmvrmodule
10  implicit none
11  private
12 
13  public :: exg_mvr_cr
14 
15  !> @brief Extends model mover for exchanges to also handle the
16  !< parallel case where the models are not on the same process.
17  type, public, extends(gwfmvrtype) :: gwfexgmovertype
18  class(virtualmodeltype), pointer :: model1 => null() !< virtual model 1
19  class(virtualmodeltype), pointer :: model2 => null() !< virtual model 2
20  logical(LGP), dimension(:), pointer, contiguous :: prov_is_m1 => null() !< .true. when the providing package is part of model 1
21  real(dp), dimension(:), pointer, contiguous :: qpactual_m1 => null() !< stores qpactual for synchronization when provider is in model 1
22  real(dp), dimension(:), pointer, contiguous :: qpactual_m2 => null() !< stores qpactual for synchronization when provider is in model 2
23  real(dp), dimension(:), pointer, contiguous :: qavailable_m1 => null() !< stores qavailable for synchronization when provider is in model 1
24  real(dp), dimension(:), pointer, contiguous :: qavailable_m2 => null() !< stores qavailable for synchronization when provider is in model 2
25  integer(I4B), dimension(:), pointer, contiguous :: id_mapped_m1 => null() !< stores the mapped feature ids for synchronization when provider is in model 1
26  integer(I4B), dimension(:), pointer, contiguous :: id_mapped_m2 => null() !< stores the mapped feature ids for synchronization when provider is in model 2
27  contains
28  procedure :: mvr_da => xmvr_da
29  procedure :: xmvr_cf
30  procedure :: mvr_fc => xmvr_fc
31  procedure :: mvr_bd => xmvr_bd
36  end type
37 
38 contains
39 
40  subroutine exg_mvr_cr(exg_mvr, name_parent, inunit, iout, dis)
41  class(gwfexgmovertype), pointer :: exg_mvr
42  character(len=*), intent(in) :: name_parent
43  integer(I4B), intent(in) :: inunit
44  integer(I4B), intent(in) :: iout
45  class(disbasetype), pointer :: dis
46 
47  allocate (exg_mvr)
48 
49  ! Init through base
50  call exg_mvr%mvr_init(name_parent, inunit, iout, dis, 1)
51 
52  end subroutine exg_mvr_cr
53 
54  subroutine xmvr_check_packages(this)
55  use constantsmodule, only: linelength
58  class(gwfexgmovertype), intent(inout) :: this
59  ! local
60  character(len=LENMODELNAME) :: mname
61  character(len=LENPACKAGENAME) :: pname
62  class(virtualmodeltype), pointer :: vm
63  character(len=LINELENGTH) :: errmsg
64  integer(I4B) :: i
65  integer(I4B), pointer :: imover_ptr
66 
67  do i = 1, size(this%pckMemPaths)
68  ! check only when local
69  call split_mem_path(this%pckMemPaths(i), mname, pname)
70  vm => get_virtual_model(mname)
71  if (vm%is_local) then
72  ! check if PackageMover is active in package:
73  imover_ptr => null()
74  call mem_setptr(imover_ptr, 'IMOVER', trim(this%pckMemPaths(i)))
75  if (imover_ptr == 0) then
76  write (errmsg, '(a, a, a)') &
77  'ERROR. MODEL AND PACKAGE "', &
78  trim(this%pckMemPaths(i)), &
79  '" DOES NOT HAVE MOVER SPECIFIED IN OPTIONS BLOCK.'
80  call store_error(errmsg)
81  end if
82  end if
83  end do
84 
85  if (count_errors() > 0) then
86  call this%parser%StoreErrorUnit()
87  end if
88 
89  end subroutine xmvr_check_packages
90 
91  !> @brief Overrides GWF MVR routine to skip assigning
92  !< pointers when the package is not local
93  subroutine xmvr_assign_packagemovers(this)
94  class(gwfexgmovertype), intent(inout) :: this !< this exchange mover
95  ! local
96  integer(I4B) :: i
97  character(len=LENMODELNAME) :: mname
98  character(len=LENPACKAGENAME) :: pname
99  class(virtualmodeltype), pointer :: vm
100 
101  do i = 1, size(this%pckMemPaths)
102  if (this%pakmovers(i)%memoryPath == '') then
103  ! is it local?
104  call split_mem_path(this%pckMemPaths(i), mname, pname)
105  vm => get_virtual_model(mname)
106  if (vm%is_local) then
107  ! yes, we need the pointers
108  call set_packagemover_pointer(this%pakmovers(i), &
109  trim(this%pckMemPaths(i)))
110  end if
111  end if
112  end do
113  end subroutine xmvr_assign_packagemovers
114 
115  !> @brief Overrides mover initialization in GWF MVR to
116  !! deactivate remote parts and build up sync. arrays
117  !< for mapped feature ids
118  subroutine xmvr_initialize_movers(this, nr_active_movers)
119  class(gwfexgmovertype) :: this
120  integer(I4B) :: nr_active_movers
121  ! local
122  integer(I4B) :: i
123  character(len=LENMODELNAME) :: mname
124  character(len=LENPACKAGENAME) :: pname
125  class(virtualmodeltype), pointer :: vm
126  class(packagemovertype), allocatable :: pkg_mvr
127 
128  call this%GwfMvrType%initialize_movers(nr_active_movers)
129 
130  this%prov_is_m1 = .false.
131 
132  ! deactivate remote parts
133  do i = 1, nr_active_movers
134  call split_mem_path(this%mvr(i)%mem_path_src, mname, pname)
135  vm => get_virtual_model(mname)
136  this%mvr(i)%is_provider_active = vm%is_local
137  this%prov_is_m1(i) = associated(vm, this%model1)
138  call split_mem_path(this%mvr(i)%mem_path_tgt, mname, pname)
139  vm => get_virtual_model(mname)
140  this%mvr(i)%is_receiver_active = vm%is_local
141  end do
142 
143  ! loop over mvr's, if provider is active,
144  ! store mapped feature index in array for sync
145  allocate (pkg_mvr)
146 
147  do i = 1, nr_active_movers
148  if (this%mvr(i)%is_provider_active) then
149  ! store mapped feature id in array (for synchronization when parallel)
150  call set_packagemover_pointer(pkg_mvr, this%mvr(i)%mem_path_src)
151  if (this%prov_is_m1(i)) then
152  this%id_mapped_m1(i) = pkg_mvr%iprmap(this%mvr(i)%iRchNrSrc)
153  this%id_mapped_m2(i) = -1
154  else
155  this%id_mapped_m1(i) = -1
156  this%id_mapped_m2(i) = pkg_mvr%iprmap(this%mvr(i)%iRchNrSrc)
157  end if
158  end if
159  end do
160 
161  end subroutine xmvr_initialize_movers
162 
163  !> @brief Calculates qpactual and stores it for synchronization
164  !<
165  subroutine xmvr_cf(this)
166  class(gwfexgmovertype) :: this
167  ! local
168  integer(I4B) :: i
169 
170  do i = 1, this%nmvr
171  if (this%mvr(i)%is_provider_active) then
172 
173  call this%mvr(i)%update_provider()
174 
175  ! copy calculated rate to arrays for synchronization:
176  if (this%prov_is_m1(i)) then
177  this%qpactual_m1(i) = this%mvr(i)%qpactual
178  this%qavailable_m1(i) = this%mvr(i)%qavailable
179  this%qpactual_m2(i) = dnodata
180  this%qavailable_m2(i) = dnodata
181  else
182  this%qpactual_m1(i) = dnodata
183  this%qavailable_m1(i) = dnodata
184  this%qpactual_m2(i) = this%mvr(i)%qpactual
185  this%qavailable_m2(i) = this%mvr(i)%qavailable
186  end if
187  end if
188  end do
189 
190  end subroutine xmvr_cf
191 
192  !> @brief Assign synced qpactual to mover and update receiver
193  !<
194  subroutine xmvr_fc(this)
195  class(gwfexgmovertype) :: this
196  ! local
197  integer(I4B) :: i
198 
199  do i = 1, this%nmvr
200  if (this%mvr(i)%is_receiver_active) then
201  ! copy from synchronization arrays back into movers:
202  if (this%prov_is_m1(i)) then
203  this%mvr(i)%qpactual = this%qpactual_m1(i)
204  this%mvr(i)%qavailable = this%qavailable_m1(i)
205  else
206  this%mvr(i)%qpactual = this%qpactual_m2(i)
207  this%mvr(i)%qavailable = this%qavailable_m2(i)
208  end if
209  call this%mvr(i)%update_receiver()
210  end if
211  end do
212 
213  end subroutine xmvr_fc
214 
215  !> @brief Overrides budget routine to first assign the
216  !< mapped features ids from the synchronization arrays
217  subroutine xmvr_bd(this)
218  class(gwfexgmovertype) :: this
219  ! local
220  integer(I4B) :: i
221 
222  ! copy from synchronization arrays back into movers:
223  do i = 1, this%nmvr
224  if (this%prov_is_m1(i)) then
225  this%mvr(i)%iRchNrSrcMapped = this%id_mapped_m1(i)
226  else
227  this%mvr(i)%iRchNrSrcMapped = this%id_mapped_m2(i)
228  end if
229  end do
230 
231  call this%fill_budobj()
232 
233  end subroutine xmvr_bd
234 
235  subroutine xmvr_allocate_arrays(this)
236  class(gwfexgmovertype) :: this
237  ! local
238  integer(I4B) :: i
239 
240  call this%GwfMvrType%allocate_arrays()
241 
242  allocate (this%prov_is_m1(this%maxmvr))
243  call mem_allocate(this%qpactual_m1, this%maxmvr, 'QPACTUAL_M1', &
244  this%memoryPath)
245  call mem_allocate(this%qpactual_m2, this%maxmvr, 'QPACTUAL_M2', &
246  this%memoryPath)
247  call mem_allocate(this%qavailable_m1, this%maxmvr, 'QAVAILABLE_M1', &
248  this%memoryPath)
249  call mem_allocate(this%qavailable_m2, this%maxmvr, 'QAVAILABLE_M2', &
250  this%memoryPath)
251  call mem_allocate(this%id_mapped_m1, this%maxmvr, 'ID_MAPPED_M1', &
252  this%memoryPath)
253  call mem_allocate(this%id_mapped_m2, this%maxmvr, 'ID_MAPPED_M2', &
254  this%memoryPath)
255 
256  do i = 1, this%maxmvr
257  this%id_mapped_m1(i) = 0
258  this%id_mapped_m2(i) = 0
259  this%qpactual_m1(i) = dnodata
260  this%qpactual_m2(i) = dnodata
261  this%qavailable_m1(i) = dnodata
262  this%qavailable_m2(i) = dnodata
263  end do
264 
265  end subroutine xmvr_allocate_arrays
266 
267  subroutine xmvr_da(this)
268  class(gwfexgmovertype) :: this
269 
270  call this%GwfMvrType%mvr_da()
271 
272  deallocate (this%prov_is_m1)
273  call mem_deallocate(this%qpactual_m1)
274  call mem_deallocate(this%qpactual_m2)
275  call mem_deallocate(this%qavailable_m1)
276  call mem_deallocate(this%qavailable_m2)
277  call mem_deallocate(this%id_mapped_m1)
278  call mem_deallocate(this%id_mapped_m2)
279 
280  end subroutine xmvr_da
281 
282 end module gwfexgmovermodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:44
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:21
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:22
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:94
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
subroutine xmvr_initialize_movers(this, nr_active_movers)
Overrides mover initialization in GWF MVR to deactivate remote parts and build up sync....
subroutine xmvr_da(this)
subroutine xmvr_assign_packagemovers(this)
Overrides GWF MVR routine to skip assigning.
subroutine xmvr_check_packages(this)
subroutine xmvr_fc(this)
Assign synced qpactual to mover and update receiver.
subroutine xmvr_cf(this)
Calculates qpactual and stores it for synchronization.
subroutine xmvr_bd(this)
Overrides budget routine to first assign the.
subroutine, public exg_mvr_cr(exg_mvr, name_parent, inunit, iout, dis)
subroutine xmvr_allocate_arrays(this)
subroutine mvr_da(this)
Deallocate.
Definition: gwf-mvr.f90:665
subroutine initialize_movers(this, nr_active_movers)
Definition: gwf-mvr.f90:416
subroutine check_packages(this)
Check to make sure packages have mover activated.
Definition: gwf-mvr.f90:981
subroutine mvr_bd(this)
Fill the mover budget object.
Definition: gwf-mvr.f90:495
subroutine assign_packagemovers(this)
Assign pointer to each package's packagemover object.
Definition: gwf-mvr.f90:1017
subroutine mvr_fc(this)
Calculate qfrommvr as a function of qtomvr.
Definition: gwf-mvr.f90:451
subroutine allocate_arrays(this)
Allocate package arrays.
Definition: gwf-mvr.f90:1080
This module defines variable data types.
Definition: kind.f90:8
subroutine split_mem_path(mem_path, component, subcomponent)
Split the memory path into component(s)
subroutine, public set_packagemover_pointer(packagemover, memPath)
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
Extends model mover for exchanges to also handle the.