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