MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
exg-gwtgwt.f90
Go to the documentation of this file.
1 !> @brief This module contains the GwtGwtExchangeModule Module
2 !!
3 !! This module contains the code for connecting two GWT Models.
4 !! The methods are based on the simple two point flux approximation
5 !! with the option to use ghost nodes to improve accuracy. This
6 !! exchange is used by GwtGwtConnection with the more sophisticated
7 !! interface model coupling approach when XT3D is needed.
8 !!
9 !<
11 
12  use kindmodule, only: dp, i4b, lgp
21  use listmodule, only: listtype
22  use listsmodule, only: basemodellist
25  use gwtmodule, only: gwtmodeltype
26  use tspmvtmodule, only: tspmvttype
28  use observemodule, only: observetype
29  use obsmodule, only: obstype
30  use tablemodule, only: tabletype, table_cr
32 
33  implicit none
34 
35  private
36  public :: gwtexchangetype
37  public :: gwtexchange_create
38  public :: getgwtexchangefromlist
39  public :: castasgwtexchange
40 
41  !> @brief Derived type for GwtExchangeType
42  !!
43  !! This derived type contains information and methods for
44  !! connecting two GWT models.
45  !<
47  !
48  ! -- names of the GWF models that are connected by this exchange
49  character(len=LENMODELNAME) :: gwfmodelname1 = '' !< name of gwfmodel that corresponds to gwtmodel1
50  character(len=LENMODELNAME) :: gwfmodelname2 = '' !< name of gwfmodel that corresponds to gwtmodel2
51  real(dp), dimension(:), pointer, contiguous :: gwfsimvals => null() !< simulated gwf flow rate for each exchange
52  !
53  ! -- pointers to gwt models
54  class(gwtmodeltype), pointer :: gwtmodel1 => null() !< pointer to GWT Model 1
55  class(gwtmodeltype), pointer :: gwtmodel2 => null() !< pointer to GWT Model 2
56  !
57  ! -- GWT specific option block:
58  integer(I4B), pointer :: inewton => null() !< unneeded newton flag allows for mvt to be used here
59  integer(I4B), pointer :: iadvscheme !< the advection scheme at the interface:
60  !! 0 = upstream, 1 = central, 2 = TVD
61  !
62  ! -- Mover transport package
63  integer(I4B), pointer :: inmvt => null() !< unit number for mover transport (0 if off)
64  type(tspmvttype), pointer :: mvt => null() !< water mover object
65  !
66  ! -- Observation package
67  integer(I4B), pointer :: inobs => null() !< unit number for GWT-GWT observations
68  type(obstype), pointer :: obs => null() !< observation object
69  !
70  ! -- internal data
71  real(dp), dimension(:), pointer, contiguous :: cond => null() !< conductance
72  real(dp), dimension(:), pointer, contiguous :: simvals => null() !< simulated flow rate for each exchange
73  !
74  ! -- table objects
75  type(tabletype), pointer :: outputtab1 => null()
76  type(tabletype), pointer :: outputtab2 => null()
77 
78  contains
79 
80  procedure :: exg_df => gwt_gwt_df
81  procedure :: exg_ar => gwt_gwt_ar
82  procedure :: exg_rp => gwt_gwt_rp
83  procedure :: exg_ad => gwt_gwt_ad
84  procedure :: exg_fc => gwt_gwt_fc
85  procedure :: exg_bd => gwt_gwt_bd
86  procedure :: exg_ot => gwt_gwt_ot
87  procedure :: exg_da => gwt_gwt_da
88  procedure :: exg_fp => gwt_gwt_fp
89  procedure :: connects_model => gwt_gwt_connects_model
90  procedure :: use_interface_model
91  procedure :: allocate_scalars
92  procedure :: allocate_arrays
93  procedure :: source_options
94  procedure :: read_mvt
95  procedure :: gwt_gwt_bdsav
96  procedure, private :: gwt_gwt_bdsav_model
97  procedure, private :: gwt_gwt_df_obs
98  procedure, private :: gwt_gwt_rp_obs
99  procedure, public :: gwt_gwt_save_simvals
100  procedure, private :: validate_exchange
101  end type gwtexchangetype
102 
103 contains
104 
105  !> @ brief Create GWT GWT exchange
106  !!
107  !! Create a new GWT to GWT exchange object.
108  !<
109  subroutine gwtexchange_create(filename, name, id, m1_id, m2_id, input_mempath)
110  ! -- modules
111  use basemodelmodule, only: basemodeltype
112  use listsmodule, only: baseexchangelist
113  use obsmodule, only: obs_cr
115  ! -- dummy
116  character(len=*), intent(in) :: filename !< filename for reading
117  integer(I4B), intent(in) :: id !< id for the exchange
118  character(len=*) :: name !< the exchange name
119  integer(I4B), intent(in) :: m1_id !< id for model 1
120  integer(I4B), intent(in) :: m2_id !< id for model 2
121  character(len=*), intent(in) :: input_mempath
122  ! -- local
123  type(gwtexchangetype), pointer :: exchange
124  class(basemodeltype), pointer :: mb
125  class(baseexchangetype), pointer :: baseexchange
126  integer(I4B) :: m1_index, m2_index
127  !
128  ! -- Create a new exchange and add it to the baseexchangelist container
129  allocate (exchange)
130  baseexchange => exchange
131  call addbaseexchangetolist(baseexchangelist, baseexchange)
132  !
133  ! -- Assign id and name
134  exchange%id = id
135  exchange%name = name
136  exchange%memoryPath = create_mem_path(exchange%name)
137  exchange%input_mempath = input_mempath
138  !
139  ! -- allocate scalars and set defaults
140  call exchange%allocate_scalars()
141  exchange%filename = filename
142  exchange%typename = 'GWT-GWT'
143  exchange%iAdvScheme = 0
144  exchange%ixt3d = 1
145  !
146  ! -- set gwtmodel1
147  m1_index = model_loc_idx(m1_id)
148  mb => getbasemodelfromlist(basemodellist, m1_index)
149  if (m1_index > 0) then
150  select type (mb)
151  type is (gwtmodeltype)
152  exchange%model1 => mb
153  exchange%gwtmodel1 => mb
154  end select
155  end if
156  exchange%v_model1 => get_virtual_model(m1_id)
157  !
158  ! -- set gwtmodel2
159  m2_index = model_loc_idx(m2_id)
160  if (m2_index > 0) then
161  mb => getbasemodelfromlist(basemodellist, m2_index)
162  select type (mb)
163  type is (gwtmodeltype)
164  exchange%model2 => mb
165  exchange%gwtmodel2 => mb
166  end select
167  end if
168  exchange%v_model2 => get_virtual_model(m2_id)
169  !
170  ! -- Verify that gwt model1 is of the correct type
171  if (.not. associated(exchange%gwtmodel1) .and. m1_index > 0) then
172  write (errmsg, '(3a)') 'Problem with GWT-GWT exchange ', &
173  trim(exchange%name), &
174  '. First specified GWT Model does not appear to be of the correct type.'
175  call store_error(errmsg, terminate=.true.)
176  end if
177  !
178  ! -- Verify that gwt model2 is of the correct type
179  if (.not. associated(exchange%gwtmodel2) .and. m2_index > 0) then
180  write (errmsg, '(3a)') 'Problem with GWT-GWT exchange ', &
181  trim(exchange%name), &
182  '. Second specified GWT Model does not appear to be of the correct type.'
183  call store_error(errmsg, terminate=.true.)
184  end if
185  !
186  ! -- Create the obs package
187  call obs_cr(exchange%obs, exchange%inobs)
188  !
189  ! -- Return
190  return
191  end subroutine gwtexchange_create
192 
193  !> @ brief Define GWT GWT exchange
194  !!
195  !! Define GWT to GWT exchange object.
196  !<
197  subroutine gwt_gwt_df(this)
198  ! -- modules
199  use simvariablesmodule, only: iout
201  use ghostnodemodule, only: gnc_cr
202  ! -- dummy
203  class(gwtexchangetype) :: this !< GwtExchangeType
204  ! -- local
205  !
206  ! -- log the exchange
207  write (iout, '(/a,a)') ' Creating exchange: ', this%name
208  !
209  ! -- Ensure models are in same solution
210  if (this%v_model1%idsoln%get() /= this%v_model2%idsoln%get()) then
211  call store_error('Two models are connected in a GWT '// &
212  'exchange but they are in different solutions. '// &
213  'GWT models must be in same solution: '// &
214  trim(this%v_model1%name)//' '// &
215  trim(this%v_model2%name))
216  call store_error_filename(this%filename)
217  end if
218  !
219  ! -- source options
220  call this%source_options(iout)
221  !
222  ! -- source dimensions
223  call this%source_dimensions(iout)
224  !
225  ! -- allocate arrays
226  call this%allocate_arrays()
227  !
228  ! -- source exchange data
229  call this%source_data(iout)
230  !
231  ! -- Read mover information
232  if (this%inmvt > 0) then
233  call this%read_mvt(iout)
234  call this%mvt%mvt_df(this%gwtmodel1%dis)
235  end if
236  !
237  ! -- Store obs
238  call this%gwt_gwt_df_obs()
239  if (associated(this%gwtmodel1)) then
240  call this%obs%obs_df(iout, this%name, 'GWT-GWT', this%gwtmodel1%dis)
241  end if
242  !
243  ! -- validate
244  call this%validate_exchange()
245  !
246  ! -- Return
247  return
248  end subroutine gwt_gwt_df
249 
250  !> @brief validate exchange data after reading
251  !<
252  subroutine validate_exchange(this)
253  ! -- dummy
254  class(gwtexchangetype) :: this !< GwtExchangeType
255  !
256  ! Ensure gwfmodel names were entered
257  if (this%gwfmodelname1 == '') then
258  write (errmsg, '(3a)') 'GWT-GWT exchange ', trim(this%name), &
259  ' requires that GWFMODELNAME1 be entered in the &
260  &OPTIONS block.'
261  call store_error(errmsg)
262  end if
263  if (this%gwfmodelname2 == '') then
264  write (errmsg, '(3a)') 'GWT-GWT exchange ', trim(this%name), &
265  ' requires that GWFMODELNAME2 be entered in the &
266  &OPTIONS block.'
267  call store_error(errmsg)
268  end if
269  !
270  ! Periodic boundary condition in exchange don't allow XT3D (=interface model)
271  if (this%v_model1 == this%v_model2) then
272  if (this%ixt3d > 0) then
273  write (errmsg, '(3a)') 'GWT-GWT exchange ', trim(this%name), &
274  ' is a periodic boundary condition which cannot'// &
275  ' be configured with XT3D'
276  call store_error(errmsg)
277  end if
278  end if
279  !
280  ! Check to see if dispersion is on in either model1 or model2.
281  ! If so, then ANGLDEGX must be provided as an auxiliary variable for this
282  ! GWT-GWT exchange (this%ianglex > 0).
283  if (associated(this%gwtmodel1) .and. associated(this%gwtmodel2)) then
284  if (this%gwtmodel1%indsp /= 0 .or. this%gwtmodel2%indsp /= 0) then
285  if (this%ianglex == 0) then
286  write (errmsg, '(3a)') 'GWT-GWT exchange ', trim(this%name), &
287  ' requires that ANGLDEGX be specified as an'// &
288  ' auxiliary variable because dispersion was '// &
289  'specified in one or both transport models.'
290  call store_error(errmsg)
291  end if
292  end if
293  end if
294  !
295  if (this%ixt3d > 0 .and. this%ianglex == 0) then
296  write (errmsg, '(3a)') 'GWT-GWT exchange ', trim(this%name), &
297  ' requires that ANGLDEGX be specified as an'// &
298  ' auxiliary variable because XT3D is enabled'
299  call store_error(errmsg)
300  end if
301  !
302  if (count_errors() > 0) then
303  call ustop()
304  end if
305  !
306  ! -- Return
307  return
308  end subroutine validate_exchange
309 
310  !> @ brief Allocate and read
311  !!
312  !! Allocated and read and calculate saturated conductance
313  !<
314  subroutine gwt_gwt_ar(this)
315  ! -- dummy
316  class(gwtexchangetype) :: this !< GwtExchangeType
317  !
318  ! -- If mover is active, then call ar routine
319  if (this%inmvt > 0) call this%mvt%mvt_ar()
320  !
321  ! -- Observation AR
322  call this%obs%obs_ar()
323  !
324  ! -- Return
325  return
326  end subroutine gwt_gwt_ar
327 
328  !> @ brief Read and prepare
329  !!
330  !! Read new data for mover and obs
331  !<
332  subroutine gwt_gwt_rp(this)
333  ! -- modules
334  use tdismodule, only: readnewdata
335  ! -- dummy
336  class(gwtexchangetype) :: this !< GwtExchangeType
337  !
338  ! -- Check with TDIS on whether or not it is time to RP
339  if (.not. readnewdata) return
340  !
341  ! -- Read and prepare for mover
342  if (this%inmvt > 0) call this%mvt%mvt_rp()
343  !
344  ! -- Read and prepare for observations
345  call this%gwt_gwt_rp_obs()
346  !
347  ! -- Return
348  return
349  end subroutine gwt_gwt_rp
350 
351  !> @ brief Advance
352  !!
353  !! Advance mover and obs
354  !<
355  subroutine gwt_gwt_ad(this)
356  ! -- dummy
357  class(gwtexchangetype) :: this !< GwtExchangeType
358  !
359  ! -- Advance mover
360  !if(this%inmvt > 0) call this%mvt%mvt_ad()
361  !
362  ! -- Push simulated values to preceding time step
363  call this%obs%obs_ad()
364  !
365  ! -- Return
366  return
367  end subroutine gwt_gwt_ad
368 
369  !> @ brief Fill coefficients
370  !!
371  !! Calculate conductance and fill coefficient matrix
372  !<
373  subroutine gwt_gwt_fc(this, kiter, matrix_sln, rhs_sln, inwtflag)
374  ! -- dummy
375  class(gwtexchangetype) :: this !< GwtExchangeType
376  integer(I4B), intent(in) :: kiter
377  class(matrixbasetype), pointer :: matrix_sln
378  real(DP), dimension(:), intent(inout) :: rhs_sln
379  integer(I4B), optional, intent(in) :: inwtflag
380  !
381  ! -- Call mvt fc routine
382  if (this%inmvt > 0) call this%mvt%mvt_fc(this%gwtmodel1%x, this%gwtmodel2%x)
383  !
384  ! -- Return
385  return
386  end subroutine gwt_gwt_fc
387 
388  !> @ brief Budget
389  !!
390  !! Accumulate budget terms
391  !<
392  subroutine gwt_gwt_bd(this, icnvg, isuppress_output, isolnid)
393  ! -- modules
395  use budgetmodule, only: rate_accumulator
396  ! -- dummy
397  class(gwtexchangetype) :: this !< GwtExchangeType
398  integer(I4B), intent(inout) :: icnvg
399  integer(I4B), intent(in) :: isuppress_output
400  integer(I4B), intent(in) :: isolnid
401  ! -- local
402  character(len=LENBUDTXT), dimension(1) :: budtxt
403  real(DP), dimension(2, 1) :: budterm
404  real(DP) :: ratin, ratout
405  !
406  ! -- initialize
407  budtxt(1) = ' FLOW-JA-FACE'
408  !
409  ! -- Calculate ratin/ratout and pass to model budgets
410  call rate_accumulator(this%simvals, ratin, ratout)
411  !
412  ! -- Add the budget terms to model 1
413  if (associated(this%gwtmodel1)) then
414  budterm(1, 1) = ratin
415  budterm(2, 1) = ratout
416  call this%gwtmodel1%model_bdentry(budterm, budtxt, this%name)
417  end if
418  !
419  ! -- Add the budget terms to model 2
420  if (associated(this%gwtmodel2)) then
421  budterm(1, 1) = ratout
422  budterm(2, 1) = ratin
423  call this%gwtmodel2%model_bdentry(budterm, budtxt, this%name)
424  end if
425  !
426  ! -- Call mvt bd routine
427  if (this%inmvt > 0) call this%mvt%mvt_bd(this%gwtmodel1%x, this%gwtmodel2%x)
428  !
429  ! -- Return
430  return
431  end subroutine gwt_gwt_bd
432 
433  !> @ brief Budget save
434  !!
435  !! Output individual flows to listing file and binary budget files
436  !<
437  subroutine gwt_gwt_bdsav(this)
438  ! -- dummy
439  class(gwtexchangetype) :: this !< GwtExchangeType
440  ! -- local
441  integer(I4B) :: icbcfl, ibudfl
442  !
443  ! -- budget for model1
444  if (associated(this%gwtmodel1)) then
445  call this%gwt_gwt_bdsav_model(this%gwtmodel1)
446  end if
447  !
448  ! -- budget for model2
449  if (associated(this%gwtmodel2)) then
450  call this%gwt_gwt_bdsav_model(this%gwtmodel2)
451  end if
452  !
453  ! -- Set icbcfl, ibudfl to zero so that flows will be printed and
454  ! saved, if the options were set in the MVT package
455  icbcfl = 1
456  ibudfl = 1
457  !
458  ! -- Call mvt bd routine
459  !cdl todo: if(this%inmvt > 0) call this%mvt%mvt_bdsav(icbcfl, ibudfl, isuppress_output)
460  !
461  ! -- Calculate and write simulated values for observations
462  if (this%inobs /= 0) then
463  call this%gwt_gwt_save_simvals()
464  end if
465  !
466  ! -- Return
467  return
468  end subroutine gwt_gwt_bdsav
469 
470  !> @ brief Budget save
471  !!
472  !! Output individual flows to listing file and binary budget files
473  !<
474  subroutine gwt_gwt_bdsav_model(this, model)
475  ! -- modules
477  use tdismodule, only: kstp, kper
478  ! -- dummy
479  class(gwtexchangetype) :: this !< GwtExchangeType
480  class(gwtmodeltype), pointer :: model
481  ! -- local
482  character(len=LENBOUNDNAME) :: bname
483  character(len=LENPACKAGENAME + 4) :: packname
484  character(len=LENBUDTXT), dimension(1) :: budtxt
485  type(tabletype), pointer :: output_tab
486  class(virtualmodeltype), pointer :: nbr_model
487  character(len=20) :: nodestr
488  integer(I4B) :: ntabrows
489  integer(I4B) :: nodeu
490  integer(I4B) :: i, n1, n2, n1u, n2u
491  integer(I4B) :: ibinun
492  real(DP) :: ratin, ratout, rrate
493  logical(LGP) :: is_for_model1
494  integer(I4B) :: isuppress_output
495  !
496  ! -- initialize local variables
497  isuppress_output = 0
498  budtxt(1) = ' FLOW-JA-FACE'
499  packname = 'EXG '//this%name
500  packname = adjustr(packname)
501  if (associated(model, this%gwtmodel1)) then
502  output_tab => this%outputtab1
503  nbr_model => this%v_model2
504  is_for_model1 = .true.
505  else
506  output_tab => this%outputtab2
507  nbr_model => this%v_model1
508  is_for_model1 = .false.
509  end if
510  !
511  ! -- update output tables
512  if (this%iprflow /= 0) then
513  !
514  ! -- update titles
515  if (model%oc%oc_save('BUDGET')) then
516  call output_tab%set_title(packname)
517  end if
518  !
519  ! -- set table kstp and kper
520  call output_tab%set_kstpkper(kstp, kper)
521  !
522  ! -- update maxbound of tables
523  ntabrows = 0
524  do i = 1, this%nexg
525  n1 = this%nodem1(i)
526  n2 = this%nodem2(i)
527  !
528  ! -- If both cells are active then calculate flow rate
529  if (this%v_model1%ibound%get(n1) /= 0 .and. &
530  this%v_model2%ibound%get(n2) /= 0) then
531  ntabrows = ntabrows + 1
532  end if
533  end do
534  if (ntabrows > 0) then
535  call output_tab%set_maxbound(ntabrows)
536  end if
537  end if
538  !
539  ! -- Print and write budget terms for model 1
540  !
541  ! -- Set binary unit numbers for saving flows
542  if (this%ipakcb /= 0) then
543  ibinun = model%oc%oc_save_unit('BUDGET')
544  else
545  ibinun = 0
546  end if
547  !
548  ! -- If save budget flag is zero for this stress period, then
549  ! shut off saving
550  if (.not. model%oc%oc_save('BUDGET')) ibinun = 0
551  if (isuppress_output /= 0) then
552  ibinun = 0
553  end if
554  !
555  ! -- If cell-by-cell flows will be saved as a list, write header.
556  if (ibinun /= 0) then
557  call model%dis%record_srcdst_list_header(budtxt(1), &
558  model%name, &
559  this%name, &
560  nbr_model%name, &
561  this%name, &
562  this%naux, this%auxname, &
563  ibinun, this%nexg, &
564  model%iout)
565  end if
566  !
567  ! Initialize accumulators
568  ratin = dzero
569  ratout = dzero
570  !
571  ! -- Loop through all exchanges
572  do i = 1, this%nexg
573  !
574  ! -- Assign boundary name
575  if (this%inamedbound > 0) then
576  bname = this%boundname(i)
577  else
578  bname = ''
579  end if
580  !
581  ! -- Calculate the flow rate between n1 and n2
582  rrate = dzero
583  n1 = this%nodem1(i)
584  n2 = this%nodem2(i)
585  !
586  ! -- If both cells are active then calculate flow rate
587  if (this%v_model1%ibound%get(n1) /= 0 .and. &
588  this%v_model2%ibound%get(n2) /= 0) then
589  rrate = this%simvals(i)
590  !
591  ! -- Print the individual rates to model list files if requested
592  if (this%iprflow /= 0) then
593  if (model%oc%oc_save('BUDGET')) then
594  !
595  ! -- set nodestr and write outputtab table
596  if (is_for_model1) then
597  nodeu = model%dis%get_nodeuser(n1)
598  call model%dis%nodeu_to_string(nodeu, nodestr)
599  call output_tab%print_list_entry(i, trim(adjustl(nodestr)), &
600  rrate, bname)
601  else
602  nodeu = model%dis%get_nodeuser(n2)
603  call model%dis%nodeu_to_string(nodeu, nodestr)
604  call output_tab%print_list_entry(i, trim(adjustl(nodestr)), &
605  -rrate, bname)
606  end if
607  end if
608  end if
609  if (rrate < dzero) then
610  ratout = ratout - rrate
611  else
612  ratin = ratin + rrate
613  end if
614  end if
615  !
616  ! -- If saving cell-by-cell flows in list, write flow
617  n1u = this%v_model1%dis_get_nodeuser(n1)
618  n2u = this%v_model2%dis_get_nodeuser(n2)
619  if (ibinun /= 0) then
620  if (is_for_model1) then
621  call model%dis%record_mf6_list_entry( &
622  ibinun, n1u, n2u, rrate, this%naux, this%auxvar(:, i), &
623  .false., .false.)
624  else
625  call model%dis%record_mf6_list_entry( &
626  ibinun, n2u, n1u, -rrate, this%naux, this%auxvar(:, i), &
627  .false., .false.)
628  end if
629  end if
630  !
631  end do
632  !
633  ! -- Return
634  return
635  end subroutine gwt_gwt_bdsav_model
636 
637  !> @ brief Output
638  !!
639  !! Write output
640  !<
641  subroutine gwt_gwt_ot(this)
642  ! -- modules
643  use simvariablesmodule, only: iout
644  use constantsmodule, only: dzero
645  ! -- dummy
646  class(gwtexchangetype) :: this !< GwtExchangeType
647  ! -- local
648  integer(I4B) :: iexg, n1, n2
649  integer(I4B) :: ibudfl
650  real(DP) :: flow
651  character(len=LINELENGTH) :: node1str, node2str
652  ! -- format
653  character(len=*), parameter :: fmtheader = &
654  "(/1x, 'SUMMARY OF EXCHANGE RATES FOR EXCHANGE ', a, ' WITH ID ', i0, /, &
655  &2a16, 5a16, /, 112('-'))"
656  character(len=*), parameter :: fmtheader2 = &
657  "(/1x, 'SUMMARY OF EXCHANGE RATES FOR EXCHANGE ', a, ' WITH ID ', i0, /, &
658  &2a16, 4a16, /, 96('-'))"
659  character(len=*), parameter :: fmtdata = &
660  "(2a16, 5(1pg16.6))"
661  !
662  ! -- Call bdsave
663  call this%gwt_gwt_bdsav()
664  !
665  ! -- Write a table of exchanges
666  if (this%iprflow /= 0) then
667  write (iout, fmtheader2) trim(adjustl(this%name)), this%id, 'NODEM1', &
668  'NODEM2', 'COND', 'X_M1', 'X_M2', 'FLOW'
669  do iexg = 1, this%nexg
670  n1 = this%nodem1(iexg)
671  n2 = this%nodem2(iexg)
672  flow = this%simvals(iexg)
673  call this%v_model1%dis_noder_to_string(n1, node1str)
674  call this%v_model2%dis_noder_to_string(n2, node2str)
675  write (iout, fmtdata) trim(adjustl(node1str)), &
676  trim(adjustl(node2str)), &
677  this%cond(iexg), this%v_model1%x%get(n1), &
678  this%v_model2%x%get(n2), flow
679  end do
680  end if
681  !
682  !cdl Implement when MVT is ready
683  ! -- Mover budget output
684  ibudfl = 1
685  if (this%inmvt > 0) call this%mvt%mvt_ot_bdsummary(ibudfl)
686  !
687  ! -- OBS output
688  call this%obs%obs_ot()
689  !
690  ! -- Return
691  return
692  end subroutine gwt_gwt_ot
693 
694  !> @ brief Source options
695  !!
696  !! Source the options block
697  !<
698  subroutine source_options(this, iout)
699  ! -- modules
700  use constantsmodule, only: lenvarname
706  ! -- dummy
707  class(gwtexchangetype) :: this !< GwtExchangeType
708  integer(I4B), intent(in) :: iout
709  ! -- local
710  type(exggwtgwtparamfoundtype) :: found
711  character(len=LENVARNAME), dimension(3) :: adv_scheme = &
712  &[character(len=LENVARNAME) :: 'UPSTREAM', 'CENTRAL', 'TVD']
713  character(len=linelength) :: mvt_fname
714  !
715  ! -- update defaults with values sourced from input context
716  call mem_set_value(this%gwfmodelname1, 'GWFMODELNAME1', this%input_mempath, &
717  found%gwfmodelname1)
718  call mem_set_value(this%gwfmodelname2, 'GWFMODELNAME2', this%input_mempath, &
719  found%gwfmodelname2)
720  call mem_set_value(this%iAdvScheme, 'ADV_SCHEME', this%input_mempath, &
721  adv_scheme, found%adv_scheme)
722  call mem_set_value(this%ixt3d, 'DSP_XT3D_OFF', this%input_mempath, &
723  found%dsp_xt3d_off)
724  call mem_set_value(this%ixt3d, 'DSP_XT3D_RHS', this%input_mempath, &
725  found%dsp_xt3d_rhs)
726  !
727  write (iout, '(1x,a)') 'PROCESSING GWT-GWT EXCHANGE OPTIONS'
728  !
729  ! -- source base class options
730  call this%DisConnExchangeType%source_options(iout)
731  !
732  if (found%gwfmodelname1) then
733  write (iout, '(4x,a,a)') &
734  'GWFMODELNAME1 IS SET TO: ', trim(this%gwfmodelname1)
735  end if
736  !
737  if (found%gwfmodelname2) then
738  write (iout, '(4x,a,a)') &
739  'GWFMODELNAME2 IS SET TO: ', trim(this%gwfmodelname2)
740  end if
741  !
742  if (found%adv_scheme) then
743  ! -- count from 0
744  this%iAdvScheme = this%iAdvScheme - 1
745  write (iout, '(4x,a,a)') &
746  'ADVECTION SCHEME METHOD HAS BEEN SET TO: ', &
747  trim(adv_scheme(this%iAdvScheme + 1))
748  end if
749  !
750  if (found%dsp_xt3d_off .and. found%dsp_xt3d_rhs) then
751  errmsg = 'DSP_XT3D_OFF and DSP_XT3D_RHS cannot both be set as options.'
752  call store_error(errmsg)
753  call store_error_filename(this%filename)
754  else if (found%dsp_xt3d_off) then
755  this%ixt3d = 0
756  write (iout, '(4x,a)') 'XT3D FORMULATION HAS BEEN SHUT OFF.'
757  else if (found%dsp_xt3d_rhs) then
758  this%ixt3d = 2
759  write (iout, '(4x,a)') 'XT3D RIGHT-HAND SIDE FORMULATION IS SELECTED.'
760  end if
761  !
762  ! -- enforce 0 or 1 MVR6_FILENAME entries in option block
763  if (filein_fname(mvt_fname, 'MVT6_FILENAME', this%input_mempath, &
764  this%filename)) then
765  this%inmvt = getunit()
766  call openfile(this%inmvt, iout, mvt_fname, 'MVT')
767  write (iout, '(4x,a)') &
768  'WATER MOVER TRANSPORT INFORMATION WILL BE READ FROM ', trim(mvt_fname)
769  end if
770  !
771  ! -- enforce 0 or 1 OBS6_FILENAME entries in option block
772  if (filein_fname(this%obs%inputFilename, 'OBS6_FILENAME', &
773  this%input_mempath, this%filename)) then
774  this%obs%active = .true.
775  this%obs%inUnitObs = getunit()
776  call openfile(this%obs%inUnitObs, iout, this%obs%inputFilename, 'OBS')
777  end if
778  !
779  write (iout, '(1x,a)') 'END OF GWT-GWT EXCHANGE OPTIONS'
780  !
781  ! -- return
782  return
783  end subroutine source_options
784 
785  !> @ brief Read mover
786  !!
787  !! Read and process movers
788  !<
789  subroutine read_mvt(this, iout)
790  ! -- modules
791  use tspmvtmodule, only: mvt_cr
792  ! -- dummy
793  class(gwtexchangetype) :: this !< GwtExchangeType
794  integer(I4B), intent(in) :: iout
795  !
796  ! -- Create and initialize the mover object Here, fmi is set to the one
797  ! for gwtmodel1 so that a call to save flows has an associated dis
798  ! object.
799  call mvt_cr(this%mvt, this%name, this%inmvt, iout, this%gwtmodel1%fmi, &
800  this%gwtmodel1%eqnsclfac, this%gwtmodel1%depvartype, &
801  gwfmodelname1=this%gwfmodelname1, &
802  gwfmodelname2=this%gwfmodelname2, &
803  fmi2=this%gwtmodel2%fmi)
804  !
805  ! -- Return
806  return
807  end subroutine read_mvt
808 
809  !> @ brief Allocate scalars
810  !!
811  !! Allocate scalar variables
812  !<
813  subroutine allocate_scalars(this)
814  ! -- modules
816  use constantsmodule, only: dzero
817  ! -- dummy
818  class(gwtexchangetype) :: this !< GwtExchangeType
819  !
820  call this%DisConnExchangeType%allocate_scalars()
821  !
822  call mem_allocate(this%inewton, 'INEWTON', this%memoryPath)
823  call mem_allocate(this%inobs, 'INOBS', this%memoryPath)
824  call mem_allocate(this%iAdvScheme, 'IADVSCHEME', this%memoryPath)
825  this%inewton = 0
826  this%inobs = 0
827  this%iAdvScheme = 0
828  !
829  call mem_allocate(this%inmvt, 'INMVT', this%memoryPath)
830  this%inmvt = 0
831  !
832  ! -- Return
833  return
834  end subroutine allocate_scalars
835 
836  !> @ brief Deallocate
837  !!
838  !! Deallocate memory associated with this object
839  !<
840  subroutine gwt_gwt_da(this)
841  ! -- modules
843  ! -- dummy
844  class(gwtexchangetype) :: this !< GwtExchangeType
845  !
846  ! -- objects
847  if (this%inmvt > 0) then
848  call this%mvt%mvt_da()
849  deallocate (this%mvt)
850  end if
851  call this%obs%obs_da()
852  deallocate (this%obs)
853  !
854  ! -- arrays
855  call mem_deallocate(this%cond)
856  call mem_deallocate(this%simvals)
857  call mem_deallocate(this%gwfsimvals, 'GWFSIMVALS', this%memoryPath) ! linked memory
858  !
859  ! -- output table objects
860  if (associated(this%outputtab1)) then
861  call this%outputtab1%table_da()
862  deallocate (this%outputtab1)
863  nullify (this%outputtab1)
864  end if
865  if (associated(this%outputtab2)) then
866  call this%outputtab2%table_da()
867  deallocate (this%outputtab2)
868  nullify (this%outputtab2)
869  end if
870  !
871  ! -- scalars
872  deallocate (this%filename)
873  call mem_deallocate(this%inewton)
874  call mem_deallocate(this%inobs)
875  call mem_deallocate(this%iAdvScheme)
876  call mem_deallocate(this%inmvt)
877  !
878  ! -- deallocate base
879  call this%DisConnExchangeType%disconnex_da()
880  !
881  ! -- Return
882  return
883  end subroutine gwt_gwt_da
884 
885  !> @ brief Allocate arrays
886  !!
887  !! Allocate arrays
888  !<
889  subroutine allocate_arrays(this)
890  ! -- modules
892  ! -- dummy
893  class(gwtexchangetype) :: this !< GwtExchangeType
894  ! -- local
895  character(len=LINELENGTH) :: text
896  integer(I4B) :: ntabcol, i
897  !
898  call this%DisConnExchangeType%allocate_arrays()
899  !
900  call mem_allocate(this%cond, this%nexg, 'COND', this%memoryPath)
901  call mem_allocate(this%simvals, this%nexg, 'SIMVALS', this%memoryPath)
902  !
903  ! -- Initialize
904  do i = 1, this%nexg
905  this%cond(i) = dnodata
906  end do
907  !
908  ! -- allocate and initialize the output table
909  if (this%iprflow /= 0) then
910  !
911  ! -- dimension table
912  ntabcol = 3
913  if (this%inamedbound > 0) then
914  ntabcol = ntabcol + 1
915  end if
916  !
917  ! -- initialize the output table objects
918  ! outouttab1
919  if (this%v_model1%is_local) then
920  call table_cr(this%outputtab1, this%name, ' ')
921  call this%outputtab1%table_df(this%nexg, ntabcol, this%gwtmodel1%iout, &
922  transient=.true.)
923  text = 'NUMBER'
924  call this%outputtab1%initialize_column(text, 10, alignment=tabcenter)
925  text = 'CELLID'
926  call this%outputtab1%initialize_column(text, 20, alignment=tableft)
927  text = 'RATE'
928  call this%outputtab1%initialize_column(text, 15, alignment=tabcenter)
929  if (this%inamedbound > 0) then
930  text = 'NAME'
931  call this%outputtab1%initialize_column(text, 20, alignment=tableft)
932  end if
933  end if
934  ! outouttab2
935  if (this%v_model2%is_local) then
936  call table_cr(this%outputtab2, this%name, ' ')
937  call this%outputtab2%table_df(this%nexg, ntabcol, this%gwtmodel2%iout, &
938  transient=.true.)
939  text = 'NUMBER'
940  call this%outputtab2%initialize_column(text, 10, alignment=tabcenter)
941  text = 'CELLID'
942  call this%outputtab2%initialize_column(text, 20, alignment=tableft)
943  text = 'RATE'
944  call this%outputtab2%initialize_column(text, 15, alignment=tabcenter)
945  if (this%inamedbound > 0) then
946  text = 'NAME'
947  call this%outputtab2%initialize_column(text, 20, alignment=tableft)
948  end if
949  end if
950  end if
951  !
952  ! -- Return
953  return
954  end subroutine allocate_arrays
955 
956  !> @ brief Define observations
957  !!
958  !! Define the observations associated with this object
959  !<
960  subroutine gwt_gwt_df_obs(this)
961  ! -- dummy
962  class(gwtexchangetype) :: this !< GwtExchangeType
963  ! -- local
964  integer(I4B) :: indx
965  !
966  ! -- Store obs type and assign procedure pointer
967  ! for gwt-gwt observation type.
968  call this%obs%StoreObsType('flow-ja-face', .true., indx)
969  this%obs%obsData(indx)%ProcessIdPtr => gwt_gwt_process_obsid
970  !
971  ! -- Return
972  return
973  end subroutine gwt_gwt_df_obs
974 
975  !> @ brief Read and prepare observations
976  !!
977  !! Handle observation exchanges exchange-boundary names.
978  !<
979  subroutine gwt_gwt_rp_obs(this)
980  ! -- modules
981  use constantsmodule, only: dzero
982  ! -- dummy
983  class(gwtexchangetype) :: this !< GwtExchangeType
984  ! -- local
985  integer(I4B) :: i
986  integer(I4B) :: j
987  class(observetype), pointer :: obsrv => null()
988  character(len=LENBOUNDNAME) :: bname
989  logical :: jfound
990  ! -- formats
991 10 format('Exchange "', a, '" for observation "', a, &
992  '" is invalid in package "', a, '"')
993 20 format('Exchange id "', i0, '" for observation "', a, &
994  '" is invalid in package "', a, '"')
995  !
996  do i = 1, this%obs%npakobs
997  obsrv => this%obs%pakobs(i)%obsrv
998  !
999  ! -- indxbnds needs to be reset each stress period because
1000  ! list of boundaries can change each stress period.
1001  ! -- Not true for exchanges, but leave this in for now anyway.
1002  call obsrv%ResetObsIndex()
1003  obsrv%BndFound = .false.
1004  !
1005  bname = obsrv%FeatureName
1006  if (bname /= '') then
1007  ! -- Observation location(s) is(are) based on a boundary name.
1008  ! Iterate through all boundaries to identify and store
1009  ! corresponding index(indices) in bound array.
1010  jfound = .false.
1011  do j = 1, this%nexg
1012  if (this%boundname(j) == bname) then
1013  jfound = .true.
1014  obsrv%BndFound = .true.
1015  obsrv%CurrentTimeStepEndValue = dzero
1016  call obsrv%AddObsIndex(j)
1017  end if
1018  end do
1019  if (.not. jfound) then
1020  write (errmsg, 10) trim(bname), trim(obsrv%ObsTypeId), trim(this%name)
1021  call store_error(errmsg)
1022  end if
1023  else
1024  ! -- Observation location is a single exchange number
1025  if (obsrv%intPak1 <= this%nexg .and. obsrv%intPak1 > 0) then
1026  jfound = .true.
1027  obsrv%BndFound = .true.
1028  obsrv%CurrentTimeStepEndValue = dzero
1029  call obsrv%AddObsIndex(obsrv%intPak1)
1030  else
1031  jfound = .false.
1032  end if
1033  if (.not. jfound) then
1034  write (errmsg, 20) obsrv%intPak1, trim(obsrv%ObsTypeId), trim(this%name)
1035  call store_error(errmsg)
1036  end if
1037  end if
1038  end do
1039  !
1040  ! -- write summary of error messages
1041  if (count_errors() > 0) then
1042  call store_error_filename(this%obs%inputFilename)
1043  end if
1044  !
1045  ! -- Return
1046  return
1047  end subroutine gwt_gwt_rp_obs
1048 
1049  !> @ brief Final processing
1050  !!
1051  !! Conduct any final processing
1052  !<
1053  subroutine gwt_gwt_fp(this)
1054  ! -- dummy
1055  class(gwtexchangetype) :: this !< GwtExchangeType
1056  !
1057  ! -- Return
1058  return
1059  end subroutine gwt_gwt_fp
1060 
1061  !> @brief Return true when this exchange provides matrix coefficients for
1062  !! solving @param model
1063  !<
1064  function gwt_gwt_connects_model(this, model) result(is_connected)
1065  ! -- dummy
1066  class(gwtexchangetype) :: this !< GwtExchangeType
1067  class(basemodeltype), pointer, intent(in) :: model !< the model to which the exchange might hold a connection
1068  ! -- return
1069  logical(LGP) :: is_connected !< true, when connected
1070  !
1071  is_connected = .false.
1072  !
1073  ! only connected when model is GwtModelType of course
1074  select type (model)
1075  class is (gwtmodeltype)
1076  if (associated(this%gwtmodel1, model)) then
1077  is_connected = .true.
1078  else if (associated(this%gwtmodel2, model)) then
1079  is_connected = .true.
1080  end if
1081  end select
1082  !
1083  ! -- Return
1084  return
1085  end function gwt_gwt_connects_model
1086 
1087  !> @brief Should interface model be used for this exchange
1088  !!
1089  !! For now this always returns true, since we do not support
1090  !! a classic-style two-point flux approximation for GWT-GWT.
1091  !! If we ever add logic to support a simpler non-interface
1092  !! model flux calculation, then logic should be added here to
1093  !! set the return accordingly.
1094  !<
1095  function use_interface_model(this) result(use_im)
1096  ! -- dummy
1097  class(gwtexchangetype) :: this !< GwtExchangeType
1098  ! -- return
1099  logical(LGP) :: use_im !< true when interface model should be used
1100  !
1101  ! For now set use_im to .true. since the interface model approach
1102  ! must currently be used for any GWT-GWT exchange.
1103  use_im = .true.
1104  !
1105  ! -- Return
1106  return
1107  end function
1108 
1109  !> @ brief Save simulated flow observations
1110  !!
1111  !! Save the simulated flows for each exchange
1112  !<
1113  subroutine gwt_gwt_save_simvals(this)
1114  ! -- dummy
1115  use simvariablesmodule, only: errmsg
1116  use constantsmodule, only: dzero
1117  use observemodule, only: observetype
1118  class(gwtexchangetype), intent(inout) :: this
1119  ! -- local
1120  integer(I4B) :: i
1121  integer(I4B) :: j
1122  integer(I4B) :: n1
1123  integer(I4B) :: n2
1124  integer(I4B) :: iexg
1125  real(DP) :: v
1126  type(observetype), pointer :: obsrv => null()
1127  !
1128  ! -- Write simulated values for all gwt-gwt observations
1129  if (this%obs%npakobs > 0) then
1130  call this%obs%obs_bd_clear()
1131  do i = 1, this%obs%npakobs
1132  obsrv => this%obs%pakobs(i)%obsrv
1133  do j = 1, obsrv%indxbnds_count
1134  iexg = obsrv%indxbnds(j)
1135  v = dzero
1136  select case (obsrv%ObsTypeId)
1137  case ('FLOW-JA-FACE')
1138  n1 = this%nodem1(iexg)
1139  n2 = this%nodem2(iexg)
1140  v = this%simvals(iexg)
1141  case default
1142  errmsg = 'Unrecognized observation type: '// &
1143  trim(obsrv%ObsTypeId)
1144  call store_error(errmsg)
1145  call store_error_filename(this%obs%inputFilename)
1146  end select
1147  call this%obs%SaveOneSimval(obsrv, v)
1148  end do
1149  end do
1150  end if
1151  !
1152  ! -- Return
1153  return
1154  end subroutine gwt_gwt_save_simvals
1155 
1156  !> @ brief Obs ID processor
1157  !!
1158  !! Process observations for this exchange
1159  !<
1160  subroutine gwt_gwt_process_obsid(obsrv, dis, inunitobs, iout)
1161  ! -- modules
1162  use constantsmodule, only: linelength
1163  use inputoutputmodule, only: urword
1164  use observemodule, only: observetype
1165  use basedismodule, only: disbasetype
1166  ! -- dummy
1167  type(observetype), intent(inout) :: obsrv
1168  class(disbasetype), intent(in) :: dis
1169  integer(I4B), intent(in) :: inunitobs
1170  integer(I4B), intent(in) :: iout
1171  ! -- local
1172  integer(I4B) :: n, iexg, istat
1173  integer(I4B) :: icol, istart, istop
1174  real(DP) :: r
1175  character(len=LINELENGTH) :: string
1176  !
1177  string = obsrv%IDstring
1178  icol = 1
1179  ! -- get exchange index
1180  call urword(string, icol, istart, istop, 1, n, r, iout, inunitobs)
1181  read (string(istart:istop), '(i10)', iostat=istat) iexg
1182  if (istat == 0) then
1183  obsrv%intPak1 = iexg
1184  else
1185  ! Integer can't be read from string; it's presumed to be an exchange
1186  ! boundary name (already converted to uppercase)
1187  obsrv%FeatureName = trim(adjustl(string))
1188  ! -- Observation may require summing rates from multiple exchange
1189  ! boundaries, so assign intPak1 as a value that indicates observation
1190  ! is for a named exchange boundary or group of exchange boundaries.
1191  obsrv%intPak1 = namedboundflag
1192  end if
1193  !
1194  ! -- Return
1195  return
1196  end subroutine gwt_gwt_process_obsid
1197 
1198  !> @ brief Cast polymorphic object as exchange
1199  !!
1200  !! Cast polymorphic object as exchange
1201  !<
1202  function castasgwtexchange(obj) result(res)
1203  implicit none
1204  ! -- dummy
1205  class(*), pointer, intent(inout) :: obj
1206  ! -- return
1207  class(gwtexchangetype), pointer :: res
1208  !
1209  res => null()
1210  if (.not. associated(obj)) return
1211  !
1212  select type (obj)
1213  class is (gwtexchangetype)
1214  res => obj
1215  end select
1216  !
1217  ! -- Return
1218  return
1219  end function castasgwtexchange
1220 
1221  !> @ brief Get exchange from list
1222  !!
1223  !! Return an exchange from the list for specified index
1224  !<
1225  function getgwtexchangefromlist(list, idx) result(res)
1226  implicit none
1227  ! -- dummy
1228  type(listtype), intent(inout) :: list
1229  integer(I4B), intent(in) :: idx
1230  ! -- return
1231  class(gwtexchangetype), pointer :: res
1232  ! -- local
1233  class(*), pointer :: obj
1234  !
1235  obj => list%GetItem(idx)
1236  res => castasgwtexchange(obj)
1237  !
1238  ! -- Return
1239  return
1240  end function getgwtexchangefromlist
1241 
1242 end module gwtgwtexchangemodule
1243 
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 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
@ tabcenter
centered table column
Definition: Constants.f90:171
@ tableft
left justified table column
Definition: Constants.f90:170
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:21
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:22
integer(i4b), parameter namedboundflag
named bound flag
Definition: Constants.f90:48
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:94
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
integer(i4b), parameter lenauxname
maximum length of a aux variable
Definition: Constants.f90:34
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:35
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
subroutine, public gnc_cr(gncobj, name_parent, inunit, iout)
Create new GNC exchange object.
Definition: GhostNode.f90:61
This module contains the GwtGwtExchangeModule Module.
Definition: exg-gwtgwt.f90:10
class(gwtexchangetype) function, pointer, public castasgwtexchange(obj)
@ brief Cast polymorphic object as exchange
subroutine allocate_scalars(this)
@ brief Allocate scalars
Definition: exg-gwtgwt.f90:814
subroutine gwt_gwt_fc(this, kiter, matrix_sln, rhs_sln, inwtflag)
@ brief Fill coefficients
Definition: exg-gwtgwt.f90:374
subroutine read_mvt(this, iout)
@ brief Read mover
Definition: exg-gwtgwt.f90:790
subroutine gwt_gwt_df_obs(this)
@ brief Define observations
Definition: exg-gwtgwt.f90:961
subroutine source_options(this, iout)
@ brief Source options
Definition: exg-gwtgwt.f90:699
subroutine gwt_gwt_df(this)
@ brief Define GWT GWT exchange
Definition: exg-gwtgwt.f90:198
subroutine gwt_gwt_process_obsid(obsrv, dis, inunitobs, iout)
@ brief Obs ID processor
subroutine, public gwtexchange_create(filename, name, id, m1_id, m2_id, input_mempath)
@ brief Create GWT GWT exchange
Definition: exg-gwtgwt.f90:110
subroutine validate_exchange(this)
validate exchange data after reading
Definition: exg-gwtgwt.f90:253
subroutine gwt_gwt_bdsav(this)
@ brief Budget save
Definition: exg-gwtgwt.f90:438
subroutine gwt_gwt_fp(this)
@ brief Final processing
logical(lgp) function gwt_gwt_connects_model(this, model)
Return true when this exchange provides matrix coefficients for solving.
subroutine gwt_gwt_save_simvals(this)
@ brief Save simulated flow observations
subroutine gwt_gwt_ad(this)
@ brief Advance
Definition: exg-gwtgwt.f90:356
subroutine gwt_gwt_rp_obs(this)
@ brief Read and prepare observations
Definition: exg-gwtgwt.f90:980
subroutine gwt_gwt_bdsav_model(this, model)
@ brief Budget save
Definition: exg-gwtgwt.f90:475
class(gwtexchangetype) function, pointer, public getgwtexchangefromlist(list, idx)
@ brief Get exchange from list
subroutine allocate_arrays(this)
@ brief Allocate arrays
Definition: exg-gwtgwt.f90:890
subroutine gwt_gwt_ar(this)
@ brief Allocate and read
Definition: exg-gwtgwt.f90:315
subroutine gwt_gwt_bd(this, icnvg, isuppress_output, isolnid)
@ brief Budget
Definition: exg-gwtgwt.f90:393
logical(lgp) function use_interface_model(this)
Should interface model be used for this exchange.
subroutine gwt_gwt_rp(this)
@ brief Read and prepare
Definition: exg-gwtgwt.f90:333
subroutine gwt_gwt_da(this)
@ brief Deallocate
Definition: exg-gwtgwt.f90:841
subroutine gwt_gwt_ot(this)
@ brief Output
Definition: exg-gwtgwt.f90:642
Definition: gwt.f90:8
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
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
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
This module contains the derived types ObserveType and ObsDataType.
Definition: Observe.f90:15
This module contains the derived type ObsType.
Definition: Obs.f90:127
subroutine, public obs_cr(obs, inobs)
@ brief Create a new ObsType object
Definition: Obs.f90:225
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
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
This module contains the SourceCommonModule.
Definition: SourceCommon.f90:7
logical(lgp) function, public filein_fname(filename, tagname, input_mempath, input_fname)
enforce and set a single input filename provided via FILEIN keyword
subroutine, public table_cr(this, name, title)
Definition: Table.f90:85
logical(lgp), pointer, public readnewdata
flag indicating time to read new data
Definition: tdis.f90:26
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
subroutine, public mvt_cr(mvt, name_model, inunit, iout, fmi1, eqnsclfac, depvartype, gwfmodelname1, gwfmodelname2, fmi2)
Create a new mover transport object.
Definition: tsp-mvt.f90:75
Highest level model type. All models extend this parent type.
Definition: BaseModel.f90:13
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
Exchange based on connection between discretizations of DisBaseType. The data specifies the connectio...
Derived type for GwtExchangeType.
Definition: exg-gwtgwt.f90:46
A generic heterogeneous doubly-linked list.
Definition: List.f90:10