MODFLOW 6  version 6.7.0.dev0
USGS Modular Hydrologic Model
exg-gwfprt.f90
Go to the documentation of this file.
2 
3  use kindmodule, only: dp, i4b
6  use simmodule, only: store_error
7  use simvariablesmodule, only: errmsg
10  use gwfmodule, only: gwfmodeltype
11  use prtmodule, only: prtmodeltype
12  use bndmodule, only: bndtype, getbndfromlist
13 
14  implicit none
15  public :: gwfprtexchangetype
16  public :: gwfprt_cr
17 
19 
20  integer(I4B), pointer :: m1id => null()
21  integer(I4B), pointer :: m2id => null()
22 
23  contains
24 
25  procedure :: exg_df
26  procedure :: exg_ar
27  procedure :: exg_da
28  procedure, private :: set_model_pointers
29  procedure, private :: allocate_scalars
30  procedure, private :: gwfbnd2prtfmi
31  ! procedure, private :: gwfconn2prtconn
32  ! procedure, private :: link_connections
33 
34  end type gwfprtexchangetype
35 
36 contains
37 
38  !> @brief Create a new GWF to PRT exchange object
39  subroutine gwfprt_cr(filename, id, m1id, m2id)
40  ! -- modules
42  ! -- dummy
43  character(len=*), intent(in) :: filename
44  integer(I4B), intent(in) :: id
45  integer(I4B), intent(in) :: m1id
46  integer(I4B), intent(in) :: m2id
47  ! -- local
48  class(baseexchangetype), pointer :: baseexchange => null()
49  type(gwfprtexchangetype), pointer :: exchange => null()
50  character(len=20) :: cint
51  !
52  ! -- Create a new exchange and add it to the baseexchangelist container
53  allocate (exchange)
54  baseexchange => exchange
55  call addbaseexchangetolist(baseexchangelist, baseexchange)
56  !
57  ! -- Assign id and name
58  exchange%id = id
59  write (cint, '(i0)') id
60  exchange%name = 'GWF-PRT_'//trim(adjustl(cint))
61  exchange%memoryPath = exchange%name
62  !
63  ! -- allocate scalars
64  call exchange%allocate_scalars()
65  !
66  ! -- NB: convert from id to local model index in base model list
67  exchange%m1id = model_loc_idx(m1id)
68  exchange%m2id = model_loc_idx(m2id)
69  !
70  ! -- set model pointers
71  call exchange%set_model_pointers()
72  end subroutine gwfprt_cr
73 
74  subroutine set_model_pointers(this)
75  ! -- modules
76  ! -- dummy
77  class(gwfprtexchangetype) :: this
78  ! -- local
79  class(basemodeltype), pointer :: mb => null()
80  type(gwfmodeltype), pointer :: gwfmodel => null()
81  type(prtmodeltype), pointer :: prtmodel => null()
82  !
83  ! -- set gwfmodel
84  mb => getbasemodelfromlist(basemodellist, this%m1id)
85  select type (mb)
86  type is (gwfmodeltype)
87  gwfmodel => mb
88  end select
89  !
90  ! -- set prtmodel
91  mb => getbasemodelfromlist(basemodellist, this%m2id)
92  select type (mb)
93  type is (prtmodeltype)
94  prtmodel => mb
95  end select
96  !
97  ! -- Verify that GWF model is of the correct type
98  if (.not. associated(gwfmodel)) then
99  write (errmsg, '(3a)') 'Problem with GWF-PRT exchange ', trim(this%name), &
100  '. Specified GWF Model does not appear to be of the correct type.'
101  call store_error(errmsg, terminate=.true.)
102  end if
103  !
104  ! -- Verify that PRT model is of the correct type
105  if (.not. associated(prtmodel)) then
106  write (errmsg, '(3a)') 'Problem with GWF-PRT exchange ', trim(this%name), &
107  '. Specified PRT Model does not appear to be of the correct type.'
108  call store_error(errmsg, terminate=.true.)
109  end if
110  !
111  ! -- Tell particle tracking model fmi flows are not read from file
112  prtmodel%fmi%flows_from_file = .false.
113  !
114  ! -- Set a pointer to the GWF bndlist. This will allow the transport model
115  ! to look through the flow packages and establish a link to GWF flows
116  prtmodel%fmi%gwfbndlist => gwfmodel%bndlist
117  end subroutine set_model_pointers
118 
119  subroutine exg_df(this)
120  ! -- modules
122  ! -- dummy
123  class(gwfprtexchangetype) :: this
124  ! -- local
125  class(basemodeltype), pointer :: mb => null()
126  type(gwfmodeltype), pointer :: gwfmodel => null()
127  type(prtmodeltype), pointer :: prtmodel => null()
128  integer(I4B) :: ngwfpack, ip
129  class(bndtype), pointer :: packobj => null()
130  !
131  !
132  ! -- set gwfmodel
133  mb => getbasemodelfromlist(basemodellist, this%m1id)
134  select type (mb)
135  type is (gwfmodeltype)
136  gwfmodel => mb
137  end select
138  !
139  ! -- set prtmodel
140  mb => getbasemodelfromlist(basemodellist, this%m2id)
141  select type (mb)
142  type is (prtmodeltype)
143  prtmodel => mb
144  end select
145  !
146  ! -- Check to make sure that flow is solved before particle tracking and in a
147  ! different solution
148  if (gwfmodel%idsoln >= prtmodel%idsoln) then
149  write (errmsg, '(3a)') 'Problem with GWF-PRT exchange ', trim(this%name), &
150  '. The GWF model must be solved by a different solution than the PRT model. &
151  &The IMS specified for GWF must be listed in mfsim.nam &
152  &before the EMS for PRT.'
153  call store_error(errmsg, terminate=.true.)
154  end if
155  !
156  ! -- Set pointer to flowja
157  prtmodel%fmi%gwfflowja => gwfmodel%flowja
158  call mem_checkin(prtmodel%fmi%gwfflowja, &
159  'GWFFLOWJA', prtmodel%fmi%memoryPath, &
160  'FLOWJA', gwfmodel%memoryPath)
161  !
162  ! -- Set the npf flag so that specific discharge is available for
163  ! transport calculations if dispersion is active
164  if (prtmodel%indsp > 0) then
165  gwfmodel%npf%icalcspdis = 1
166  end if
167  !
168  ! -- Set the auxiliary names for gwf flow packages in prt%fmi
169  ngwfpack = gwfmodel%bndlist%Count()
170  do ip = 1, ngwfpack
171  packobj => getbndfromlist(gwfmodel%bndlist, ip)
172  call prtmodel%fmi%gwfpackages(ip)%set_auxname(packobj%naux, &
173  packobj%auxname)
174  end do
175  end subroutine exg_df
176 
177  subroutine exg_ar(this)
178  ! -- modules
180  use dismodule, only: distype
181  use disvmodule, only: disvtype
182  use disumodule, only: disutype
183  ! -- dummy
184  class(gwfprtexchangetype) :: this
185  ! -- local
186  class(basemodeltype), pointer :: mb => null()
187  type(gwfmodeltype), pointer :: gwfmodel => null()
188  type(prtmodeltype), pointer :: prtmodel => null()
189  ! -- formats
190  character(len=*), parameter :: fmtdiserr = &
191  "('GWF and PRT Models do not have the same discretization for exchange&
192  & ',a,'.&
193  & GWF Model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
194  & PRT Model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
195  & Ensure discretization packages, including IDOMAIN, are identical.')"
196  character(len=*), parameter :: fmtidomerr = &
197  "('GWF and PRT Models do not have the same discretization for exchange&
198  & ',a,'.&
199  & GWF Model and PRT Model have different IDOMAIN arrays.&
200  & Ensure discretization packages, including IDOMAIN, are identical.')"
201  !
202  ! -- set gwfmodel
203  mb => getbasemodelfromlist(basemodellist, this%m1id)
204  select type (mb)
205  type is (gwfmodeltype)
206  gwfmodel => mb
207  end select
208  !
209  ! -- set prtmodel
210  mb => getbasemodelfromlist(basemodellist, this%m2id)
211  select type (mb)
212  type is (prtmodeltype)
213  prtmodel => mb
214  end select
215  !
216  ! -- Check to make sure sizes are identical
217  if (prtmodel%dis%nodes /= gwfmodel%dis%nodes .or. &
218  prtmodel%dis%nodesuser /= gwfmodel%dis%nodesuser) then
219  write (errmsg, fmtdiserr) trim(this%name), &
220  gwfmodel%dis%nodesuser, &
221  gwfmodel%dis%nodes, &
222  prtmodel%dis%nodesuser, &
223  prtmodel%dis%nodes
224  call store_error(errmsg, terminate=.true.)
225  end if
226  !
227  ! -- Make sure idomains are identical
228  select type (gwfdis => gwfmodel%dis)
229  type is (distype)
230  select type (prtdis => prtmodel%dis)
231  type is (distype)
232  if (.not. all(gwfdis%idomain == prtdis%idomain)) then
233  write (errmsg, fmtidomerr) trim(this%name)
234  call store_error(errmsg, terminate=.true.)
235  end if
236  end select
237  type is (disvtype)
238  select type (prtdis => prtmodel%dis)
239  type is (disvtype)
240  if (.not. all(gwfdis%idomain == prtdis%idomain)) then
241  write (errmsg, fmtidomerr) trim(this%name)
242  call store_error(errmsg, terminate=.true.)
243  end if
244  end select
245  type is (disutype)
246  select type (prtdis => prtmodel%dis)
247  type is (disutype)
248  if (.not. all(gwfdis%idomain == prtdis%idomain)) then
249  write (errmsg, fmtidomerr) trim(this%name)
250  call store_error(errmsg, terminate=.true.)
251  end if
252  end select
253  end select
254  !
255  ! -- setup pointers to gwf variables allocated in gwf_ar
256  prtmodel%fmi%gwfhead => gwfmodel%x
257  call mem_checkin(prtmodel%fmi%gwfhead, &
258  'GWFHEAD', prtmodel%fmi%memoryPath, &
259  'X', gwfmodel%memoryPath)
260  prtmodel%fmi%gwfsat => gwfmodel%npf%sat
261  call mem_checkin(prtmodel%fmi%gwfsat, &
262  'GWFSAT', prtmodel%fmi%memoryPath, &
263  'SAT', gwfmodel%npf%memoryPath)
264  prtmodel%fmi%gwfspdis => gwfmodel%npf%spdis
265  call mem_checkin(prtmodel%fmi%gwfspdis, &
266  'GWFSPDIS', prtmodel%fmi%memoryPath, &
267  'SPDIS', gwfmodel%npf%memoryPath)
268  !
269  ! -- setup pointers to the flow storage rates. GWF strg arrays are
270  ! available after the gwf_ar routine is called.
271  if (prtmodel%inmst > 0) then
272  if (gwfmodel%insto > 0) then
273  prtmodel%fmi%gwfstrgss => gwfmodel%sto%strgss
274  prtmodel%fmi%igwfstrgss = 1
275  if (gwfmodel%sto%iusesy == 1) then
276  prtmodel%fmi%gwfstrgsy => gwfmodel%sto%strgsy
277  prtmodel%fmi%igwfstrgsy = 1
278  end if
279  end if
280  end if
281 
282  ! -- transfer the boundary package information from gwf to prt
283  call this%gwfbnd2prtfmi()
284 
285  ! -- if mover package is active, then set a pointer to it's budget object
286  if (gwfmodel%inmvr /= 0) &
287  prtmodel%fmi%mvrbudobj => gwfmodel%mvr%budobj
288 
289  ! -- todo connections
290  end subroutine exg_ar
291 
292  ! todo subroutines: gwfconn2prtconn and link_connections
293 
294  subroutine exg_da(this)
295  ! -- modules
297  ! -- dummy
298  class(gwfprtexchangetype) :: this
299  ! -- local
300  !
301  call mem_deallocate(this%m1id)
302  call mem_deallocate(this%m2id)
303  end subroutine exg_da
304 
305  subroutine allocate_scalars(this)
306  ! -- modules
308  ! -- dummy
309  class(gwfprtexchangetype) :: this
310  ! -- local
311  !
312  call mem_allocate(this%m1id, 'M1ID', this%memoryPath)
313  call mem_allocate(this%m2id, 'M2ID', this%memoryPath)
314  this%m1id = 0
315  this%m2id = 0
316  end subroutine allocate_scalars
317 
318  subroutine gwfbnd2prtfmi(this)
319  ! -- modules
320  ! -- dummy
321  class(gwfprtexchangetype) :: this
322  ! -- local
323  integer(I4B) :: ngwfpack, ip, iterm, imover
324  class(basemodeltype), pointer :: mb => null()
325  type(gwfmodeltype), pointer :: gwfmodel => null()
326  type(prtmodeltype), pointer :: prtmodel => null()
327  class(bndtype), pointer :: packobj => null()
328  !
329  ! -- set gwfmodel
330  mb => getbasemodelfromlist(basemodellist, this%m1id)
331  select type (mb)
332  type is (gwfmodeltype)
333  gwfmodel => mb
334  end select
335  !
336  ! -- set prtmodel
337  mb => getbasemodelfromlist(basemodellist, this%m2id)
338  select type (mb)
339  type is (prtmodeltype)
340  prtmodel => mb
341  end select
342  !
343  ! -- Call routines in FMI that will set pointers to the necessary flow
344  ! data (SIMVALS and SIMTOMVR) stored within each GWF flow package
345  ngwfpack = gwfmodel%bndlist%Count()
346  iterm = 1
347  do ip = 1, ngwfpack
348  packobj => getbndfromlist(gwfmodel%bndlist, ip)
349  call prtmodel%fmi%gwfpackages(iterm)%set_pointers( &
350  'SIMVALS', &
351  packobj%memoryPath, &
352  packobj%input_mempath)
353  iterm = iterm + 1
354  !
355  ! -- If a mover is active for this package, then establish a separate
356  ! pointer link for the mover flows stored in SIMTOMVR
357  imover = packobj%imover
358  if (packobj%isadvpak /= 0) imover = 0
359  if (imover /= 0) then
360  call prtmodel%fmi%gwfpackages(iterm)%set_pointers( &
361  'SIMTOMVR', &
362  packobj%memoryPath, &
363  packobj%input_mempath)
364  iterm = iterm + 1
365  end if
366  end do
367  end subroutine gwfbnd2prtfmi
368 
369 end module gwfprtexchangemodule
subroutine, public addbaseexchangetolist(list, exchange)
Add the exchange object (BaseExchangeType) to a list.
class(basemodeltype) function, pointer, public getbasemodelfromlist(list, idx)
Definition: BaseModel.f90:172
This module contains the base boundary package.
class(bndtype) function, pointer, public getbndfromlist(list, idx)
Get boundary from package list.
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
Definition: Dis.f90:1
Definition: gwf.f90:1
subroutine, public gwfprt_cr(filename, id, m1id, m2id)
Create a new GWF to PRT exchange object.
Definition: exg-gwfprt.f90:40
subroutine exg_da(this)
Definition: exg-gwfprt.f90:295
subroutine gwfbnd2prtfmi(this)
Definition: exg-gwfprt.f90:319
subroutine allocate_scalars(this)
Definition: exg-gwfprt.f90:306
subroutine set_model_pointers(this)
Definition: exg-gwfprt.f90:75
This module defines variable data types.
Definition: kind.f90:8
type(listtype), public basemodellist
Definition: mf6lists.f90:16
type(listtype), public baseexchangelist
Definition: mf6lists.f90:25
Definition: prt.f90:1
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
integer(i4b), dimension(:), allocatable model_loc_idx
equals the local index into the basemodel list (-1 when not available)
Highest level model type. All models extend this parent type.
Definition: BaseModel.f90:13
@ brief BndType
Structured grid discretization.
Definition: Dis.f90:23
Unstructured grid discretization.
Definition: Disu.f90:28
Vertex grid discretization.
Definition: Disv.f90:24
Particle tracking (PRT) model.
Definition: prt.f90:41