MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
GwtGwtConnection.f90
Go to the documentation of this file.
2  use kindmodule, only: i4b, dp, lgp
4  use csrutilsmodule, only: getcsrindex
5  use simmodule, only: ustop
9  use gwtmodule
13  use sparsemodule, only: sparsematrix
17  use simstagesmodule
19 
20  implicit none
21  private
22 
23  public :: castasgwtgwtconnection
24 
25  !> Connects a GWT model to other GWT models in space. Derives
26  !! from NumericalExchangeType so the solution can use it to
27  !! fetch the coefficients for this connection.
28  !<
30 
31  class(gwtmodeltype), pointer :: gwtmodel => null() !< the model for which this connection exists
32  class(gwtexchangetype), pointer :: gwtexchange => null() !< the primary exchange, cast to GWT-GWT
33  class(gwtinterfacemodeltype), pointer :: gwtinterfacemodel => null() !< the interface model
34  integer(I4B), pointer :: iifaceadvscheme => null() !< the advection scheme at the interface:
35  !! 0 = upstream, 1 = central, 2 = TVD
36  integer(I4B), pointer :: iifacext3d => null() !< XT3D in the interface DSP package: 0 = no, 1 = lhs, 2 = rhs
37  integer(I4B), pointer :: exgflowsign => null() !< indicates the flow direction of exgflowja
38  real(dp), dimension(:), pointer, contiguous :: exgflowjagwt => null() !< gwt-flowja at the interface (this is a subset of the GWT
39  !! interface model flowja's)
40 
41  real(dp), dimension(:), pointer, contiguous :: gwfflowja => null() !< gwfflowja for the interface model
42  real(dp), dimension(:), pointer, contiguous :: gwfsat => null() !< gwfsat for the interface model
43  real(dp), dimension(:), pointer, contiguous :: gwfhead => null() !< gwfhead for the interface model
44  real(dp), dimension(:, :), pointer, contiguous :: gwfspdis => null() !< gwfspdis for the interface model
45 
46  real(dp), dimension(:), pointer, contiguous :: conc => null() !< pointer to concentration array
47  integer(I4B), dimension(:), pointer, contiguous :: icbound => null() !< store pointer to gwt ibound array
48 
49  integer(I4B) :: iout = 0 !< the list file for the interface model
50 
51  contains
52 
53  procedure :: gwtgwtconnection_ctor
54  generic, public :: construct => gwtgwtconnection_ctor
55 
56  procedure :: exg_ar => gwtgwtcon_ar
57  procedure :: exg_df => gwtgwtcon_df
58  procedure :: exg_rp => gwtgwtcon_rp
59  procedure :: exg_ad => gwtgwtcon_ad
60  procedure :: exg_fc => gwtgwtcon_fc
61  procedure :: exg_da => gwtgwtcon_da
62  procedure :: exg_cq => gwtgwtcon_cq
63  procedure :: exg_bd => gwtgwtcon_bd
64  procedure :: exg_ot => gwtgwtcon_ot
65 
66  ! overriding 'protected'
67  procedure :: validateconnection
68 
69  ! local stuff
70  procedure, private :: allocate_scalars
71  procedure, private :: allocate_arrays
72  procedure, private :: cfg_dist_vars
73  procedure, private :: setgridextent
74  procedure, private :: setflowtoexchange
75 
76  end type gwtgwtconnectiontype
77 
78 contains
79 
80  !> @brief Basic construction of the connection
81  !<
82  subroutine gwtgwtconnection_ctor(this, model, gwtEx)
83  use inputoutputmodule, only: openfile
84  class(gwtgwtconnectiontype) :: this !< the connection
85  class(numericalmodeltype), pointer :: model !< the model owning this connection,
86  !! this must be a GwtModelType
87  class(disconnexchangetype), pointer :: gwtEx !< the GWT-GWT exchange the interface model is created for
88  ! local
89  character(len=LINELENGTH) :: fname
90  character(len=LENCOMPONENTNAME) :: name
91  class(*), pointer :: objPtr
92  logical(LGP) :: write_ifmodel_listfile = .false.
93 
94  objptr => model
95  this%gwtModel => castasgwtmodel(objptr)
96  objptr => gwtex
97  this%gwtExchange => castasgwtexchange(objptr)
98 
99  if (gwtex%v_model1%is_local .and. gwtex%v_model2%is_local) then
100  this%owns_exchange = associated(model, gwtex%model1)
101  else
102  this%owns_exchange = .true.
103  end if
104 
105  if (gwtex%v_model1 == model) then
106  write (name, '(a,i0)') 'GWTCON1_', gwtex%id
107  else
108  write (name, '(a,i0)') 'GWTCON2_', gwtex%id
109  end if
110 
111  ! .lst file for interface model
112  if (write_ifmodel_listfile) then
113  fname = trim(name)//'.im.lst'
114  call openfile(this%iout, 0, fname, 'LIST', filstat_opt='REPLACE')
115  write (this%iout, '(4a)') 'Creating GWT-GWT connection for model ', &
116  trim(this%gwtModel%name), 'from exchange ', &
117  trim(gwtex%name)
118  end if
119 
120  ! first call base constructor
121  call this%SpatialModelConnectionType%spatialConnection_ctor(model, &
122  gwtex, &
123  name)
124 
125  call this%allocate_scalars()
126  this%typename = 'GWT-GWT'
127  this%iIfaceAdvScheme = 0
128  this%iIfaceXt3d = 0
129  this%exgflowSign = 1
130 
131  allocate (this%gwtInterfaceModel)
132  this%interface_model => this%gwtInterfaceModel
133 
134  end subroutine gwtgwtconnection_ctor
135 
136  !> @brief Allocate scalar variables for this connection
137  !<
138  subroutine allocate_scalars(this)
139  class(gwtgwtconnectiontype) :: this !< the connection
140 
141  call mem_allocate(this%iIfaceAdvScheme, 'IADVSCHEME', this%memoryPath)
142  call mem_allocate(this%iIfaceXt3d, 'IXT3D', this%memoryPath)
143  call mem_allocate(this%exgflowSign, 'EXGFLOWSIGN', this%memoryPath)
144 
145  end subroutine allocate_scalars
146 
147  !> @brief define the GWT-GWT connection
148  !<
149  subroutine gwtgwtcon_df(this)
150  class(gwtgwtconnectiontype) :: this !< the connection
151  ! local
152  character(len=LENCOMPONENTNAME) :: imName
153 
154  ! determine advection scheme (the GWT-GWT exchange
155  ! has been read at this point)
156  this%iIfaceAdvScheme = this%gwtExchange%iAdvScheme
157  !
158  ! determine xt3d setting on interface
159  this%iIfaceXt3d = this%gwtExchange%ixt3d
160 
161  ! turn off when off in the owning model
162  if (this%gwtModel%indsp > 0) then
163  this%iIfaceXt3d = this%gwtModel%dsp%ixt3d
164  end if
165 
166  ! determine the required size of the interface model grid
167  call this%setGridExtent()
168 
169  ! now set up the GridConnection
170  call this%spatialcon_df()
171 
172  ! we have to 'catch up' and create the interface model
173  ! here, then the remainder of this routine will be define
174  if (this%prim_exchange%v_model1 == this%owner) then
175  write (imname, '(a,i0)') 'GWTIM1_', this%gwtExchange%id
176  else
177  write (imname, '(a,i0)') 'GWTIM2_', this%gwtExchange%id
178  end if
179  call this%gwtInterfaceModel%gwtifmod_cr(imname, &
180  this%iout, &
181  this%ig_builder)
182  call this%gwtInterfaceModel%set_idsoln(this%gwtModel%idsoln)
183  this%gwtInterfaceModel%iAdvScheme = this%iIfaceAdvScheme
184  this%gwtInterfaceModel%ixt3d = this%iIfaceXt3d
185  call this%gwtInterfaceModel%model_df()
186 
187  call this%cfg_dist_vars()
188 
189  call this%allocate_arrays()
190  call this%gwtInterfaceModel%allocate_fmi()
191 
192  ! connect X, RHS, IBOUND, and flowja
193  call this%spatialcon_setmodelptrs()
194 
195  ! connect pointers (used by BUY)
196  this%conc => this%gwtInterfaceModel%x
197  this%icbound => this%gwtInterfaceModel%ibound
198 
199  ! add connections from the interface model to solution matrix
200  call this%spatialcon_connect()
201 
202  end subroutine gwtgwtcon_df
203 
204  !> @brief Configure distributed variables for this interface model
205  !<
206  subroutine cfg_dist_vars(this)
207  class(gwtgwtconnectiontype) :: this !< the connection
208 
209  call this%cfg_dv('X', '', sync_nds, &
211  call this%cfg_dv('IBOUND', '', sync_nds, (/stg_bfr_con_ar/))
212  call this%cfg_dv('TOP', 'DIS', sync_nds, (/stg_bfr_con_ar/))
213  call this%cfg_dv('BOT', 'DIS', sync_nds, (/stg_bfr_con_ar/))
214  call this%cfg_dv('AREA', 'DIS', sync_nds, (/stg_bfr_con_ar/))
215  if (this%gwtInterfaceModel%dsp%idiffc > 0) then
216  call this%cfg_dv('DIFFC', 'DSP', sync_nds, (/stg_bfr_con_ar/))
217  end if
218  if (this%gwtInterfaceModel%dsp%idisp > 0) then
219  call this%cfg_dv('ALH', 'DSP', sync_nds, (/stg_bfr_con_ar/))
220  call this%cfg_dv('ALV', 'DSP', sync_nds, (/stg_bfr_con_ar/))
221  call this%cfg_dv('ATH1', 'DSP', sync_nds, (/stg_bfr_con_ar/))
222  call this%cfg_dv('ATH2', 'DSP', sync_nds, (/stg_bfr_con_ar/))
223  call this%cfg_dv('ATV', 'DSP', sync_nds, (/stg_bfr_con_ar/))
224  end if
225  call this%cfg_dv('GWFHEAD', 'FMI', sync_nds, (/stg_bfr_exg_ad/))
226  call this%cfg_dv('GWFSAT', 'FMI', sync_nds, (/stg_bfr_exg_ad/))
227  call this%cfg_dv('GWFSPDIS', 'FMI', sync_nds, (/stg_bfr_exg_ad/))
228  call this%cfg_dv('GWFFLOWJA', 'FMI', sync_con, (/stg_bfr_exg_ad/))
229  call this%cfg_dv('GWFFLOWJA', 'FMI', sync_exg, (/stg_bfr_exg_ad/), &
230  exg_var_name='GWFSIMVALS')
231  ! fill thetam from mst packages, needed for dsp
232  if (this%gwtModel%indsp > 0 .and. this%gwtModel%inmst > 0) then
233  call this%cfg_dv('THETAM', 'MST', sync_nds, (/stg_aft_con_ar/))
234  end if
235 
236  end subroutine cfg_dist_vars
237 
238  !> @brief Allocate array variables for this connection
239  !<
240  subroutine allocate_arrays(this)
241  class(gwtgwtconnectiontype) :: this !< the connection
242 
243  call mem_allocate(this%exgflowjaGwt, this%ig_builder%nrOfBoundaryCells, &
244  'EXGFLOWJAGWT', this%memoryPath)
245 
246  end subroutine allocate_arrays
247 
248  !> @brief Set required extent of the interface grid from
249  !< the configuration
250  subroutine setgridextent(this)
251  class(gwtgwtconnectiontype) :: this !< the connection
252  ! local
253  logical(LGP) :: hasAdv, hasDsp
254 
255  hasadv = this%gwtModel%inadv > 0
256  hasdsp = this%gwtModel%indsp > 0
257 
258  if (hasadv) then
259  if (this%iIfaceAdvScheme == 2) then
260  this%exg_stencil_depth = 2
261  if (this%gwtModel%adv%iadvwt == 2) then
262  this%int_stencil_depth = 2
263  end if
264  end if
265  end if
266 
267  if (hasdsp) then
268  if (this%iIfaceXt3d > 0) then
269  this%exg_stencil_depth = 2
270  if (this%gwtModel%dsp%ixt3d > 0) then
271  this%int_stencil_depth = 2
272  end if
273  end if
274  end if
275 
276  end subroutine setgridextent
277 
278  !> @brief allocate and read/set the connection's data structures
279  !<
280  subroutine gwtgwtcon_ar(this)
281  class(gwtgwtconnectiontype) :: this !< the connection
282 
283  ! check if we can construct an interface model
284  ! NB: only makes sense after the models' allocate&read have been
285  ! called, which is why we do it here
286  call this%validateConnection()
287 
288  ! allocate and read base
289  call this%spatialcon_ar()
290 
291  ! ... and now the interface model
292  call this%gwtInterfaceModel%model_ar()
293 
294  ! AR the movers and obs through the exchange
295  if (this%owns_exchange) then
296  !cdl implement this when MVT is ready
297  !cdl if (this%gwtExchange%inmvt > 0) then
298  !cdl call this%gwtExchange%mvt%mvt_ar()
299  !cdl end if
300  if (this%gwtExchange%inobs > 0) then
301  call this%gwtExchange%obs%obs_ar()
302  end if
303  end if
304 
305  end subroutine gwtgwtcon_ar
306 
307  !> @brief validate this connection prior to constructing
308  !< the interface model
309  subroutine validateconnection(this)
310  use simvariablesmodule, only: errmsg
312  class(gwtgwtconnectiontype) :: this !< this connection
313 
314  ! base validation, the spatial/geometry part
315  call this%SpatialModelConnectionType%validateConnection()
316 
317  ! we cannot validate this (yet) in parallel mode
318  if (.not. this%gwtExchange%v_model1%is_local) return
319  if (.not. this%gwtExchange%v_model2%is_local) return
320 
321  ! GWT related matters
322  if ((this%gwtExchange%gwtmodel1%inadv > 0 .and. &
323  this%gwtExchange%gwtmodel2%inadv == 0) .or. &
324  (this%gwtExchange%gwtmodel2%inadv > 0 .and. &
325  this%gwtExchange%gwtmodel1%inadv == 0)) then
326  write (errmsg, '(a,a,a)') 'Cannot connect GWT models in exchange ', &
327  trim(this%gwtExchange%name), ' because one model is configured with ADV &
328  &and the other one is not'
329  call store_error(errmsg)
330  end if
331 
332  if ((this%gwtExchange%gwtmodel1%indsp > 0 .and. &
333  this%gwtExchange%gwtmodel2%indsp == 0) .or. &
334  (this%gwtExchange%gwtmodel2%indsp > 0 .and. &
335  this%gwtExchange%gwtmodel1%indsp == 0)) then
336  write (errmsg, '(a,a,a)') 'Cannot connect GWT models in exchange ', &
337  trim(this%gwtExchange%name), ' because one model is configured with DSP &
338  &and the other one is not'
339  call store_error(errmsg)
340  end if
341 
342  ! abort on errors
343  if (count_errors() > 0) then
344  write (errmsg, '(a)') 'Errors occurred while processing exchange(s)'
345  call ustop()
346  end if
347 
348  end subroutine validateconnection
349 
350  subroutine gwtgwtcon_rp(this)
351  class(gwtgwtconnectiontype) :: this !< the connection
352 
353  ! Call exchange rp routines
354  if (this%owns_exchange) then
355  call this%gwtExchange%exg_rp()
356  end if
357 
358  end subroutine gwtgwtcon_rp
359 
360  !> @brief Advance this connection
361  !<
362  subroutine gwtgwtcon_ad(this)
363  class(gwtgwtconnectiontype) :: this !< this connection
364 
365  ! recalculate dispersion ellipse
366  if (this%gwtInterfaceModel%indsp > 0) call this%gwtInterfaceModel%dsp%dsp_ad()
367 
368  if (this%owns_exchange) then
369  call this%gwtExchange%exg_ad()
370  end if
371 
372  end subroutine gwtgwtcon_ad
373 
374  subroutine gwtgwtcon_fc(this, kiter, matrix_sln, rhs_sln, inwtflag)
375  class(gwtgwtconnectiontype) :: this !< the connection
376  integer(I4B), intent(in) :: kiter !< the iteration counter
377  class(matrixbasetype), pointer :: matrix_sln !< the system matrix
378  real(DP), dimension(:), intent(inout) :: rhs_sln !< global right-hand-side
379  integer(I4B), optional, intent(in) :: inwtflag !< newton-raphson flag
380  !
381 
382  call this%SpatialModelConnectionType%spatialcon_fc( &
383  kiter, matrix_sln, rhs_sln, inwtflag)
384  !
385  ! FC the movers through the exchange
386  if (this%owns_exchange) then
387  if (this%gwtExchange%inmvt > 0) then
388  call this%gwtExchange%mvt%mvt_fc(this%gwtExchange%gwtmodel1%x, &
389  this%gwtExchange%gwtmodel2%x)
390  end if
391  end if
392 
393  end subroutine gwtgwtcon_fc
394 
395  subroutine gwtgwtcon_cq(this, icnvg, isuppress_output, isolnid)
396  class(gwtgwtconnectiontype) :: this !< the connection
397  integer(I4B), intent(inout) :: icnvg !< convergence flag
398  integer(I4B), intent(in) :: isuppress_output !< suppress output when =1
399  integer(I4B), intent(in) :: isolnid !< solution id
400 
401  call this%gwtInterfaceModel%model_cq(icnvg, isuppress_output)
402  call this%setFlowToExchange()
403 
404  end subroutine gwtgwtcon_cq
405 
406  !> @brief Set the flows (flowja from interface model) to the
407  !< simvals in the exchange, leaving the budget calcution in there
408  subroutine setflowtoexchange(this)
409  use indexmapmodule
410  class(gwtgwtconnectiontype) :: this !< this connection
411  ! local
412  integer(I4B) :: i
413  class(gwtexchangetype), pointer :: gwtEx
414  type(indexmapsgntype), pointer :: map
415 
416  if (this%owns_exchange) then
417  gwtex => this%gwtExchange
418  map => this%interface_map%exchange_maps(this%interface_map%prim_exg_idx)
419 
420  ! use (half of) the exchange map in reverse:
421  do i = 1, size(map%src_idx)
422  if (map%sign(i) < 0) cycle ! simvals is defined from exg%m1 => exg%m2
423  gwtex%simvals(map%src_idx(i)) = &
424  this%gwtInterfaceModel%flowja(map%tgt_idx(i))
425  end do
426  end if
427 
428  end subroutine setflowtoexchange
429 
430  subroutine gwtgwtcon_bd(this, icnvg, isuppress_output, isolnid)
431  use budgetmodule, only: rate_accumulator
432  class(gwtgwtconnectiontype) :: this !< the connection
433  integer(I4B), intent(inout) :: icnvg !< convergence flag
434  integer(I4B), intent(in) :: isuppress_output !< suppress output when =1
435  integer(I4B), intent(in) :: isolnid !< solution id
436 
437  ! call exchange budget routine, also calls bd
438  ! for movers.
439  if (this%owns_exchange) then
440  call this%gwtExchange%exg_bd(icnvg, isuppress_output, isolnid)
441  end if
442 
443  end subroutine gwtgwtcon_bd
444 
445  subroutine gwtgwtcon_ot(this)
446  class(gwtgwtconnectiontype) :: this !< the connection
447 
448  ! Call exg_ot() here as it handles all output processing
449  ! based on gwtExchange%simvals(:), which was correctly
450  ! filled from gwtgwtcon
451  if (this%owns_exchange) then
452  call this%gwtExchange%exg_ot()
453  end if
454 
455  end subroutine gwtgwtcon_ot
456 
457  subroutine gwtgwtcon_da(this)
458  class(gwtgwtconnectiontype) :: this !< the connection
459  ! local
460  logical(LGP) :: isOpen
461 
462  ! scalars
463  call mem_deallocate(this%iIfaceAdvScheme)
464  call mem_deallocate(this%iIfaceXt3d)
465  call mem_deallocate(this%exgflowSign)
466 
467  ! arrays
468  call mem_deallocate(this%exgflowjaGwt)
469 
470  ! interface model
471  call this%gwtInterfaceModel%model_da()
472  deallocate (this%gwtInterfaceModel)
473 
474  ! dealloc base
475  call this%spatialcon_da()
476 
477  inquire (this%iout, opened=isopen)
478  if (isopen) then
479  close (this%iout)
480  end if
481 
482  ! we need to deallocate the exchange we own:
483  if (this%owns_exchange) then
484  call this%gwtExchange%exg_da()
485  end if
486 
487  end subroutine gwtgwtcon_da
488 
489  !> @brief Cast to GwtGwtConnectionType
490  !<
491  function castasgwtgwtconnection(obj) result(res)
492  implicit none
493  class(*), pointer, intent(inout) :: obj !< object to be cast
494  class(gwtgwtconnectiontype), pointer :: res !< the GwtGwtConnection
495 
496  res => null()
497  if (.not. associated(obj)) return
498 
499  select type (obj)
500  class is (gwtgwtconnectiontype)
501  res => obj
502  end select
503  return
504  end function castasgwtgwtconnection
505 
506 end module
This module contains the BudgetModule.
Definition: Budget.f90:20
subroutine, public rate_accumulator(flow, rin, rout)
@ brief Rate accumulator subroutine
Definition: Budget.f90:664
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 lencomponentname
maximum length of a component name
Definition: Constants.f90:18
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:36
integer(i4b) function, public getcsrindex(i, j, ia, ja)
Return index for element i,j in CSR storage,.
Definition: CsrUtils.f90:13
subroutine allocate_scalars(this)
Allocate scalars and initialize to defaults.
subroutine allocate_arrays(this)
Allocate array data, using the number of connected nodes.
integer(i4b), parameter, public sync_nds
synchronize over nodes
integer(i4b), parameter, public sync_exg
synchronize as exchange variable
integer(i4b), parameter, public sync_con
synchronize over connections
subroutine gwtgwtconnection_ctor(this, model, gwtEx)
Basic construction of the connection.
subroutine gwtgwtcon_rp(this)
class(gwtgwtconnectiontype) function, pointer, public castasgwtgwtconnection(obj)
Cast to GwtGwtConnectionType.
subroutine setgridextent(this)
Set required extent of the interface grid from.
subroutine gwtgwtcon_ad(this)
Advance this connection.
subroutine setflowtoexchange(this)
Set the flows (flowja from interface model) to the.
subroutine gwtgwtcon_bd(this, icnvg, isuppress_output, isolnid)
subroutine gwtgwtcon_fc(this, kiter, matrix_sln, rhs_sln, inwtflag)
subroutine validateconnection(this)
validate this connection prior to constructing
subroutine cfg_dist_vars(this)
Configure distributed variables for this interface model.
subroutine gwtgwtcon_cq(this, icnvg, isuppress_output, isolnid)
subroutine gwtgwtcon_da(this)
subroutine gwtgwtcon_ar(this)
allocate and read/set the connection's data structures
subroutine gwtgwtcon_ot(this)
subroutine gwtgwtcon_df(this)
define the GWT-GWT connection
This module contains the GwtGwtExchangeModule Module.
Definition: exg-gwtgwt.f90:10
class(gwtexchangetype) function, pointer, public castasgwtexchange(obj)
@ brief Cast polymorphic object as exchange
Definition: gwt.f90:8
class(gwtmodeltype) function, pointer, public castasgwtmodel(model)
Cast to GwtModelType.
Definition: gwt.f90:841
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
This module defines variable data types.
Definition: kind.f90:8
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public ustop(stopmess, ioutlocal)
Stop the simulation.
Definition: Sim.f90:315
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
integer(i4b), parameter, public stg_aft_con_ar
afterr connection allocate read
Definition: SimStages.f90:18
integer(i4b), parameter, public stg_bfr_exg_ad
before exchange advance (per solution)
Definition: SimStages.f90:21
integer(i4b), parameter, public stg_bfr_exg_cf
before exchange calculate (per solution)
Definition: SimStages.f90:22
integer(i4b), parameter, public stg_bfr_con_ar
before connection allocate read
Definition: SimStages.f90:17
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
Data structure to hold a global cell identifier, using a pointer to the model and its local cell.
Exchange based on connection between discretizations of DisBaseType. The data specifies the connectio...
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
The GWT Interface Model is a utility to calculate the solution's exchange coefficients from the inter...
Class to manage spatial connection of a model to one or more models of the same type....