MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
exg-gwfgwt.f90
Go to the documentation of this file.
2  use kindmodule, only: dp, i4b, lgp
6  use simmodule, only: store_error
7  use simvariablesmodule, only: errmsg
17  use gwfmodule, only: gwfmodeltype
18  use gwtmodule, only: gwtmodeltype
19  use bndmodule, only: bndtype, getbndfromlist
20 
21  implicit none
22  public :: gwfgwtexchangetype
23  public :: gwfgwt_cr
24 
26 
27  integer(I4B), pointer :: m1_idx => null() !< index into the list of base exchanges for model 1
28  integer(I4B), pointer :: m2_idx => null() !< index into the list of base exchanges for model 2
29  character(len=LINELENGTH) :: filename !< the input file for the GWF-GWT exchange
30 
31  contains
32 
33  procedure :: exg_df
34  procedure :: exg_ar
35  procedure :: exg_da
36  procedure, private :: set_model_pointers
37  procedure, private :: allocate_scalars
38  procedure, private :: gwfbnd2gwtfmi
39  procedure, private :: gwfconn2gwtconn
40  procedure, private :: link_connections
41 
42  end type gwfgwtexchangetype
43 
44 contains
45 
46  !> @brief Create a new GWF to GWT exchange object
47  !<
48  subroutine gwfgwt_cr(filename, id, m1_id, m2_id)
49  ! -- modules
51  ! -- dummy
52  character(len=*), intent(in) :: filename
53  integer(I4B), intent(in) :: id
54  integer(I4B), intent(in) :: m1_id
55  integer(I4B), intent(in) :: m2_id
56  ! -- local
57  class(baseexchangetype), pointer :: baseexchange => null()
58  type(gwfgwtexchangetype), pointer :: exchange => null()
59  character(len=20) :: cint
60  !
61  ! -- Create a new exchange and add it to the baseexchangelist container
62  allocate (exchange)
63  baseexchange => exchange
64  call addbaseexchangetolist(baseexchangelist, baseexchange)
65  !
66  ! -- Assign id and name
67  exchange%id = id
68  write (cint, '(i0)') id
69  exchange%name = 'GWF-GWT_'//trim(adjustl(cint))
70  exchange%memoryPath = exchange%name
71  exchange%filename = filename
72  !
73  ! -- allocate scalars
74  call exchange%allocate_scalars()
75  !
76  ! -- NB: convert from id to local model index in base model list
77  exchange%m1_idx = model_loc_idx(m1_id)
78  exchange%m2_idx = model_loc_idx(m2_id)
79  !
80  ! -- set model pointers
81  call exchange%set_model_pointers()
82  end subroutine gwfgwt_cr
83 
84  !> @brief Allocate and read
85  !<
86  subroutine set_model_pointers(this)
87  ! -- dummy
88  class(gwfgwtexchangetype) :: this
89  ! -- local
90  class(basemodeltype), pointer :: mb => null()
91  type(gwfmodeltype), pointer :: gwfmodel => null()
92  type(gwtmodeltype), pointer :: gwtmodel => null()
93  !
94  ! -- set gwfmodel
95  gwfmodel => null()
96  mb => getbasemodelfromlist(basemodellist, this%m1_idx)
97  select type (mb)
98  type is (gwfmodeltype)
99  gwfmodel => mb
100  end select
101  !
102  ! -- set gwtmodel
103  gwtmodel => null()
104  mb => getbasemodelfromlist(basemodellist, this%m2_idx)
105  select type (mb)
106  type is (gwtmodeltype)
107  gwtmodel => mb
108  end select
109  !
110  ! -- Verify that gwf model is of the correct type
111  if (.not. associated(gwfmodel)) then
112  write (errmsg, '(3a)') 'Problem with GWF-GWT exchange ', trim(this%name), &
113  '. Specified GWF Model does not appear to be of the correct type.'
114  call store_error(errmsg, terminate=.true.)
115  end if
116  !
117  ! -- Verify that gwt model is of the correct type
118  if (.not. associated(gwtmodel)) then
119  write (errmsg, '(3a)') 'Problem with GWF-GWT exchange ', trim(this%name), &
120  '. Specified GWT Model does not appear to be of the correct type.'
121  call store_error(errmsg, terminate=.true.)
122  end if
123  !
124  ! -- Tell transport model fmi flows are not read from file
125  gwtmodel%fmi%flows_from_file = .false.
126  !
127  ! -- Set a pointer to the GWF bndlist. This will allow the transport model
128  ! to look through the flow packages and establish a link to GWF flows
129  gwtmodel%fmi%gwfbndlist => gwfmodel%bndlist
130  end subroutine set_model_pointers
131 
132  !> @brief Define the GwfGwt Exchange object
133  !<
134  subroutine exg_df(this)
135  ! -- modules
137  ! -- dummy
138  class(gwfgwtexchangetype) :: this
139  ! -- local
140  class(basemodeltype), pointer :: mb => null()
141  type(gwfmodeltype), pointer :: gwfmodel => null()
142  type(gwtmodeltype), pointer :: gwtmodel => null()
143  !
144  ! -- set gwfmodel
145  mb => getbasemodelfromlist(basemodellist, this%m1_idx)
146  select type (mb)
147  type is (gwfmodeltype)
148  gwfmodel => mb
149  end select
150  !
151  ! -- set gwtmodel
152  mb => getbasemodelfromlist(basemodellist, this%m2_idx)
153  select type (mb)
154  type is (gwtmodeltype)
155  gwtmodel => mb
156  end select
157  !
158  ! -- Check to make sure that flow is solved before transport and in a
159  ! different IMS solution
160  if (gwfmodel%idsoln >= gwtmodel%idsoln) then
161  write (errmsg, '(3a)') 'Problem with GWF-GWT exchange ', trim(this%name), &
162  '. The GWF model must be solved by a different IMS than the GWT model. &
163  &Furthermore, the IMS specified for GWF must be listed in mfsim.nam &
164  &before the IMS for GWT.'
165  call store_error(errmsg, terminate=.true.)
166  end if
167  !
168  ! -- Set pointer to flowja
169  gwtmodel%fmi%gwfflowja => gwfmodel%flowja
170  call mem_checkin(gwtmodel%fmi%gwfflowja, &
171  'GWFFLOWJA', gwtmodel%fmi%memoryPath, &
172  'FLOWJA', gwfmodel%memoryPath)
173 
174  !
175  ! -- Set the npf flag so that specific discharge is available for
176  ! transport calculations if dispersion is active
177  if (gwtmodel%indsp > 0) then
178  gwfmodel%npf%icalcspdis = 1
179  end if
180  end subroutine exg_df
181 
182  !> @brief Allocate and read
183  !<
184  subroutine exg_ar(this)
185  ! -- modules
187  ! -- dummy
188  class(gwfgwtexchangetype) :: this
189  ! -- local
190  class(basemodeltype), pointer :: mb => null()
191  type(gwfmodeltype), pointer :: gwfmodel => null()
192  type(gwtmodeltype), pointer :: gwtmodel => null()
193  ! -- formats
194  character(len=*), parameter :: fmtdiserr = &
195  "('GWF and GWT Models do not have the same discretization for exchange&
196  & ',a,'.&
197  & GWF Model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
198  & GWT Model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
199  & Ensure discretization packages, including IDOMAIN, are identical.')"
200  !
201  ! -- set gwfmodel
202  mb => getbasemodelfromlist(basemodellist, this%m1_idx)
203  select type (mb)
204  type is (gwfmodeltype)
205  gwfmodel => mb
206  end select
207  !
208  ! -- set gwtmodel
209  mb => getbasemodelfromlist(basemodellist, this%m2_idx)
210  select type (mb)
211  type is (gwtmodeltype)
212  gwtmodel => mb
213  end select
214  !
215  ! -- Check to make sure sizes are identical
216  if (gwtmodel%dis%nodes /= gwfmodel%dis%nodes .or. &
217  gwtmodel%dis%nodesuser /= gwfmodel%dis%nodesuser) then
218  write (errmsg, fmtdiserr) trim(this%name), &
219  gwfmodel%dis%nodesuser, &
220  gwfmodel%dis%nodes, &
221  gwtmodel%dis%nodesuser, &
222  gwtmodel%dis%nodes
223  call store_error(errmsg, terminate=.true.)
224  end if
225  !
226  ! -- setup pointers to gwf variables allocated in gwf_ar
227  gwtmodel%fmi%gwfhead => gwfmodel%x
228  call mem_checkin(gwtmodel%fmi%gwfhead, &
229  'GWFHEAD', gwtmodel%fmi%memoryPath, &
230  'X', gwfmodel%memoryPath)
231  gwtmodel%fmi%gwfsat => gwfmodel%npf%sat
232  call mem_checkin(gwtmodel%fmi%gwfsat, &
233  'GWFSAT', gwtmodel%fmi%memoryPath, &
234  'SAT', gwfmodel%npf%memoryPath)
235  gwtmodel%fmi%gwfspdis => gwfmodel%npf%spdis
236  call mem_checkin(gwtmodel%fmi%gwfspdis, &
237  'GWFSPDIS', gwtmodel%fmi%memoryPath, &
238  'SPDIS', gwfmodel%npf%memoryPath)
239  !
240  ! -- setup pointers to the flow storage rates. GWF strg arrays are
241  ! available after the gwf_ar routine is called.
242  if (gwtmodel%inmst > 0) then
243  if (gwfmodel%insto > 0) then
244  gwtmodel%fmi%gwfstrgss => gwfmodel%sto%strgss
245  gwtmodel%fmi%igwfstrgss = 1
246  if (gwfmodel%sto%iusesy == 1) then
247  gwtmodel%fmi%gwfstrgsy => gwfmodel%sto%strgsy
248  gwtmodel%fmi%igwfstrgsy = 1
249  end if
250  end if
251  end if
252  !
253  ! -- Set a pointer to conc in buy
254  if (gwfmodel%inbuy > 0) then
255  call gwfmodel%buy%set_concentration_pointer(gwtmodel%name, gwtmodel%x, &
256  gwtmodel%ibound)
257  end if
258  !
259  ! -- Set a pointer to conc (which could be a temperature) in vsc
260  if (gwfmodel%invsc > 0) then
261  call gwfmodel%vsc%set_concentration_pointer(gwtmodel%name, gwtmodel%x, &
262  gwtmodel%ibound)
263  end if
264  !
265  ! -- transfer the boundary package information from gwf to gwt
266  call this%gwfbnd2gwtfmi()
267  !
268  ! -- if mover package is active, then set a pointer to it's budget object
269  if (gwfmodel%inmvr /= 0) then
270  gwtmodel%fmi%mvrbudobj => gwfmodel%mvr%budobj
271  end if
272  !
273  ! -- connect Connections
274  call this%gwfconn2gwtconn(gwfmodel, gwtmodel)
275  end subroutine exg_ar
276 
277  !> @brief Link GWT connections to GWF connections or exchanges
278  !<
279  subroutine gwfconn2gwtconn(this, gwfModel, gwtModel)
280  ! -- modules
282  use simvariablesmodule, only: iout
284  ! -- dummy
285  class(gwfgwtexchangetype) :: this !< this exchange
286  type(gwfmodeltype), pointer :: gwfModel !< the flow model
287  type(gwtmodeltype), pointer :: gwtModel !< the transport model
288  ! -- local
289  class(spatialmodelconnectiontype), pointer :: conn => null()
290  class(*), pointer :: objPtr => null()
291  class(gwtgwtconnectiontype), pointer :: gwtConn => null()
292  class(gwfgwfconnectiontype), pointer :: gwfConn => null()
293  class(gwfexchangetype), pointer :: gwfExg => null()
294  class(gwtexchangetype), pointer :: gwtExg => null()
295  integer(I4B) :: ic1, ic2, iex
296  integer(I4B) :: gwfConnIdx, gwfExIdx
297  logical(LGP) :: areEqual
298  !
299  ! loop over all connections
300  gwtloop: do ic1 = 1, baseconnectionlist%Count()
301  !
303  if (.not. associated(conn%owner, gwtmodel)) cycle gwtloop
304  !
305  ! start with a GWT conn.
306  objptr => conn
307  gwtconn => castasgwtgwtconnection(objptr)
308  gwtexg => gwtconn%gwtExchange
309  gwfconnidx = -1
310  gwfexidx = -1
311  !
312  ! find matching GWF conn. in same list
313  gwfloop: do ic2 = 1, baseconnectionlist%Count()
315  !
316  if (associated(conn%owner, gwfmodel)) then
317  !
318  objptr => conn
319  gwfconn => castasgwfgwfconnection(objptr)
320  gwfexg => gwfconn%gwfExchange
321  !
322  ! A model can have multiple exchanges, even connecting the same two
323  ! models. We have a match if
324  ! 1. gwtgwt%model1 is connected to gwfgwf%model1
325  ! 2. gwtgwt%model2 is connected to gwfgwf%model2
326  ! 3. the list of connected nodes (nodem1, nodem2) is equivalent, such
327  ! that it contains the same nodes, appearing in the same order in the
328  ! exchange data block
329  !
330  if (gwfexg%v_model1%name /= gwtexg%gwfmodelname1) cycle
331  if (gwfexg%v_model2%name /= gwtexg%gwfmodelname2) cycle
332  !
333  areequal = (gwfexg%nexg == gwtexg%nexg)
334  if (areequal) then
335  areequal = all(gwfexg%nodem1 == gwtexg%nodem1)
336  areequal = areequal .and. all(gwfexg%nodem2 == gwtexg%nodem2)
337  end if
338  if (areequal) then
339  ! same DIS, same exchange: link and go to next GWT conn.
340  write (iout, '(/6a)') 'Linking exchange ', &
341  trim(gwtexg%name), ' to ', trim(gwfexg%name), &
342  ' (using interface model) for GWT model ', &
343  trim(gwtmodel%name)
344  gwfconnidx = ic2
345  call this%link_connections(gwtconn, gwfconn)
346  exit gwfloop
347  end if
348  end if
349  end do gwfloop
350  !
351  ! fallback option: coupling to old gwfgwf exchange,
352  ! the conditions are equal to what is used above
353  ! (this will go obsolete at some point)
354  if (gwfconnidx == -1) then
355  gwfloopexg: do iex = 1, baseexchangelist%Count()
357  !
358  if (.not. associated(gwfexg)) cycle gwfloopexg
359  !
360  if (associated(gwfexg%model1, gwfmodel) .or. &
361  associated(gwfexg%model2, gwfmodel)) then
362  !
363  if (gwfexg%v_model1%name /= gwtexg%gwfmodelname1) cycle
364  if (gwfexg%v_model2%name /= gwtexg%gwfmodelname2) cycle
365  !
366  areequal = (gwfexg%nexg == gwtexg%nexg)
367  !
368  if (areequal) then
369  areequal = all(gwfexg%nodem1 == gwtexg%nodem1)
370  areequal = areequal .and. all(gwfexg%nodem2 == gwtexg%nodem2)
371  end if
372  if (areequal) then
373  ! link exchange to connection
374  write (iout, '(/6a)') 'Linking exchange ', &
375  trim(gwtexg%name), ' to ', trim(gwfexg%name), ' for GWT model ', &
376  trim(gwtmodel%name)
377  gwfexidx = iex
378  if (gwtconn%owns_exchange) then
379  gwtexg%gwfsimvals => gwfexg%simvals
380  call mem_checkin(gwtexg%gwfsimvals, &
381  'GWFSIMVALS', gwtexg%memoryPath, &
382  'SIMVALS', gwfexg%memoryPath)
383  end if
384  !
385  !cdl link up mvt to mvr
386  if (gwfexg%inmvr > 0) then
387  if (gwtconn%owns_exchange) then
388  !cdl todo: check and make sure gwtEx has mvt active
389  call gwtexg%mvt%set_pointer_mvrbudobj(gwfexg%mvr%budobj)
390  end if
391  end if
392  !
393  if (associated(gwfexg%model2, gwfmodel)) gwtconn%exgflowSign = -1
394  gwtconn%gwtInterfaceModel%fmi%flows_from_file = .false.
395  !
396  exit gwfloopexg
397  end if
398  end if
399  !
400  end do gwfloopexg
401  end if
402  !
403  if (gwfconnidx == -1 .and. gwfexidx == -1) then
404  ! none found, report
405  write (errmsg, *) 'Cannot find GWF-GWF exchange when connecting'// &
406  ' GWT model ', trim(gwtmodel%name), ' with exchange ', &
407  trim(gwtexg%name), ' to GWF model ', trim(gwfmodel%name), &
408  '. Note: GWF-GWF and GWT-GWT need identical exchange data '// &
409  '(both in value and order) for the match to succeed.'
410  call store_error(errmsg)
411  end if
412  !
413  end do gwtloop
414  !
415  ! -- report errors
416  if (count_errors() > 0) then
417  call store_error_filename(this%filename)
418  end if
419  end subroutine gwfconn2gwtconn
420 
421  !> @brief Links a GWT connection to its GWF counterpart
422  !<
423  subroutine link_connections(this, gwtConn, gwfConn)
424  ! -- modules
426  ! -- dummy
427  class(gwfgwtexchangetype) :: this !< this exchange
428  class(gwtgwtconnectiontype), pointer :: gwtConn !< GWT connection
429  class(gwfgwfconnectiontype), pointer :: gwfConn !< GWF connection
430  !
431  !gwtConn%exgflowja => gwfConn%exgflowja
432  if (gwtconn%owns_exchange) then
433  gwtconn%gwtExchange%gwfsimvals => gwfconn%gwfExchange%simvals
434  call mem_checkin(gwtconn%gwtExchange%gwfsimvals, &
435  'GWFSIMVALS', gwtconn%gwtExchange%memoryPath, &
436  'SIMVALS', gwfconn%gwfExchange%memoryPath)
437  end if
438  !
439  !cdl link up mvt to mvr
440  if (gwfconn%gwfExchange%inmvr > 0) then
441  if (gwtconn%owns_exchange) then
442  !cdl todo: check and make sure gwtEx has mvt active
443  call gwtconn%gwtExchange%mvt%set_pointer_mvrbudobj( &
444  gwfconn%gwfExchange%mvr%budobj)
445  end if
446  end if
447  !
448  if (associated(gwfconn%gwfExchange%model2, gwfconn%owner)) then
449  gwtconn%exgflowSign = -1
450  end if
451  !
452  ! fmi flows are not read from file
453  gwtconn%gwtInterfaceModel%fmi%flows_from_file = .false.
454  !
455  ! set concentration pointer for buoyancy
456  ! call gwfConn%gwfInterfaceModel%buy%set_concentration_pointer( &
457  ! gwtConn%gwtModel%name, &
458  ! gwtConn%conc, &
459  ! gwtConn%icbound)
460  end subroutine link_connections
461 
462  !> @brief Deallocate memory
463  !<
464  subroutine exg_da(this)
465  ! -- modules
467  ! -- dummy
468  class(gwfgwtexchangetype) :: this
469  !
470  call mem_deallocate(this%m1_idx)
471  call mem_deallocate(this%m2_idx)
472  end subroutine exg_da
473 
474  !> @brief Allocate package scalars
475  !<
476  subroutine allocate_scalars(this)
477  ! -- modules
479  ! -- dummy
480  class(gwfgwtexchangetype) :: this
481  !
482  call mem_allocate(this%m1_idx, 'M1ID', this%memoryPath)
483  call mem_allocate(this%m2_idx, 'M2ID', this%memoryPath)
484  this%m1_idx = 0
485  this%m2_idx = 0
486  end subroutine allocate_scalars
487 
488  !> @brief Call routines in FMI that will set pointers to the necessary flow
489  !! data
490  !<
491  subroutine gwfbnd2gwtfmi(this)
492  ! -- dummy
493  class(gwfgwtexchangetype) :: this
494  ! -- local
495  integer(I4B) :: ngwfpack, ip, iterm, imover
496  class(basemodeltype), pointer :: mb => null()
497  type(gwfmodeltype), pointer :: gwfmodel => null()
498  type(gwtmodeltype), pointer :: gwtmodel => null()
499  class(bndtype), pointer :: packobj => null()
500  !
501  ! -- set gwfmodel
502  mb => getbasemodelfromlist(basemodellist, this%m1_idx)
503  select type (mb)
504  type is (gwfmodeltype)
505  gwfmodel => mb
506  end select
507  !
508  ! -- set gwtmodel
509  mb => getbasemodelfromlist(basemodellist, this%m2_idx)
510  select type (mb)
511  type is (gwtmodeltype)
512  gwtmodel => mb
513  end select
514  !
515  ! -- Call routines in FMI that will set pointers to the necessary flow
516  ! data (SIMVALS and SIMTOMVR) stored within each GWF flow package
517  ngwfpack = gwfmodel%bndlist%Count()
518  iterm = 1
519  do ip = 1, ngwfpack
520  packobj => getbndfromlist(gwfmodel%bndlist, ip)
521  call gwtmodel%fmi%gwfpackages(iterm)%set_pointers( &
522  'SIMVALS', &
523  packobj%memoryPath, packobj%input_mempath)
524  iterm = iterm + 1
525  !
526  ! -- If a mover is active for this package, then establish a separate
527  ! pointer link for the mover flows stored in SIMTOMVR
528  imover = packobj%imover
529  if (packobj%isadvpak /= 0) imover = 0
530  if (imover /= 0) then
531  call gwtmodel%fmi%gwfpackages(iterm)%set_pointers( &
532  'SIMTOMVR', &
533  packobj%memoryPath, packobj%input_mempath)
534  iterm = iterm + 1
535  end if
536  end do
537  end subroutine gwfbnd2gwtfmi
538 
539 end module gwfgwtexchangemodule
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 linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
class(gwfgwfconnectiontype) function, pointer, public castasgwfgwfconnection(obj)
Cast to GwfGwfConnectionType.
This module contains the GwfGwfExchangeModule Module.
Definition: exg-gwfgwf.f90:10
class(gwfexchangetype) function, pointer, public getgwfexchangefromlist(list, idx)
@ brief Get exchange from list
subroutine exg_da(this)
Deallocate memory.
Definition: exg-gwfgwt.f90:465
subroutine gwfconn2gwtconn(this, gwfModel, gwtModel)
Link GWT connections to GWF connections or exchanges.
Definition: exg-gwfgwt.f90:280
subroutine, public gwfgwt_cr(filename, id, m1_id, m2_id)
Create a new GWF to GWT exchange object.
Definition: exg-gwfgwt.f90:49
subroutine link_connections(this, gwtConn, gwfConn)
Links a GWT connection to its GWF counterpart.
Definition: exg-gwfgwt.f90:424
subroutine gwfbnd2gwtfmi(this)
Call routines in FMI that will set pointers to the necessary flow data.
Definition: exg-gwfgwt.f90:492
subroutine allocate_scalars(this)
Allocate package scalars.
Definition: exg-gwfgwt.f90:477
subroutine set_model_pointers(this)
Allocate and read.
Definition: exg-gwfgwt.f90:87
Definition: gwf.f90:1
class(gwtgwtconnectiontype) function, pointer, public castasgwtgwtconnection(obj)
Cast to GwtGwtConnectionType.
This module contains the GwtGwtExchangeModule Module.
Definition: exg-gwtgwt.f90:10
Definition: gwt.f90:8
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
type(listtype), public baseconnectionlist
Definition: mf6lists.f90:28
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_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
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)
integer(i4b) iout
file unit number for simulation output
class(spatialmodelconnectiontype) function, pointer, public get_smc_from_list(list, idx)
Get the connection from a list.
Highest level model type. All models extend this parent type.
Definition: BaseModel.f90:13
@ brief BndType
Connecting a GWF model to other models in space, implements NumericalExchangeType so the solution can...
Derived type for GwfExchangeType.
Definition: exg-gwfgwf.f90:47
Connects a GWT model to other GWT models in space. Derives from NumericalExchangeType so the solution...
Derived type for GwtExchangeType.
Definition: exg-gwtgwt.f90:46
Class to manage spatial connection of a model to one or more models of the same type....