MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
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  !
73  ! -- return
74  return
75  end subroutine gwfprt_cr
76 
77  subroutine set_model_pointers(this)
78  ! -- modules
79  ! -- dummy
80  class(gwfprtexchangetype) :: this
81  ! -- local
82  class(basemodeltype), pointer :: mb => null()
83  type(gwfmodeltype), pointer :: gwfmodel => null()
84  type(prtmodeltype), pointer :: prtmodel => null()
85  !
86  ! -- set gwfmodel
87  mb => getbasemodelfromlist(basemodellist, this%m1id)
88  select type (mb)
89  type is (gwfmodeltype)
90  gwfmodel => mb
91  end select
92  !
93  ! -- set prtmodel
94  mb => getbasemodelfromlist(basemodellist, this%m2id)
95  select type (mb)
96  type is (prtmodeltype)
97  prtmodel => mb
98  end select
99  !
100  ! -- Verify that GWF model is of the correct type
101  if (.not. associated(gwfmodel)) then
102  write (errmsg, '(3a)') 'Problem with GWF-PRT exchange ', trim(this%name), &
103  '. Specified GWF Model does not appear to be of the correct type.'
104  call store_error(errmsg, terminate=.true.)
105  end if
106  !
107  ! -- Verify that PRT model is of the correct type
108  if (.not. associated(prtmodel)) then
109  write (errmsg, '(3a)') 'Problem with GWF-PRT exchange ', trim(this%name), &
110  '. Specified PRT Model does not appear to be of the correct type.'
111  call store_error(errmsg, terminate=.true.)
112  end if
113  !
114  ! -- Tell particle tracking model fmi flows are not read from file
115  prtmodel%fmi%flows_from_file = .false.
116  !
117  ! -- Set a pointer to the GWF bndlist. This will allow the transport model
118  ! to look through the flow packages and establish a link to GWF flows
119  prtmodel%fmi%gwfbndlist => gwfmodel%bndlist
120  !
121  ! -- return
122  return
123  end subroutine set_model_pointers
124 
125  subroutine exg_df(this)
126  ! -- modules
128  ! -- dummy
129  class(gwfprtexchangetype) :: this
130  ! -- local
131  class(basemodeltype), pointer :: mb => null()
132  type(gwfmodeltype), pointer :: gwfmodel => null()
133  type(prtmodeltype), pointer :: prtmodel => null()
134  integer(I4B) :: ngwfpack, ip
135  class(bndtype), pointer :: packobj => null()
136  !
137  !
138  ! -- set gwfmodel
139  mb => getbasemodelfromlist(basemodellist, this%m1id)
140  select type (mb)
141  type is (gwfmodeltype)
142  gwfmodel => mb
143  end select
144  !
145  ! -- set prtmodel
146  mb => getbasemodelfromlist(basemodellist, this%m2id)
147  select type (mb)
148  type is (prtmodeltype)
149  prtmodel => mb
150  end select
151  !
152  ! -- Check to make sure that flow is solved before particle tracking and in a
153  ! different solution
154  if (gwfmodel%idsoln >= prtmodel%idsoln) then
155  write (errmsg, '(3a)') 'Problem with GWF-PRT exchange ', trim(this%name), &
156  '. The GWF model must be solved by a different solution than the PRT model. &
157  &The IMS specified for GWF must be listed in mfsim.nam &
158  &before the EMS for PRT.'
159  call store_error(errmsg, terminate=.true.)
160  end if
161  !
162  ! -- Set pointer to flowja
163  prtmodel%fmi%gwfflowja => gwfmodel%flowja
164  call mem_checkin(prtmodel%fmi%gwfflowja, &
165  'GWFFLOWJA', prtmodel%fmi%memoryPath, &
166  'FLOWJA', gwfmodel%memoryPath)
167  !
168  ! -- Set the npf flag so that specific discharge is available for
169  ! transport calculations if dispersion is active
170  if (prtmodel%indsp > 0) then
171  gwfmodel%npf%icalcspdis = 1
172  end if
173  !
174  ! -- Set the auxiliary names for gwf flow packages in prt%fmi
175  ngwfpack = gwfmodel%bndlist%Count()
176  do ip = 1, ngwfpack
177  packobj => getbndfromlist(gwfmodel%bndlist, ip)
178  call prtmodel%fmi%gwfpackages(ip)%set_auxname(packobj%naux, &
179  packobj%auxname)
180  end do
181  !
182  ! -- return
183  return
184  end subroutine exg_df
185 
186  subroutine exg_ar(this)
187  ! -- modules
189  ! -- dummy
190  class(gwfprtexchangetype) :: this
191  ! -- local
192  class(basemodeltype), pointer :: mb => null()
193  type(gwfmodeltype), pointer :: gwfmodel => null()
194  type(prtmodeltype), pointer :: prtmodel => null()
195  ! -- formats
196  character(len=*), parameter :: fmtdiserr = &
197  "('GWF and PRT Models do not have the same discretization for exchange&
198  & ',a,'.&
199  & GWF Model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
200  & PRT Model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
201  & Ensure discretization packages, including IDOMAIN, are identical.')"
202  !
203  ! -- set gwfmodel
204  mb => getbasemodelfromlist(basemodellist, this%m1id)
205  select type (mb)
206  type is (gwfmodeltype)
207  gwfmodel => mb
208  end select
209  !
210  ! -- set prtmodel
211  mb => getbasemodelfromlist(basemodellist, this%m2id)
212  select type (mb)
213  type is (prtmodeltype)
214  prtmodel => mb
215  end select
216  !
217  ! -- Check to make sure sizes are identical
218  if (prtmodel%dis%nodes /= gwfmodel%dis%nodes .or. &
219  prtmodel%dis%nodesuser /= gwfmodel%dis%nodesuser) then
220  write (errmsg, fmtdiserr) trim(this%name), &
221  gwfmodel%dis%nodesuser, &
222  gwfmodel%dis%nodes, &
223  prtmodel%dis%nodesuser, &
224  prtmodel%dis%nodes
225  call store_error(errmsg, terminate=.true.)
226  end if
227  !
228  ! -- setup pointers to gwf variables allocated in gwf_ar
229  prtmodel%fmi%gwfhead => gwfmodel%x
230  call mem_checkin(prtmodel%fmi%gwfhead, &
231  'GWFHEAD', prtmodel%fmi%memoryPath, &
232  'X', gwfmodel%memoryPath)
233  prtmodel%fmi%gwfsat => gwfmodel%npf%sat
234  call mem_checkin(prtmodel%fmi%gwfsat, &
235  'GWFSAT', prtmodel%fmi%memoryPath, &
236  'SAT', gwfmodel%npf%memoryPath)
237  prtmodel%fmi%gwfspdis => gwfmodel%npf%spdis
238  call mem_checkin(prtmodel%fmi%gwfspdis, &
239  'GWFSPDIS', prtmodel%fmi%memoryPath, &
240  'SPDIS', gwfmodel%npf%memoryPath)
241  !
242  ! -- setup pointers to the flow storage rates. GWF strg arrays are
243  ! available after the gwf_ar routine is called.
244  if (prtmodel%inmst > 0) then
245  if (gwfmodel%insto > 0) then
246  prtmodel%fmi%gwfstrgss => gwfmodel%sto%strgss
247  prtmodel%fmi%igwfstrgss = 1
248  if (gwfmodel%sto%iusesy == 1) then
249  prtmodel%fmi%gwfstrgsy => gwfmodel%sto%strgsy
250  prtmodel%fmi%igwfstrgsy = 1
251  end if
252  end if
253  end if
254 
255  ! -- todo: set pointer to particle mass concentration, once calculated?
256  ! if (gwfmodel%inbuy > 0) &
257  ! call gwfmodel%buy%set_concentration_pointer(&
258  ! prtmodel%name, prtmodel%mass, prtmodel%ibound)
259 
260  ! -- transfer the boundary package information from gwf to prt
261  call this%gwfbnd2prtfmi()
262 
263  ! -- if mover package is active, then set a pointer to it's budget object
264  if (gwfmodel%inmvr /= 0) &
265  prtmodel%fmi%mvrbudobj => gwfmodel%mvr%budobj
266 
267  ! -- todo connections
268  end subroutine exg_ar
269 
270  ! todo subroutines: gwfconn2prtconn and link_connections
271 
272  subroutine exg_da(this)
273  ! -- modules
275  ! -- dummy
276  class(gwfprtexchangetype) :: this
277  ! -- local
278  !
279  call mem_deallocate(this%m1id)
280  call mem_deallocate(this%m2id)
281  !
282  ! -- return
283  return
284  end subroutine exg_da
285 
286  subroutine allocate_scalars(this)
287  ! -- modules
289  ! -- dummy
290  class(gwfprtexchangetype) :: this
291  ! -- local
292  !
293  call mem_allocate(this%m1id, 'M1ID', this%memoryPath)
294  call mem_allocate(this%m2id, 'M2ID', this%memoryPath)
295  this%m1id = 0
296  this%m2id = 0
297  !
298  ! -- return
299  return
300  end subroutine allocate_scalars
301 
302  subroutine gwfbnd2prtfmi(this)
303  ! -- modules
304  ! -- dummy
305  class(gwfprtexchangetype) :: this
306  ! -- local
307  integer(I4B) :: ngwfpack, ip, iterm, imover
308  class(basemodeltype), pointer :: mb => null()
309  type(gwfmodeltype), pointer :: gwfmodel => null()
310  type(prtmodeltype), pointer :: prtmodel => null()
311  class(bndtype), pointer :: packobj => null()
312  !
313  ! -- set gwfmodel
314  mb => getbasemodelfromlist(basemodellist, this%m1id)
315  select type (mb)
316  type is (gwfmodeltype)
317  gwfmodel => mb
318  end select
319  !
320  ! -- set prtmodel
321  mb => getbasemodelfromlist(basemodellist, this%m2id)
322  select type (mb)
323  type is (prtmodeltype)
324  prtmodel => mb
325  end select
326  !
327  ! -- Call routines in FMI that will set pointers to the necessary flow
328  ! data (SIMVALS and SIMTOMVR) stored within each GWF flow package
329  ngwfpack = gwfmodel%bndlist%Count()
330  iterm = 1
331  do ip = 1, ngwfpack
332  packobj => getbndfromlist(gwfmodel%bndlist, ip)
333  call prtmodel%fmi%gwfpackages(iterm)%set_pointers( &
334  'SIMVALS', &
335  packobj%memoryPath, &
336  packobj%input_mempath)
337  iterm = iterm + 1
338  !
339  ! -- If a mover is active for this package, then establish a separate
340  ! pointer link for the mover flows stored in SIMTOMVR
341  imover = packobj%imover
342  if (packobj%isadvpak /= 0) imover = 0
343  if (imover /= 0) then
344  call prtmodel%fmi%gwfpackages(iterm)%set_pointers( &
345  'SIMTOMVR', &
346  packobj%memoryPath, &
347  packobj%input_mempath)
348  iterm = iterm + 1
349  end if
350  end do
351  !
352  ! -- return
353  return
354  end subroutine gwfbnd2prtfmi
355 
356 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:22
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:273
subroutine gwfbnd2prtfmi(this)
Definition: exg-gwfprt.f90:303
subroutine allocate_scalars(this)
Definition: exg-gwfprt.f90:287
subroutine set_model_pointers(this)
Definition: exg-gwfprt.f90:78
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
Particle tracking (PRT) model.
Definition: prt.f90:41