MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
exg-gwfgwf.f90
Go to the documentation of this file.
1 !> @brief This module contains the GwfGwfExchangeModule Module
2 !!
3 !! This module contains the code for connecting two GWF 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 GwfGwfConnection with the more sophisticated
7 !! interface model coupling approach when XT3D is needed.
8 !!
9 !<
11 
12  use kindmodule, only: dp, i4b, lgp
13  use simvariablesmodule, only: errmsg
18  use basedismodule, only: disbasetype
21  use listmodule, only: listtype
22  use listsmodule, only: basemodellist
24  use gwfmodule, only: gwfmodeltype
28  use observemodule, only: observetype
29  use obsmodule, only: obstype
31  use tablemodule, only: tabletype, table_cr
33 
34  implicit none
35 
36  private
37  public :: gwfexchangetype
38  public :: gwfexchange_create
39  public :: getgwfexchangefromlist
40  public :: castasgwfexchange
41 
42  !> @brief Derived type for GwfExchangeType
43  !!
44  !! This derived type contains information and methods for
45  !! connecting two GWF models.
46  !<
48  class(gwfmodeltype), pointer :: gwfmodel1 => null() !< pointer to GWF Model 1
49  class(gwfmodeltype), pointer :: gwfmodel2 => null() !< pointer to GWF Model 2
50  !
51  ! -- GWF specific option block:
52  integer(I4B), pointer :: inewton => null() !< newton flag (1 newton is on)
53  integer(I4B), pointer :: icellavg => null() !< cell averaging
54  integer(I4B), pointer :: ivarcv => null() !< variable cv
55  integer(I4B), pointer :: idewatcv => null() !< dewatered cv
56  integer(I4B), pointer :: ingnc => null() !< unit number for gnc (0 if off)
57  type(ghostnodetype), pointer :: gnc => null() !< gnc object
58  integer(I4B), pointer :: inmvr => null() !< unit number for mover (0 if off)
59  class(gwfexgmovertype), pointer :: mvr => null() !< water mover object
60  integer(I4B), pointer :: inobs => null() !< unit number for GWF-GWF observations
61  type(obstype), pointer :: obs => null() !< observation object
62  !
63  ! -- internal data
64  real(dp), dimension(:), pointer, contiguous :: cond => null() !< conductance
65  real(dp), dimension(:), pointer, contiguous :: condsat => null() !< saturated conductance
66  integer(I4B), dimension(:), pointer, contiguous :: idxglo => null() !< mapping to global (solution) amat
67  integer(I4B), dimension(:), pointer, contiguous :: idxsymglo => null() !< mapping to global (solution) symmetric amat
68  real(dp), pointer :: satomega => null() !< saturation smoothing
69  real(dp), dimension(:), pointer, contiguous :: simvals => null() !< simulated flow rate for each exchange
70  !
71  ! -- table objects
72  type(tabletype), pointer :: outputtab1 => null()
73  type(tabletype), pointer :: outputtab2 => null()
74 
75  contains
76 
77  procedure :: exg_df => gwf_gwf_df
78  procedure :: exg_ac => gwf_gwf_ac
79  procedure :: exg_mc => gwf_gwf_mc
80  procedure :: exg_ar => gwf_gwf_ar
81  procedure :: exg_rp => gwf_gwf_rp
82  procedure :: exg_ad => gwf_gwf_ad
83  procedure :: exg_cf => gwf_gwf_cf
84  procedure :: exg_fc => gwf_gwf_fc
85  procedure :: exg_fn => gwf_gwf_fn
86  procedure :: exg_cq => gwf_gwf_cq
87  procedure :: exg_bd => gwf_gwf_bd
88  procedure :: exg_ot => gwf_gwf_ot
89  procedure :: exg_da => gwf_gwf_da
90  procedure :: exg_fp => gwf_gwf_fp
91  procedure :: get_iasym => gwf_gwf_get_iasym
92  procedure :: connects_model => gwf_gwf_connects_model
93  procedure :: use_interface_model
94  procedure :: allocate_scalars
95  procedure :: allocate_arrays
96  procedure :: source_options
97  procedure :: read_gnc
98  procedure :: read_mvr
99  procedure, private :: calc_cond_sat
100  procedure, private :: condcalc
101  procedure, private :: rewet
102  procedure, private :: qcalc
103  procedure, private :: gwf_gwf_chd_bd
104  procedure :: gwf_gwf_bdsav
105  procedure, private :: gwf_gwf_bdsav_model
106  procedure, private :: gwf_gwf_df_obs
107  procedure, private :: gwf_gwf_rp_obs
108  procedure, public :: gwf_gwf_save_simvals
109  procedure, private :: gwf_gwf_calc_simvals
110  procedure, public :: gwf_gwf_set_flow_to_npf
111  procedure, private :: validate_exchange
113  end type gwfexchangetype
114 
115 contains
116 
117  !> @ brief Create GWF GWF exchange
118  !!
119  !! Create a new GWF to GWF exchange object.
120  !<
121  subroutine gwfexchange_create(filename, name, id, m1_id, m2_id, input_mempath)
122  ! -- modules
123  use basemodelmodule, only: basemodeltype
125  use listsmodule, only: baseexchangelist
126  use obsmodule, only: obs_cr
128  ! -- dummy
129  character(len=*), intent(in) :: filename !< filename for reading
130  character(len=*) :: name !< exchange name
131  integer(I4B), intent(in) :: id !< id for the exchange
132  integer(I4B), intent(in) :: m1_id !< id for model 1
133  integer(I4B), intent(in) :: m2_id !< id for model 2
134  character(len=*), intent(in) :: input_mempath
135  ! -- local
136  type(gwfexchangetype), pointer :: exchange
137  class(basemodeltype), pointer :: mb
138  class(baseexchangetype), pointer :: baseexchange
139  integer(I4B) :: m1_index, m2_index
140  !
141  ! -- Create a new exchange and add it to the baseexchangelist container
142  allocate (exchange)
143  baseexchange => exchange
144  call addbaseexchangetolist(baseexchangelist, baseexchange)
145  !
146  ! -- Assign id and name
147  exchange%id = id
148  exchange%name = name
149  exchange%memoryPath = create_mem_path(exchange%name)
150  exchange%input_mempath = input_mempath
151  !
152  ! -- allocate scalars and set defaults
153  call exchange%allocate_scalars()
154  exchange%filename = filename
155  exchange%typename = 'GWF-GWF'
156  !
157  ! -- set gwfmodel1
158  m1_index = model_loc_idx(m1_id)
159  if (m1_index > 0) then
160  mb => getbasemodelfromlist(basemodellist, m1_index)
161  select type (mb)
162  type is (gwfmodeltype)
163  exchange%model1 => mb
164  exchange%gwfmodel1 => mb
165  end select
166  end if
167  exchange%v_model1 => get_virtual_model(m1_id)
168  exchange%is_datacopy = .not. exchange%v_model1%is_local
169  !
170  ! -- set gwfmodel2
171  m2_index = model_loc_idx(m2_id)
172  if (m2_index > 0) then
173  mb => getbasemodelfromlist(basemodellist, m2_index)
174  select type (mb)
175  type is (gwfmodeltype)
176  exchange%model2 => mb
177  exchange%gwfmodel2 => mb
178  end select
179  end if
180  exchange%v_model2 => get_virtual_model(m2_id)
181  !
182  ! -- Verify that gwf model1 is of the correct type
183  if (.not. associated(exchange%gwfmodel1) .and. m1_index > 0) then
184  write (errmsg, '(3a)') 'Problem with GWF-GWF exchange ', &
185  trim(exchange%name), &
186  '. First specified GWF Model does not appear to be of the correct type.'
187  call store_error(errmsg, terminate=.true.)
188  end if
189  !
190  ! -- Verify that gwf model2 is of the correct type
191  if (.not. associated(exchange%gwfmodel2) .and. m2_index > 0) then
192  write (errmsg, '(3a)') 'Problem with GWF-GWF exchange ', &
193  trim(exchange%name), &
194  '. Second specified GWF Model does not appear to be of the correct type.'
195  call store_error(errmsg, terminate=.true.)
196  end if
197  !
198  ! -- Create the obs package
199  call obs_cr(exchange%obs, exchange%inobs)
200  !
201  ! -- Return
202  return
203  end subroutine gwfexchange_create
204 
205  !> @ brief Define GWF GWF exchange
206  !!
207  !! Define GWF to GWF exchange object.
208  !<
209  subroutine gwf_gwf_df(this)
210  ! -- modules
211  use simvariablesmodule, only: iout
213  use ghostnodemodule, only: gnc_cr
214  ! -- dummy
215  class(gwfexchangetype) :: this !< GwfExchangeType
216  ! -- local
217  !
218  ! -- log the exchange
219  write (iout, '(/a,a)') ' Creating exchange: ', this%name
220  !
221  ! -- Ensure models are in same solution
222  if (this%v_model1%idsoln%get() /= this%v_model2%idsoln%get()) then
223  call store_error('Two models are connected in a GWF '// &
224  'exchange but they are in different solutions. '// &
225  'GWF models must be in same solution: '// &
226  trim(this%v_model1%name)//' '// &
227  trim(this%v_model2%name))
228  call store_error_filename(this%filename)
229  end if
230  !
231  ! -- source options
232  call this%source_options(iout)
233  !
234  ! -- source dimensions
235  call this%source_dimensions(iout)
236  !
237  ! -- allocate arrays
238  call this%allocate_arrays()
239  !
240  ! -- source exchange data
241  call this%source_data(iout)
242  !
243  ! -- call each model and increase the edge count
244  if (associated(this%gwfmodel1)) then
245  call this%gwfmodel1%npf%increase_edge_count(this%nexg)
246  end if
247  if (associated(this%gwfmodel2)) then
248  call this%gwfmodel2%npf%increase_edge_count(this%nexg)
249  end if
250  !
251  ! -- Create and read ghost node information
252  if (this%ingnc > 0) then
253  if (associated(this%gwfmodel1) .and. associated(this%gwfmodel2)) then
254  call gnc_cr(this%gnc, this%name, this%ingnc, iout)
255  call this%read_gnc()
256  end if
257  end if
258  !
259  ! -- Read mover information
260  if (this%inmvr > 0) then
261  call this%read_mvr(iout)
262  end if
263  !
264  ! -- Store obs
265  call this%gwf_gwf_df_obs()
266  if (associated(this%gwfmodel1)) then
267  call this%obs%obs_df(iout, this%name, 'GWF-GWF', this%gwfmodel1%dis)
268  end if
269  !
270  ! -- validate
271  call this%validate_exchange()
272  !
273  ! -- Return
274  return
275  end subroutine gwf_gwf_df
276 
277  !> @brief validate exchange data after reading
278  !<
279  subroutine validate_exchange(this)
280  ! -- modules
281  class(gwfexchangetype) :: this !< GwfExchangeType
282  ! -- local
283  logical(LGP) :: has_k22, has_spdis, has_vsc
284  !
285  ! Periodic boundary condition in exchange don't allow XT3D (=interface model)
286  if (this%v_model1 == this%v_model2) then
287  if (this%ixt3d > 0) then
288  write (errmsg, '(3a)') 'GWF-GWF exchange ', trim(this%name), &
289  ' is a periodic boundary condition which cannot'// &
290  ' be configured with XT3D'
291  call store_error(errmsg, terminate=.true.)
292  end if
293  end if
294  !
295  ! XT3D needs angle information
296  if (this%ixt3d > 0 .and. this%ianglex == 0) then
297  write (errmsg, '(3a)') 'GWF-GWF exchange ', trim(this%name), &
298  ' requires that ANGLDEGX be specified as an'// &
299  ' auxiliary variable because XT3D is enabled'
300  call store_error(errmsg, terminate=.true.)
301  end if
302  !
303  ! determine if specific functionality is demanded,
304  ! in model 1 or model 2 (in parallel, only one of
305  ! the models is checked, but the exchange is duplicated)
306  has_k22 = .false.
307  has_spdis = .false.
308  has_vsc = .false.
309  if (associated(this%gwfmodel1)) then
310  has_k22 = (this%gwfmodel1%npf%ik22 /= 0)
311  has_spdis = (this%gwfmodel1%npf%icalcspdis /= 0)
312  has_vsc = (this%gwfmodel1%npf%invsc /= 0)
313  end if
314  if (associated(this%gwfmodel2)) then
315  has_k22 = has_k22 .or. (this%gwfmodel2%npf%ik22 /= 0)
316  has_spdis = has_spdis .or. (this%gwfmodel2%npf%icalcspdis /= 0)
317  has_vsc = has_vsc .or. (this%gwfmodel2%npf%invsc /= 0)
318  end if
319  !
320  ! If horizontal anisotropy is in either model1 or model2,
321  ! ANGLDEGX must be provided as an auxiliary variable for this
322  ! GWF-GWF exchange (this%ianglex > 0).
323  if (has_k22) then
324  if (this%ianglex == 0) then
325  write (errmsg, '(3a)') 'GWF-GWF exchange ', trim(this%name), &
326  ' requires that ANGLDEGX be specified as an'// &
327  ' auxiliary variable because K22 was specified'// &
328  ' in one or both groundwater models.'
329  call store_error(errmsg, terminate=.true.)
330  end if
331  end if
332  !
333  ! If specific discharge is needed for model1 or model2,
334  ! ANGLDEGX must be provided as an auxiliary variable for this
335  ! GWF-GWF exchange (this%ianglex > 0).
336  if (has_spdis) then
337  if (this%ianglex == 0) then
338  write (errmsg, '(3a)') 'GWF-GWF exchange ', trim(this%name), &
339  ' requires that ANGLDEGX be specified as an'// &
340  ' auxiliary variable because specific discharge'// &
341  ' is being calculated in one or both'// &
342  ' groundwater models.'
343  call store_error(errmsg, terminate=.true.)
344  end if
345  if (this%icdist == 0) then
346  write (errmsg, '(3a)') 'GWF-GWF exchange ', trim(this%name), &
347  ' requires that CDIST be specified as an'// &
348  ' auxiliary variable because specific discharge'// &
349  ' is being calculated in one or both'// &
350  ' groundwater models.'
351  call store_error(errmsg, terminate=.true.)
352  end if
353  end if
354  !
355  ! If viscosity is on in either model, then terminate with an
356  ! error as viscosity package doesn't work yet with exchanges.
357  if (has_vsc) then
358  write (errmsg, '(3a)') 'GWF-GWF exchange ', trim(this%name), &
359  ' requires that the Viscosity Package is inactive'// &
360  ' in both of the connected models.'
361  call store_error(errmsg, terminate=.true.)
362  end if
363  !
364  ! -- Return
365  return
366  end subroutine validate_exchange
367 
368  !> @ brief Add connections
369  !!
370  !! Override parent exg_ac so that gnc can add connections here.
371  !<
372  subroutine gwf_gwf_ac(this, sparse)
373  ! -- modules
374  use sparsemodule, only: sparsematrix
375  ! -- dummy
376  class(gwfexchangetype) :: this !< GwfExchangeType
377  type(sparsematrix), intent(inout) :: sparse
378  ! -- local
379  integer(I4B) :: n, iglo, jglo
380  !
381  ! -- add exchange connections
382  do n = 1, this%nexg
383  iglo = this%nodem1(n) + this%gwfmodel1%moffset
384  jglo = this%nodem2(n) + this%gwfmodel2%moffset
385  call sparse%addconnection(iglo, jglo, 1)
386  call sparse%addconnection(jglo, iglo, 1)
387  end do
388  !
389  ! -- add gnc connections
390  if (this%ingnc > 0) then
391  call this%gnc%gnc_ac(sparse)
392  end if
393  !
394  ! -- Return
395  return
396  end subroutine gwf_gwf_ac
397 
398  !> @ brief Map connections
399  !!
400  !! Map the connections in the global matrix
401  !<
402  subroutine gwf_gwf_mc(this, matrix_sln)
403  ! -- modules
404  use sparsemodule, only: sparsematrix
405  ! -- dummy
406  class(gwfexchangetype) :: this !< GwfExchangeType
407  class(matrixbasetype), pointer :: matrix_sln !< the system matrix
408  ! -- local
409  integer(I4B) :: n, iglo, jglo
410  !
411  ! -- map exchange connections
412  do n = 1, this%nexg
413  iglo = this%nodem1(n) + this%gwfmodel1%moffset
414  jglo = this%nodem2(n) + this%gwfmodel2%moffset
415  this%idxglo(n) = matrix_sln%get_position(iglo, jglo)
416  this%idxsymglo(n) = matrix_sln%get_position(jglo, iglo)
417  end do
418  !
419  ! -- map gnc connections
420  if (this%ingnc > 0) then
421  call this%gnc%gnc_mc(matrix_sln)
422  end if
423  !
424  ! -- Return
425  return
426  end subroutine gwf_gwf_mc
427 
428  !> @ brief Allocate and read
429  !!
430  !! Allocated and read and calculate saturated conductance
431  !<
432  subroutine gwf_gwf_ar(this)
433  ! -- dummy
434  class(gwfexchangetype) :: this !< GwfExchangeType
435  !
436  ! -- If mover is active, then call ar routine
437  if (this%inmvr > 0) call this%mvr%mvr_ar()
438  !
439  ! -- Calculate the saturated conductance for all connections
440  if (.not. this%use_interface_model()) call this%calc_cond_sat()
441  !
442  ! -- Observation AR
443  call this%obs%obs_ar()
444  !
445  ! -- Return
446  return
447  end subroutine gwf_gwf_ar
448 
449  !> @ brief Read and prepare
450  !!
451  !! Read new data for mover and obs
452  !<
453  subroutine gwf_gwf_rp(this)
454  ! -- modules
455  use tdismodule, only: readnewdata
456  ! -- dummy
457  class(gwfexchangetype) :: this !< GwfExchangeType
458  !
459  ! -- Check with TDIS on whether or not it is time to RP
460  if (.not. readnewdata) return
461  !
462  ! -- Read and prepare for mover
463  if (this%inmvr > 0) call this%mvr%mvr_rp()
464  !
465  ! -- Read and prepare for observations
466  call this%gwf_gwf_rp_obs()
467  !
468  ! -- Return
469  return
470  end subroutine gwf_gwf_rp
471 
472  !> @ brief Advance
473  !!
474  !! Advance mover and obs
475  !<
476  subroutine gwf_gwf_ad(this)
477  ! -- dummy
478  class(gwfexchangetype) :: this !< GwfExchangeType
479  !
480  ! -- Advance mover
481  if (this%inmvr > 0) call this%mvr%mvr_ad()
482  !
483  ! -- Push simulated values to preceding time step
484  call this%obs%obs_ad()
485  !
486  ! -- Return
487  return
488  end subroutine gwf_gwf_ad
489 
490  !> @ brief Calculate coefficients
491  !!
492  !! Rewet as necessary
493  !<
494  subroutine gwf_gwf_cf(this, kiter)
495  ! -- dummy
496  class(gwfexchangetype) :: this !< GwfExchangeType
497  integer(I4B), intent(in) :: kiter
498  ! -- local
499  !
500  ! -- Call mvr fc routine
501  if (this%inmvr > 0) call this%mvr%xmvr_cf()
502  !
503  ! -- Rewet cells across models using the wetdry parameters in each model's
504  ! npf package, and the head in the connected model.
505  call this%rewet(kiter)
506  !
507  ! -- Return
508  return
509  end subroutine gwf_gwf_cf
510 
511  !> @ brief Fill coefficients
512  !!
513  !! Calculate conductance and fill coefficient matrix
514  !<
515  subroutine gwf_gwf_fc(this, kiter, matrix_sln, rhs_sln, inwtflag)
516  ! -- modules
517  use constantsmodule, only: dhalf
519  ! -- dummy
520  class(gwfexchangetype) :: this !< GwfExchangeType
521  integer(I4B), intent(in) :: kiter
522  class(matrixbasetype), pointer :: matrix_sln
523  real(DP), dimension(:), intent(inout) :: rhs_sln
524  integer(I4B), optional, intent(in) :: inwtflag
525  ! -- local
526  integer(I4B) :: inwt, iexg
527  integer(I4B) :: i, nodem1sln, nodem2sln
528  !
529  ! -- calculate the conductance for each exchange connection
530  call this%condcalc()
531  !
532  ! -- if gnc is active, then copy cond into gnc cond (might consider a
533  ! pointer here in the future)
534  if (this%ingnc > 0) then
535  do iexg = 1, this%nexg
536  this%gnc%cond(iexg) = this%cond(iexg)
537  end do
538  end if
539  !
540  ! -- Put this%cond into amatsln
541  do i = 1, this%nexg
542  call matrix_sln%set_value_pos(this%idxglo(i), this%cond(i))
543  call matrix_sln%set_value_pos(this%idxsymglo(i), this%cond(i))
544 
545  nodem1sln = this%nodem1(i) + this%gwfmodel1%moffset
546  nodem2sln = this%nodem2(i) + this%gwfmodel2%moffset
547  call matrix_sln%add_diag_value(nodem1sln, -this%cond(i))
548  call matrix_sln%add_diag_value(nodem2sln, -this%cond(i))
549  end do
550  !
551  ! -- Fill the gnc terms in the solution matrix
552  if (this%ingnc > 0) then
553  call this%gnc%gnc_fc(kiter, matrix_sln)
554  end if
555  !
556  ! -- Call mvr fc routine
557  if (this%inmvr > 0) call this%mvr%mvr_fc()
558  !
559  ! -- Set inwt to exchange newton, but shut off if requested by caller
560  inwt = this%inewton
561  if (present(inwtflag)) then
562  if (inwtflag == 0) inwt = 0
563  end if
564  if (inwt /= 0) then
565  call this%exg_fn(kiter, matrix_sln)
566  end if
567  !
568  ! -- Ghost node Newton-Raphson
569  if (this%ingnc > 0) then
570  if (inwt /= 0) then
571  call this%gnc%gnc_fn(kiter, matrix_sln, this%condsat, &
572  ihc_opt=this%ihc, ivarcv_opt=this%ivarcv, &
573  ictm1_opt=this%gwfmodel1%npf%icelltype, &
574  ictm2_opt=this%gwfmodel2%npf%icelltype)
575  end if
576  end if
577  !
578  ! -- Return
579  return
580  end subroutine gwf_gwf_fc
581 
582  !> @ brief Fill Newton
583  !!
584  !! Fill amatsln with Newton terms
585  !<
586  subroutine gwf_gwf_fn(this, kiter, matrix_sln)
587  ! -- modules
589  ! -- dummy
590  class(gwfexchangetype) :: this !< GwfExchangeType
591  integer(I4B), intent(in) :: kiter
592  class(matrixbasetype), pointer :: matrix_sln
593  ! -- local
594  logical :: nisup
595  integer(I4B) :: iexg
596  integer(I4B) :: n, m
597  integer(I4B) :: nodensln, nodemsln
598  integer(I4B) :: ibdn, ibdm
599  real(DP) :: topn, topm
600  real(DP) :: botn, botm
601  real(DP) :: topup, botup
602  real(DP) :: hn, hm
603  real(DP) :: hup, hdn
604  real(DP) :: cond
605  real(DP) :: term
606  real(DP) :: consterm
607  real(DP) :: derv
608  !
609  do iexg = 1, this%nexg
610  n = this%nodem1(iexg)
611  m = this%nodem2(iexg)
612  nodensln = this%nodem1(iexg) + this%gwfmodel1%moffset
613  nodemsln = this%nodem2(iexg) + this%gwfmodel2%moffset
614  ibdn = this%gwfmodel1%ibound(n)
615  ibdm = this%gwfmodel2%ibound(m)
616  topn = this%gwfmodel1%dis%top(n)
617  topm = this%gwfmodel2%dis%top(m)
618  botn = this%gwfmodel1%dis%bot(n)
619  botm = this%gwfmodel2%dis%bot(m)
620  hn = this%gwfmodel1%x(n)
621  hm = this%gwfmodel2%x(m)
622  if (this%ihc(iexg) == 0) then
623  ! -- vertical connection, newton not supported
624  else
625  ! -- determine upstream node
626  nisup = .false.
627  if (hm < hn) nisup = .true.
628  !
629  ! -- set upstream top and bot
630  if (nisup) then
631  topup = topn
632  botup = botn
633  hup = hn
634  hdn = hm
635  else
636  topup = topm
637  botup = botm
638  hup = hm
639  hdn = hn
640  end if
641  !
642  ! -- no newton terms if upstream cell is confined
643  if (nisup) then
644  if (this%gwfmodel1%npf%icelltype(n) == 0) cycle
645  else
646  if (this%gwfmodel2%npf%icelltype(m) == 0) cycle
647  end if
648  !
649  ! -- set topup and botup
650  if (this%ihc(iexg) == 2) then
651  topup = min(topn, topm)
652  botup = max(botn, botm)
653  end if
654  !
655  ! get saturated conductivity for derivative
656  cond = this%condsat(iexg)
657  !
658  ! -- TO DO deal with MODFLOW-NWT upstream weighting option
659  !
660  ! -- compute terms
661  consterm = -cond * (hup - hdn)
662  derv = squadraticsaturationderivative(topup, botup, hup)
663  if (nisup) then
664  !
665  ! -- fill jacobian with n being upstream
666  term = consterm * derv
667  this%gwfmodel1%rhs(n) = this%gwfmodel1%rhs(n) + term * hn
668  this%gwfmodel2%rhs(m) = this%gwfmodel2%rhs(m) - term * hn
669  call matrix_sln%add_diag_value(nodensln, term)
670  if (ibdm > 0) then
671  call matrix_sln%add_value_pos(this%idxsymglo(iexg), -term)
672  end if
673  else
674  !
675  ! -- fill jacobian with m being upstream
676  term = -consterm * derv
677  this%gwfmodel1%rhs(n) = this%gwfmodel1%rhs(n) + term * hm
678  this%gwfmodel2%rhs(m) = this%gwfmodel2%rhs(m) - term * hm
679  call matrix_sln%add_diag_value(nodemsln, -term)
680  if (ibdn > 0) then
681  call matrix_sln%add_value_pos(this%idxglo(iexg), term)
682  end if
683  end if
684  end if
685  end do
686  !
687  ! -- Return
688  return
689  end subroutine gwf_gwf_fn
690 
691  !> @ brief Calculate flow
692  !!
693  !! Calculate flow between two cells and store in simvals, also set
694  !! information needed for specific discharge calculation
695  !<
696  subroutine gwf_gwf_cq(this, icnvg, isuppress_output, isolnid)
697  ! -- dummy
698  class(gwfexchangetype) :: this !< GwfExchangeType
699  integer(I4B), intent(inout) :: icnvg
700  integer(I4B), intent(in) :: isuppress_output
701  integer(I4B), intent(in) :: isolnid
702  !
703  ! -- calculate flow and store in simvals
704  call this%gwf_gwf_calc_simvals()
705  !
706  ! -- set flows to model edges in NPF
707  call this%gwf_gwf_set_flow_to_npf()
708  !
709  ! -- add exchange flows to model's flowja diagonal
710  call this%gwf_gwf_add_to_flowja()
711  !
712  ! -- Return
713  return
714  end subroutine gwf_gwf_cq
715 
716  !> @brief Calculate flow rates for the exchanges and store them in a member
717  !! array
718  !<
719  subroutine gwf_gwf_calc_simvals(this)
720  ! -- modules
721  use constantsmodule, only: dzero
722  ! -- dummy
723  class(gwfexchangetype) :: this !< GwfExchangeType
724  ! -- local
725  integer(I4B) :: i
726  integer(I4B) :: n1, n2
727  integer(I4B) :: ibdn1, ibdn2
728  real(DP) :: rrate
729  !
730  do i = 1, this%nexg
731  rrate = dzero
732  n1 = this%nodem1(i)
733  n2 = this%nodem2(i)
734  ibdn1 = this%gwfmodel1%ibound(n1)
735  ibdn2 = this%gwfmodel2%ibound(n2)
736  if (ibdn1 /= 0 .and. ibdn2 /= 0) then
737  rrate = this%qcalc(i, n1, n2)
738  if (this%ingnc > 0) then
739  rrate = rrate + this%gnc%deltaqgnc(i)
740  end if
741  end if
742  this%simvals(i) = rrate
743  end do
744  !
745  ! -- Return
746  return
747  end subroutine gwf_gwf_calc_simvals
748 
749  !> @brief Add exchange flow to each model flowja diagonal position so that
750  !! residual is calculated correctly.
751  !<
752  subroutine gwf_gwf_add_to_flowja(this)
753  ! -- modules
754  class(gwfexchangetype) :: this !< GwfExchangeType
755  ! -- local
756  integer(I4B) :: i
757  integer(I4B) :: n
758  integer(I4B) :: idiag
759  real(DP) :: flow
760  !
761  do i = 1, this%nexg
762  !
763  if (associated(this%gwfmodel1)) then
764  n = this%nodem1(i)
765  if (this%gwfmodel1%ibound(n) > 0) then
766  flow = this%simvals(i)
767  idiag = this%gwfmodel1%ia(n)
768  this%gwfmodel1%flowja(idiag) = this%gwfmodel1%flowja(idiag) + flow
769  end if
770  end if
771  !
772  if (associated(this%gwfmodel2)) then
773  n = this%nodem2(i)
774  if (this%gwfmodel2%ibound(n) > 0) then
775  flow = -this%simvals(i)
776  idiag = this%gwfmodel2%ia(n)
777  this%gwfmodel2%flowja(idiag) = this%gwfmodel2%flowja(idiag) + flow
778  end if
779  end if
780  !
781  end do
782  !
783  ! -- Return
784  return
785  end subroutine gwf_gwf_add_to_flowja
786 
787  !> @brief Set flow rates to the edges in the models
788  !<
789  subroutine gwf_gwf_set_flow_to_npf(this)
790  ! -- modules
791  use constantsmodule, only: dzero, dpio180
793  ! -- dummy
794  class(gwfexchangetype) :: this !< GwfExchangeType
795  ! -- local
796  integer(I4B) :: i
797  integer(I4B) :: n1, n2
798  integer(I4B) :: ibdn1, ibdn2
799  integer(I4B) :: ictn1, ictn2
800  integer(I4B) :: ihc
801  real(DP) :: rrate
802  real(DP) :: topn1, topn2
803  real(DP) :: botn1, botn2
804  real(DP) :: satn1, satn2
805  real(DP) :: hn1, hn2
806  real(DP) :: nx, ny
807  real(DP) :: distance
808  real(DP) :: dltot
809  real(DP) :: hwva
810  real(DP) :: area
811  real(DP) :: thksat
812  real(DP) :: angle
813  !
814  ! -- Return if there neither model needs to calculate specific discharge
815  if (this%gwfmodel1%npf%icalcspdis == 0 .and. &
816  this%gwfmodel2%npf%icalcspdis == 0) return
817  !
818  ! -- Loop through all exchanges using the flow rate
819  ! stored in simvals
820  do i = 1, this%nexg
821  rrate = this%simvals(i)
822  n1 = this%nodem1(i)
823  n2 = this%nodem2(i)
824  ihc = this%ihc(i)
825  hwva = this%hwva(i)
826  ibdn1 = this%gwfmodel1%ibound(n1)
827  ibdn2 = this%gwfmodel2%ibound(n2)
828  ictn1 = this%gwfmodel1%npf%icelltype(n1)
829  ictn2 = this%gwfmodel2%npf%icelltype(n2)
830  topn1 = this%gwfmodel1%dis%top(n1)
831  topn2 = this%gwfmodel2%dis%top(n2)
832  botn1 = this%gwfmodel1%dis%bot(n1)
833  botn2 = this%gwfmodel2%dis%bot(n2)
834  satn1 = this%gwfmodel1%npf%sat(n1)
835  satn2 = this%gwfmodel2%npf%sat(n2)
836  hn1 = this%gwfmodel1%x(n1)
837  hn2 = this%gwfmodel2%x(n2)
838  !
839  ! -- Calculate face normal components
840  if (ihc == 0) then
841  nx = dzero
842  ny = dzero
843  area = hwva
844  if (botn1 < botn2) then
845  ! -- n1 is beneath n2, so rate is positive downward. Flip rate
846  ! upward so that points in positive z direction
847  rrate = -rrate
848  end if
849  else
850  if (this%ianglex > 0) then
851  angle = this%auxvar(this%ianglex, i) * dpio180
852  nx = cos(angle)
853  ny = sin(angle)
854  else
855  ! error?
856  call store_error('error in gwf_gwf_cq', terminate=.true.)
857  end if
858  !
859  ! -- Calculate the saturated thickness at interface between n1 and n2
860  thksat = thksatnm(ibdn1, ibdn2, ictn1, ictn2, this%inewton, ihc, &
861  hn1, hn2, satn1, satn2, &
862  topn1, topn2, botn1, botn2)
863  area = hwva * thksat
864  end if
865  !
866  ! -- Submit this connection and flow information to the npf
867  ! package of gwfmodel1
868  if (this%icdist > 0) then
869  dltot = this%auxvar(this%icdist, i)
870  else
871  call store_error('error in gwf_gwf_cq', terminate=.true.)
872  end if
873  distance = dltot * this%cl1(i) / (this%cl1(i) + this%cl2(i))
874  if (this%gwfmodel1%npf%icalcspdis == 1) then
875  call this%gwfmodel1%npf%set_edge_properties(n1, ihc, rrate, area, &
876  nx, ny, distance)
877  end if
878  !
879  ! -- Submit this connection and flow information to the npf
880  ! package of gwfmodel2
881  if (this%icdist > 0) then
882  dltot = this%auxvar(this%icdist, i)
883  else
884  call store_error('error in gwf_gwf_cq', terminate=.true.)
885  end if
886  if (this%gwfmodel2%npf%icalcspdis == 1) then
887  distance = dltot * this%cl2(i) / (this%cl1(i) + this%cl2(i))
888  if (ihc /= 0) rrate = -rrate
889  call this%gwfmodel2%npf%set_edge_properties(n2, ihc, rrate, area, &
890  -nx, -ny, distance)
891  end if
892  !
893  end do
894  !
895  ! -- Return
896  return
897  end subroutine gwf_gwf_set_flow_to_npf
898 
899  !> @ brief Budget
900  !!
901  !! Accumulate budget terms
902  !<
903  subroutine gwf_gwf_bd(this, icnvg, isuppress_output, isolnid)
904  ! -- modules
906  use budgetmodule, only: rate_accumulator
907  ! -- dummy
908  class(gwfexchangetype) :: this !< GwfExchangeType
909  integer(I4B), intent(inout) :: icnvg
910  integer(I4B), intent(in) :: isuppress_output
911  integer(I4B), intent(in) :: isolnid
912  ! -- local
913  character(len=LENBUDTXT), dimension(1) :: budtxt
914  real(DP), dimension(2, 1) :: budterm
915  real(DP) :: ratin, ratout
916  !
917  ! -- initialize
918  budtxt(1) = ' FLOW-JA-FACE'
919  !
920  ! -- Calculate ratin/ratout and pass to model budgets
921  call rate_accumulator(this%simvals, ratin, ratout)
922  !
923  ! -- Add the budget terms to model 1
924  if (associated(this%gwfmodel1)) then
925  budterm(1, 1) = ratin
926  budterm(2, 1) = ratout
927  call this%gwfmodel1%model_bdentry(budterm, budtxt, this%name)
928  end if
929  !
930  ! -- Add the budget terms to model 2
931  if (associated(this%gwfmodel2)) then
932  budterm(1, 1) = ratout
933  budterm(2, 1) = ratin
934  call this%gwfmodel2%model_bdentry(budterm, budtxt, this%name)
935  end if
936  !
937  ! -- Add any flows from one model into a constant head in another model
938  ! as a separate budget term called FLOW-JA-FACE-CHD
939  call this%gwf_gwf_chd_bd()
940  !
941  ! -- Call mvr bd routine
942  if (this%inmvr > 0) call this%mvr%mvr_bd()
943  !
944  ! -- Return
945  return
946  end subroutine gwf_gwf_bd
947 
948  !> @ brief gwf-gwf-chd-bd
949  !!
950  !! Account for flow from an external model into a chd cell
951  !<
952  subroutine gwf_gwf_chd_bd(this)
953  ! -- modules
955  use budgetmodule, only: rate_accumulator
956  ! -- dummy
957  class(gwfexchangetype) :: this !< GwfExchangeType
958  ! -- local
959  character(len=LENBUDTXT), dimension(1) :: budtxt
960  integer(I4B) :: n
961  integer(I4B) :: i
962  real(DP), dimension(2, 1) :: budterm
963  real(DP) :: ratin, ratout
964  real(DP) :: q
965  !
966  ! -- initialize
967  budtxt(1) = 'FLOW-JA-FACE-CHD'
968  !
969  ! -- Add the constant-head budget terms for flow from model 2 into model 1
970  if (associated(this%gwfmodel1)) then
971  ratin = dzero
972  ratout = dzero
973  do i = 1, this%nexg
974  n = this%nodem1(i)
975  if (this%gwfmodel1%ibound(n) < 0) then
976  q = this%simvals(i)
977  if (q > dzero) then
978  ratout = ratout + q
979  else
980  ratin = ratin - q
981  end if
982  end if
983  end do
984  budterm(1, 1) = ratin
985  budterm(2, 1) = ratout
986  call this%gwfmodel1%model_bdentry(budterm, budtxt, this%name)
987  end if
988  !
989  ! -- Add the constant-head budget terms for flow from model 1 into model 2
990  if (associated(this%gwfmodel2)) then
991  ratin = dzero
992  ratout = dzero
993  do i = 1, this%nexg
994  n = this%nodem2(i)
995  if (this%gwfmodel2%ibound(n) < 0) then
996  ! -- flip flow sign as flow is relative to model 1
997  q = -this%simvals(i)
998  if (q > dzero) then
999  ratout = ratout + q
1000  else
1001  ratin = ratin - q
1002  end if
1003  end if
1004  end do
1005  budterm(1, 1) = ratin
1006  budterm(2, 1) = ratout
1007  call this%gwfmodel2%model_bdentry(budterm, budtxt, this%name)
1008  end if
1009  !
1010  ! -- Return
1011  return
1012  end subroutine gwf_gwf_chd_bd
1013 
1014  !> @ brief Budget save
1015  !!
1016  !! Output individual flows to listing file and binary budget files
1017  !<
1018  subroutine gwf_gwf_bdsav(this)
1019  ! -- dummy
1020  class(gwfexchangetype) :: this !< GwfExchangeType
1021  ! -- local
1022  integer(I4B) :: icbcfl, ibudfl
1023  !
1024  ! -- budget for model1
1025  if (associated(this%gwfmodel1)) then
1026  call this%gwf_gwf_bdsav_model(this%gwfmodel1)
1027  end if
1028  !
1029  ! -- budget for model2
1030  if (associated(this%gwfmodel2)) then
1031  call this%gwf_gwf_bdsav_model(this%gwfmodel2)
1032  end if
1033  !
1034  ! -- Set icbcfl, ibudfl to zero so that flows will be printed and
1035  ! saved, if the options were set in the MVR package
1036  icbcfl = 1
1037  ibudfl = 1
1038  !
1039  ! -- Call mvr bd routine
1040  if (this%inmvr > 0) call this%mvr%mvr_bdsav(icbcfl, ibudfl, 0)
1041  !
1042  ! -- Calculate and write simulated values for observations
1043  if (this%inobs /= 0) then
1044  call this%gwf_gwf_save_simvals()
1045  end if
1046  !
1047  ! -- Return
1048  return
1049  end subroutine gwf_gwf_bdsav
1050 
1051  subroutine gwf_gwf_bdsav_model(this, model)
1052  ! -- modules
1054  use tdismodule, only: kstp, kper
1055  ! -- dummy
1056  class(gwfexchangetype) :: this !< this exchange
1057  class(gwfmodeltype), pointer :: model !< the model to save budget for
1058  ! -- local
1059  character(len=LENPACKAGENAME + 4) :: packname
1060  character(len=LENBUDTXT), dimension(1) :: budtxt
1061  type(tabletype), pointer :: output_tab
1062  class(virtualmodeltype), pointer :: nbr_model
1063  character(len=20) :: nodestr
1064  character(len=LENBOUNDNAME) :: bname
1065  integer(I4B) :: ntabrows
1066  integer(I4B) :: nodeu
1067  integer(I4B) :: i, n1, n2, n1u, n2u
1068  integer(I4B) :: ibinun
1069  real(DP) :: ratin, ratout, rrate
1070  logical(LGP) :: is_for_model1
1071  !
1072  budtxt(1) = ' FLOW-JA-FACE'
1073  packname = 'EXG '//this%name
1074  packname = adjustr(packname)
1075  if (associated(model, this%gwfmodel1)) then
1076  output_tab => this%outputtab1
1077  nbr_model => this%v_model2
1078  is_for_model1 = .true.
1079  else
1080  output_tab => this%outputtab2
1081  nbr_model => this%v_model1
1082  is_for_model1 = .false.
1083  end if
1084  !
1085  ! -- update output tables
1086  if (this%iprflow /= 0) then
1087  !
1088  ! -- update titles
1089  if (model%oc%oc_save('BUDGET')) then
1090  call output_tab%set_title(packname)
1091  end if
1092  !
1093  ! -- set table kstp and kper
1094  call output_tab%set_kstpkper(kstp, kper)
1095  !
1096  ! -- update maxbound of tables
1097  ntabrows = 0
1098  do i = 1, this%nexg
1099  n1 = this%nodem1(i)
1100  n2 = this%nodem2(i)
1101  !
1102  ! -- If both cells are active then calculate flow rate
1103  if (this%v_model1%ibound%get(n1) /= 0 .and. &
1104  this%v_model2%ibound%get(n2) /= 0) then
1105  ntabrows = ntabrows + 1
1106  end if
1107  end do
1108  if (ntabrows > 0) then
1109  call output_tab%set_maxbound(ntabrows)
1110  end if
1111  end if
1112  !
1113  ! -- Print and write budget terms
1114  !
1115  ! -- Set binary unit numbers for saving flows
1116  if (this%ipakcb /= 0) then
1117  ibinun = model%oc%oc_save_unit('BUDGET')
1118  else
1119  ibinun = 0
1120  end if
1121  !
1122  ! -- If save budget flag is zero for this stress period, then
1123  ! shut off saving
1124  if (.not. model%oc%oc_save('BUDGET')) ibinun = 0
1125  !
1126  ! -- If cell-by-cell flows will be saved as a list, write header.
1127  if (ibinun /= 0) then
1128  call model%dis%record_srcdst_list_header(budtxt(1), &
1129  model%name, &
1130  this%name, &
1131  nbr_model%name, &
1132  this%name, &
1133  this%naux, this%auxname, &
1134  ibinun, this%nexg, &
1135  model%iout)
1136  end if
1137  !
1138  ! Initialize accumulators
1139  ratin = dzero
1140  ratout = dzero
1141  !
1142  ! -- Loop through all exchanges
1143  do i = 1, this%nexg
1144  !
1145  ! -- Assign boundary name
1146  if (this%inamedbound > 0) then
1147  bname = this%boundname(i)
1148  else
1149  bname = ''
1150  end if
1151  !
1152  ! -- Calculate the flow rate between n1 and n2
1153  rrate = dzero
1154  n1 = this%nodem1(i)
1155  n2 = this%nodem2(i)
1156  !
1157  ! -- If both cells are active then calculate flow rate
1158  if (this%v_model1%ibound%get(n1) /= 0 .and. &
1159  this%v_model2%ibound%get(n2) /= 0) then
1160  rrate = this%simvals(i)
1161  !
1162  ! -- Print the individual rates to model list files if requested
1163  if (this%iprflow /= 0) then
1164  if (model%oc%oc_save('BUDGET')) then
1165  !
1166  ! -- set nodestr and write outputtab table
1167  if (is_for_model1) then
1168  nodeu = model%dis%get_nodeuser(n1)
1169  call model%dis%nodeu_to_string(nodeu, nodestr)
1170  call output_tab%print_list_entry(i, trim(adjustl(nodestr)), &
1171  rrate, bname)
1172  else
1173  nodeu = model%dis%get_nodeuser(n2)
1174  call model%dis%nodeu_to_string(nodeu, nodestr)
1175  call output_tab%print_list_entry(i, trim(adjustl(nodestr)), &
1176  -rrate, bname)
1177  end if
1178  end if
1179  end if
1180  if (rrate < dzero) then
1181  ratout = ratout - rrate
1182  else
1183  ratin = ratin + rrate
1184  end if
1185  end if
1186  !
1187  ! -- If saving cell-by-cell flows in list, write flow
1188  n1u = this%v_model1%dis_get_nodeuser(n1)
1189  n2u = this%v_model2%dis_get_nodeuser(n2)
1190  if (ibinun /= 0) then
1191  if (is_for_model1) then
1192  call model%dis%record_mf6_list_entry(ibinun, n1u, n2u, rrate, &
1193  this%naux, this%auxvar(:, i), &
1194  .false., .false.)
1195  else
1196  call model%dis%record_mf6_list_entry(ibinun, n2u, n1u, -rrate, &
1197  this%naux, this%auxvar(:, i), &
1198  .false., .false.)
1199  end if
1200  end if
1201  !
1202  end do
1203  !
1204  ! -- Return
1205  return
1206  end subroutine gwf_gwf_bdsav_model
1207 
1208  !> @ brief Output
1209  !!
1210  !! Write output
1211  !<
1212  subroutine gwf_gwf_ot(this)
1213  ! -- modules
1214  use simvariablesmodule, only: iout
1215  use constantsmodule, only: dzero
1216  ! -- dummy
1217  class(gwfexchangetype) :: this !< GwfExchangeType
1218  ! -- local
1219  integer(I4B) :: iexg, n1, n2
1220  integer(I4B) :: ibudfl
1221  real(DP) :: flow, deltaqgnc
1222  character(len=LINELENGTH) :: node1str, node2str
1223  ! -- format
1224  character(len=*), parameter :: fmtheader = &
1225  "(/1x, 'SUMMARY OF EXCHANGE RATES FOR EXCHANGE ', a, ' WITH ID ', i0, /, &
1226  &2a16, 5a16, /, 112('-'))"
1227  character(len=*), parameter :: fmtheader2 = &
1228  "(/1x, 'SUMMARY OF EXCHANGE RATES FOR EXCHANGE ', a, ' WITH ID ', i0, /, &
1229  &2a16, 4a16, /, 96('-'))"
1230  character(len=*), parameter :: fmtdata = &
1231  "(2a16, 5(1pg16.6))"
1232  !
1233  ! -- Call bdsave
1234  call this%gwf_gwf_bdsav()
1235  !
1236  ! -- Initialize
1237  deltaqgnc = dzero
1238  !
1239  ! -- Write a table of exchanges
1240  if (this%iprflow /= 0) then
1241  if (this%ingnc > 0) then
1242  write (iout, fmtheader) trim(adjustl(this%name)), this%id, 'NODEM1', &
1243  'NODEM2', 'COND', 'X_M1', 'X_M2', 'DELTAQGNC', &
1244  'FLOW'
1245  else
1246  write (iout, fmtheader2) trim(adjustl(this%name)), this%id, 'NODEM1', &
1247  'NODEM2', 'COND', 'X_M1', 'X_M2', 'FLOW'
1248  end if
1249  do iexg = 1, this%nexg
1250  n1 = this%nodem1(iexg)
1251  n2 = this%nodem2(iexg)
1252  flow = this%simvals(iexg)
1253  call this%v_model1%dis_noder_to_string(n1, node1str)
1254  call this%v_model2%dis_noder_to_string(n2, node2str)
1255 
1256  if (this%ingnc > 0) then
1257  deltaqgnc = this%gnc%deltaqgnc(iexg)
1258  write (iout, fmtdata) trim(adjustl(node1str)), &
1259  trim(adjustl(node2str)), &
1260  this%cond(iexg), this%v_model1%x%get(n1), &
1261  this%v_model2%x%get(n2), deltaqgnc, flow
1262  else
1263  write (iout, fmtdata) trim(adjustl(node1str)), &
1264  trim(adjustl(node2str)), &
1265  this%cond(iexg), this%v_model1%x%get(n1), &
1266  this%v_model2%x%get(n2), flow
1267  end if
1268  end do
1269  end if
1270  !
1271  ! -- Mover budget output
1272  ibudfl = 1
1273  if (this%inmvr > 0) call this%mvr%mvr_ot_bdsummary(ibudfl)
1274  !
1275  ! -- OBS output
1276  call this%obs%obs_ot()
1277  !
1278  ! -- Return
1279  return
1280  end subroutine gwf_gwf_ot
1281 
1282  !> @ brief Source options
1283  !!
1284  !! Source the options block
1285  !<
1286  subroutine source_options(this, iout)
1287  ! -- modules
1288  use constantsmodule, only: lenvarname, dem6
1289  use inputoutputmodule, only: getunit, openfile
1293  use sourcecommonmodule, only: filein_fname
1294  ! -- dummy
1295  class(gwfexchangetype) :: this !< GwfExchangeType
1296  integer(I4B), intent(in) :: iout
1297  ! -- local
1298  type(exggwfgwfparamfoundtype) :: found
1299  character(len=LENVARNAME), dimension(3) :: cellavg_method = &
1300  &[character(len=LENVARNAME) :: 'HARMONIC', 'LOGARITHMIC', 'AMT-LMK']
1301  character(len=linelength) :: gnc_fname, mvr_fname
1302  !
1303  ! -- update defaults with idm sourced values
1304  call mem_set_value(this%icellavg, 'CELL_AVERAGING', this%input_mempath, &
1305  cellavg_method, found%cell_averaging)
1306  call mem_set_value(this%inewton, 'NEWTON', this%input_mempath, found%newton)
1307  call mem_set_value(this%ixt3d, 'XT3D', this%input_mempath, found%xt3d)
1308  call mem_set_value(this%ivarcv, 'VARIABLECV', this%input_mempath, &
1309  found%variablecv)
1310  call mem_set_value(this%idewatcv, 'DEWATERED', this%input_mempath, &
1311  found%dewatered)
1312  !
1313  write (iout, '(1x,a)') 'PROCESSING GWF-GWF EXCHANGE OPTIONS'
1314  !
1315  ! -- source base class options
1316  call this%DisConnExchangeType%source_options(iout)
1317  !
1318  if (found%cell_averaging) then
1319  ! -- count from 0
1320  this%icellavg = this%icellavg - 1
1321  write (iout, '(4x,a,a)') &
1322  'CELL AVERAGING METHOD HAS BEEN SET TO: ', &
1323  trim(cellavg_method(this%icellavg + 1))
1324  end if
1325  !
1326  if (found%newton) then
1327  write (iout, '(4x,a)') &
1328  'NEWTON-RAPHSON method used for unconfined cells'
1329  end if
1330  !
1331  if (found%xt3d) then
1332  write (iout, '(4x,a)') 'XT3D WILL BE APPLIED ON THE INTERFACE'
1333  end if
1334  !
1335  if (found%variablecv) then
1336  write (iout, '(4x,a)') &
1337  'VERTICAL CONDUCTANCE VARIES WITH WATER TABLE.'
1338  end if
1339  !
1340  if (found%dewatered) then
1341  write (iout, '(4x,a)') &
1342  'VERTICAL CONDUCTANCE ACCOUNTS FOR DEWATERED PORTION OF '// &
1343  'AN UNDERLYING CELL.'
1344  end if
1345  !
1346  ! -- enforce 0 or 1 GNC6_FILENAME entries in option block
1347  if (filein_fname(gnc_fname, 'GNC6_FILENAME', this%input_mempath, &
1348  this%filename)) then
1349  this%ingnc = getunit()
1350  call openfile(this%ingnc, iout, gnc_fname, 'GNC')
1351  write (iout, '(4x,a)') &
1352  'GHOST NODES WILL BE READ FROM ', trim(gnc_fname)
1353  end if
1354  !
1355  ! -- enforce 0 or 1 MVR6_FILENAME entries in option block
1356  if (filein_fname(mvr_fname, 'MVR6_FILENAME', this%input_mempath, &
1357  this%filename)) then
1358  this%inmvr = getunit()
1359  call openfile(this%inmvr, iout, mvr_fname, 'MVR')
1360  write (iout, '(4x,a)') &
1361  'WATER MOVER INFORMATION WILL BE READ FROM ', trim(mvr_fname)
1362  end if
1363  !
1364  ! -- enforce 0 or 1 OBS6_FILENAME entries in option block
1365  if (.not. this%is_datacopy) then
1366  if (filein_fname(this%obs%inputFilename, 'OBS6_FILENAME', &
1367  this%input_mempath, this%filename)) then
1368  this%obs%active = .true.
1369  this%obs%inUnitObs = getunit()
1370  call openfile(this%obs%inUnitObs, iout, this%obs%inputFilename, 'OBS')
1371  end if
1372  end if
1373  !
1374  write (iout, '(1x,a)') 'END OF GWF-GWF EXCHANGE OPTIONS'
1375  !
1376  ! -- set omega value used for saturation calculations
1377  if (this%inewton > 0) then
1378  this%satomega = dem6
1379  end if
1380  !
1381  ! -- Return
1382  return
1383  end subroutine source_options
1384 
1385  !> @ brief Read ghost nodes
1386  !!
1387  !! Read and process ghost nodes
1388  !<
1389  subroutine read_gnc(this)
1390  ! -- modules
1391  use constantsmodule, only: linelength
1392  ! -- dummy
1393  class(gwfexchangetype) :: this !< GwfExchangeType
1394  ! -- local
1395  integer(I4B) :: i, nm1, nm2, nmgnc1, nmgnc2
1396  character(len=*), parameter :: fmterr = &
1397  "('EXCHANGE NODES ', i0, ' AND ', i0,"// &
1398  "' NOT CONSISTENT WITH GNC NODES ', "// &
1399  "i0, ' AND ', i0)"
1400  !
1401  ! -- If exchange has ghost nodes, then initialize ghost node object
1402  ! This will read the ghost node blocks from the gnc input file.
1403  call this%gnc%gnc_df(this%gwfmodel1, m2=this%gwfmodel2)
1404  !
1405  ! -- Verify gnc is implicit if exchange has Newton Terms
1406  if (.not. this%gnc%implicit .and. this%inewton /= 0) then
1407  call store_error('GNC is explicit, but GWF exchange has active newton.')
1408  call store_error('Add implicit option to GNC or remove NEWTON from '// &
1409  'GWF exchange.')
1410  call store_error_unit(this%ingnc)
1411  end if
1412  !
1413  ! -- Perform checks to ensure GNCs match with GWF-GWF nodes
1414  if (this%nexg /= this%gnc%nexg) then
1415  call store_error('Number of exchanges does not match number of GNCs')
1416  call store_error_unit(this%ingnc)
1417  end if
1418  !
1419  ! -- Go through each entry and confirm
1420  do i = 1, this%nexg
1421  if (this%nodem1(i) /= this%gnc%nodem1(i) .or. &
1422  this%nodem2(i) /= this%gnc%nodem2(i)) then
1423  nm1 = this%gwfmodel1%dis%get_nodeuser(this%nodem1(i))
1424  nm2 = this%gwfmodel2%dis%get_nodeuser(this%nodem2(i))
1425  nmgnc1 = this%gwfmodel1%dis%get_nodeuser(this%gnc%nodem1(i))
1426  nmgnc2 = this%gwfmodel2%dis%get_nodeuser(this%gnc%nodem2(i))
1427  write (errmsg, fmterr) nm1, nm2, nmgnc1, nmgnc2
1428  call store_error(errmsg)
1429  end if
1430  end do
1431  if (count_errors() > 0) then
1432  call store_error_unit(this%ingnc)
1433  end if
1434  !
1435  ! -- close the file
1436  close (this%ingnc)
1437  !
1438  ! -- Return
1439  return
1440  end subroutine read_gnc
1441 
1442  !> @ brief Read mover
1443  !!
1444  !! Read and process movers
1445  !<
1446  subroutine read_mvr(this, iout)
1447  ! -- modules
1448  use gwfexgmovermodule, only: exg_mvr_cr
1449  ! -- dummy
1450  class(gwfexchangetype) :: this !< GwfExchangeType
1451  integer(I4B), intent(in) :: iout
1452  class(disbasetype), pointer :: dis
1453  ! -- local
1454  !
1455  ! -- Create and initialize the mover object Here, dis is set to the one
1456  ! for gwfmodel1 so that a call to save flows has an associated dis
1457  ! object. Because the conversion flags for the mover are both false,
1458  ! the dis object does not convert from reduced to user node numbers.
1459  ! So in this case, the dis object is just writing unconverted package
1460  ! numbers to the binary budget file.
1461  dis => null()
1462  if (this%v_model1%is_local) then
1463  dis => this%gwfmodel1%dis
1464  else if (this%v_model2%is_local) then
1465  dis => this%gwfmodel2%dis
1466  end if
1467  call exg_mvr_cr(this%mvr, this%name, this%inmvr, iout, dis)
1468  this%mvr%model1 => this%v_model1
1469  this%mvr%model2 => this%v_model2
1470  !
1471  ! -- Return
1472  return
1473  end subroutine read_mvr
1474 
1475  !> @ brief Rewet
1476  !!
1477  !! Check if rewetting should propagate from one model to another
1478  !<
1479  subroutine rewet(this, kiter)
1480  ! -- modules
1481  use tdismodule, only: kper, kstp
1482  ! -- dummy
1483  class(gwfexchangetype) :: this !< GwfExchangeType
1484  integer(I4B), intent(in) :: kiter
1485  ! -- local
1486  integer(I4B) :: iexg
1487  integer(I4B) :: n, m
1488  integer(I4B) :: ibdn, ibdm
1489  integer(I4B) :: ihc
1490  real(DP) :: hn, hm
1491  integer(I4B) :: irewet
1492  character(len=30) :: nodestrn, nodestrm
1493  character(len=*), parameter :: fmtrwt = &
1494  "(1x, 'CELL ',A,' REWET FROM GWF MODEL ',A,' CELL ',A, &
1495  &' FOR ITER. ',I0, ' STEP ',I0, ' PERIOD ', I0)"
1496  !
1497  ! -- Use model 1 to rewet model 2 and vice versa
1498  do iexg = 1, this%nexg
1499  n = this%nodem1(iexg)
1500  m = this%nodem2(iexg)
1501  hn = this%gwfmodel1%x(n)
1502  hm = this%gwfmodel2%x(m)
1503  ibdn = this%gwfmodel1%ibound(n)
1504  ibdm = this%gwfmodel2%ibound(m)
1505  ihc = this%ihc(iexg)
1506  call this%gwfmodel1%npf%rewet_check(kiter, n, hm, ibdm, ihc, &
1507  this%gwfmodel1%x, irewet)
1508  if (irewet == 1) then
1509  call this%gwfmodel1%dis%noder_to_string(n, nodestrn)
1510  call this%gwfmodel2%dis%noder_to_string(m, nodestrm)
1511  write (this%gwfmodel1%iout, fmtrwt) trim(nodestrn), &
1512  trim(this%gwfmodel2%name), trim(nodestrm), kiter, kstp, kper
1513  end if
1514  call this%gwfmodel2%npf%rewet_check(kiter, m, hn, ibdn, ihc, &
1515  this%gwfmodel2%x, irewet)
1516  if (irewet == 1) then
1517  call this%gwfmodel1%dis%noder_to_string(n, nodestrm)
1518  call this%gwfmodel2%dis%noder_to_string(m, nodestrn)
1519  write (this%gwfmodel2%iout, fmtrwt) trim(nodestrn), &
1520  trim(this%gwfmodel1%name), trim(nodestrm), kiter, kstp, kper
1521  end if
1522  !
1523  end do
1524  !
1525  ! -- Return
1526  return
1527  end subroutine rewet
1528 
1529  subroutine calc_cond_sat(this)
1530  ! -- modules
1533  ! -- dummy
1534  class(gwfexchangetype) :: this !< GwfExchangeType
1535  ! -- local
1536  integer(I4B) :: iexg
1537  integer(I4B) :: n, m, ihc
1538  real(DP) :: topn, topm
1539  real(DP) :: botn, botm
1540  real(DP) :: satn, satm
1541  real(DP) :: thickn, thickm
1542  real(DP) :: angle, hyn, hym
1543  real(DP) :: csat
1544  real(DP) :: fawidth
1545  real(DP), dimension(3) :: vg
1546  !
1547  do iexg = 1, this%nexg
1548  !
1549  ihc = this%ihc(iexg)
1550  n = this%nodem1(iexg)
1551  m = this%nodem2(iexg)
1552  topn = this%gwfmodel1%dis%top(n)
1553  topm = this%gwfmodel2%dis%top(m)
1554  botn = this%gwfmodel1%dis%bot(n)
1555  botm = this%gwfmodel2%dis%bot(m)
1556  satn = this%gwfmodel1%npf%sat(n)
1557  satm = this%gwfmodel2%npf%sat(m)
1558  thickn = (topn - botn) * satn
1559  thickm = (topm - botm) * satm
1560  !
1561  ! -- Calculate conductance depending on connection orientation
1562  if (ihc == 0) then
1563  !
1564  ! -- Vertical conductance for fully saturated conditions
1565  vg(1) = dzero
1566  vg(2) = dzero
1567  vg(3) = done
1568  hyn = this%gwfmodel1%npf%hy_eff(n, 0, ihc, vg=vg)
1569  hym = this%gwfmodel2%npf%hy_eff(m, 0, ihc, vg=vg)
1570  csat = vcond(1, 1, 1, 1, 0, 1, 1, done, &
1571  botn, botm, &
1572  hyn, hym, &
1573  satn, satm, &
1574  topn, topm, &
1575  botn, botm, &
1576  this%hwva(iexg))
1577  else
1578  !
1579  ! -- Calculate horizontal conductance
1580  hyn = this%gwfmodel1%npf%k11(n)
1581  hym = this%gwfmodel2%npf%k11(m)
1582  !
1583  ! -- Check for anisotropy in models, and recalculate hyn and hym
1584  if (this%ianglex > 0) then
1585  angle = this%auxvar(this%ianglex, iexg) * dpio180
1586  vg(1) = abs(cos(angle))
1587  vg(2) = abs(sin(angle))
1588  vg(3) = dzero
1589  !
1590  ! -- anisotropy in model 1
1591  if (this%gwfmodel1%npf%ik22 /= 0) then
1592  hyn = this%gwfmodel1%npf%hy_eff(n, 0, ihc, vg=vg)
1593  end if
1594  !
1595  ! -- anisotropy in model 2
1596  if (this%gwfmodel2%npf%ik22 /= 0) then
1597  hym = this%gwfmodel2%npf%hy_eff(m, 0, ihc, vg=vg)
1598  end if
1599  end if
1600  !
1601  fawidth = this%hwva(iexg)
1602  csat = hcond(1, 1, 1, 1, 0, ihc, &
1603  this%icellavg, done, &
1604  topn, topm, satn, satm, hyn, hym, &
1605  topn, topm, &
1606  botn, botm, &
1607  this%cl1(iexg), this%cl2(iexg), &
1608  fawidth)
1609  end if
1610  !
1611  ! -- store csat in condsat
1612  this%condsat(iexg) = csat
1613  end do
1614  !
1615  ! -- Return
1616  return
1617  end subroutine calc_cond_sat
1618 
1619  !> @ brief Calculate the conductance
1620  !!
1621  !! Calculate the conductance based on state
1622  !<
1623  subroutine condcalc(this)
1624  ! -- modules
1625  use constantsmodule, only: dhalf, dzero, done
1627  ! -- dummy
1628  class(gwfexchangetype) :: this !< GwfExchangeType
1629  ! -- local
1630  integer(I4B) :: iexg
1631  integer(I4B) :: n, m, ihc
1632  integer(I4B) :: ibdn, ibdm
1633  integer(I4B) :: ictn, ictm
1634  real(DP) :: topn, topm
1635  real(DP) :: botn, botm
1636  real(DP) :: satn, satm
1637  real(DP) :: hyn, hym
1638  real(DP) :: angle
1639  real(DP) :: hn, hm
1640  real(DP) :: cond
1641  real(DP) :: fawidth
1642  real(DP), dimension(3) :: vg
1643  !
1644  ! -- Calculate conductance and put into amat
1645  do iexg = 1, this%nexg
1646  ihc = this%ihc(iexg)
1647  n = this%nodem1(iexg)
1648  m = this%nodem2(iexg)
1649  ibdn = this%gwfmodel1%ibound(n)
1650  ibdm = this%gwfmodel2%ibound(m)
1651  ictn = this%gwfmodel1%npf%icelltype(n)
1652  ictm = this%gwfmodel2%npf%icelltype(m)
1653  topn = this%gwfmodel1%dis%top(n)
1654  topm = this%gwfmodel2%dis%top(m)
1655  botn = this%gwfmodel1%dis%bot(n)
1656  botm = this%gwfmodel2%dis%bot(m)
1657  satn = this%gwfmodel1%npf%sat(n)
1658  satm = this%gwfmodel2%npf%sat(m)
1659  hn = this%gwfmodel1%x(n)
1660  hm = this%gwfmodel2%x(m)
1661  !
1662  ! -- Calculate conductance depending on connection orientation
1663  if (ihc == 0) then
1664  !
1665  ! -- Vertical connection
1666  vg(1) = dzero
1667  vg(2) = dzero
1668  vg(3) = done
1669  hyn = this%gwfmodel1%npf%hy_eff(n, 0, ihc, vg=vg)
1670  hym = this%gwfmodel2%npf%hy_eff(m, 0, ihc, vg=vg)
1671  cond = vcond(ibdn, ibdm, ictn, ictm, this%inewton, this%ivarcv, &
1672  this%idewatcv, this%condsat(iexg), hn, hm, hyn, hym, &
1673  satn, satm, topn, topm, botn, botm, this%hwva(iexg))
1674  else
1675  !
1676  ! -- Horizontal Connection
1677  hyn = this%gwfmodel1%npf%k11(n)
1678  hym = this%gwfmodel2%npf%k11(m)
1679  !
1680  ! -- Check for anisotropy in models, and recalculate hyn and hym
1681  if (this%ianglex > 0) then
1682  angle = this%auxvar(this%ianglex, iexg)
1683  vg(1) = abs(cos(angle))
1684  vg(2) = abs(sin(angle))
1685  vg(3) = dzero
1686  !
1687  ! -- anisotropy in model 1
1688  if (this%gwfmodel1%npf%ik22 /= 0) then
1689  hyn = this%gwfmodel1%npf%hy_eff(n, 0, ihc, vg=vg)
1690  end if
1691  !
1692  ! -- anisotropy in model 2
1693  if (this%gwfmodel2%npf%ik22 /= 0) then
1694  hym = this%gwfmodel2%npf%hy_eff(m, 0, ihc, vg=vg)
1695  end if
1696  end if
1697  !
1698  fawidth = this%hwva(iexg)
1699  cond = hcond(ibdn, ibdm, ictn, ictm, this%inewton, &
1700  this%ihc(iexg), this%icellavg, this%condsat(iexg), &
1701  hn, hm, satn, satm, hyn, hym, topn, topm, botn, botm, &
1702  this%cl1(iexg), this%cl2(iexg), fawidth)
1703  end if
1704  !
1705  this%cond(iexg) = cond
1706  !
1707  end do
1708  !
1709  ! -- Return
1710  return
1711  end subroutine condcalc
1712 
1713  !> @ brief Allocate scalars
1714  !!
1715  !! Allocate scalar variables
1716  !<
1717  subroutine allocate_scalars(this)
1718  ! -- modules
1720  use constantsmodule, only: dzero
1721  ! -- dummy
1722  class(gwfexchangetype) :: this !< GwfExchangeType
1723  !
1724  call this%DisConnExchangeType%allocate_scalars()
1725  !
1726  call mem_allocate(this%icellavg, 'ICELLAVG', this%memoryPath)
1727  call mem_allocate(this%ivarcv, 'IVARCV', this%memoryPath)
1728  call mem_allocate(this%idewatcv, 'IDEWATCV', this%memoryPath)
1729  call mem_allocate(this%inewton, 'INEWTON', this%memoryPath)
1730  call mem_allocate(this%ingnc, 'INGNC', this%memoryPath)
1731  call mem_allocate(this%inmvr, 'INMVR', this%memoryPath)
1732  call mem_allocate(this%inobs, 'INOBS', this%memoryPath)
1733  call mem_allocate(this%satomega, 'SATOMEGA', this%memoryPath)
1734  this%icellavg = 0
1735  this%ivarcv = 0
1736  this%idewatcv = 0
1737  this%inewton = 0
1738  this%ingnc = 0
1739  this%inmvr = 0
1740  this%inobs = 0
1741  this%satomega = dzero
1742  !
1743  ! -- Return
1744  return
1745  end subroutine allocate_scalars
1746 
1747  !> @ brief Deallocate
1748  !!
1749  !! Deallocate memory associated with this object
1750  !<
1751  subroutine gwf_gwf_da(this)
1752  ! -- modules
1754  ! -- dummy
1755  class(gwfexchangetype) :: this !< GwfExchangeType
1756  !
1757  ! -- objects
1758  if (this%ingnc > 0) then
1759  call this%gnc%gnc_da()
1760  deallocate (this%gnc)
1761  end if
1762  if (this%inmvr > 0) then
1763  call this%mvr%mvr_da()
1764  deallocate (this%mvr)
1765  end if
1766  call this%obs%obs_da()
1767  deallocate (this%obs)
1768  !
1769  ! -- arrays
1770  call mem_deallocate(this%cond)
1771  call mem_deallocate(this%condsat)
1772  call mem_deallocate(this%idxglo)
1773  call mem_deallocate(this%idxsymglo)
1774  call mem_deallocate(this%simvals)
1775  !
1776  ! -- output table objects
1777  if (associated(this%outputtab1)) then
1778  call this%outputtab1%table_da()
1779  deallocate (this%outputtab1)
1780  nullify (this%outputtab1)
1781  end if
1782  if (associated(this%outputtab2)) then
1783  call this%outputtab2%table_da()
1784  deallocate (this%outputtab2)
1785  nullify (this%outputtab2)
1786  end if
1787  !
1788  ! -- scalars
1789  deallocate (this%filename)
1790  !
1791  call mem_deallocate(this%icellavg)
1792  call mem_deallocate(this%ivarcv)
1793  call mem_deallocate(this%idewatcv)
1794  call mem_deallocate(this%inewton)
1795  call mem_deallocate(this%ingnc)
1796  call mem_deallocate(this%inmvr)
1797  call mem_deallocate(this%inobs)
1798  call mem_deallocate(this%satomega)
1799  !
1800  ! -- deallocate base
1801  call this%DisConnExchangeType%disconnex_da()
1802  !
1803  ! -- Return
1804  return
1805  end subroutine gwf_gwf_da
1806 
1807  !> @ brief Allocate arrays
1808  !!
1809  !! Allocate arrays
1810  !<
1811  subroutine allocate_arrays(this)
1812  ! -- modules
1814  ! -- dummy
1815  class(gwfexchangetype) :: this !< GwfExchangeType
1816  ! -- local
1817  character(len=LINELENGTH) :: text
1818  integer(I4B) :: ntabcol, i
1819  !
1820  call this%DisConnExchangeType%allocate_arrays()
1821  !
1822  call mem_allocate(this%cond, this%nexg, 'COND', this%memoryPath)
1823  call mem_allocate(this%idxglo, this%nexg, 'IDXGLO', this%memoryPath)
1824  call mem_allocate(this%idxsymglo, this%nexg, 'IDXSYMGLO', this%memoryPath) !
1825  call mem_allocate(this%condsat, this%nexg, 'CONDSAT', this%memoryPath)
1826  call mem_allocate(this%simvals, this%nexg, 'SIMVALS', this%memoryPath)
1827  !
1828  ! -- Initialize
1829  do i = 1, this%nexg
1830  this%cond(i) = dnodata
1831  end do
1832  !
1833  ! -- allocate and initialize the output table
1834  if (this%iprflow /= 0) then
1835  !
1836  ! -- dimension table
1837  ntabcol = 3
1838  if (this%inamedbound > 0) then
1839  ntabcol = ntabcol + 1
1840  end if
1841  !
1842  ! -- initialize the output table objects
1843  ! outouttab1
1844  if (this%v_model1%is_local) then
1845  call table_cr(this%outputtab1, this%name, ' ')
1846  call this%outputtab1%table_df(this%nexg, ntabcol, this%gwfmodel1%iout, &
1847  transient=.true.)
1848  text = 'NUMBER'
1849  call this%outputtab1%initialize_column(text, 10, alignment=tabcenter)
1850  text = 'CELLID'
1851  call this%outputtab1%initialize_column(text, 20, alignment=tableft)
1852  text = 'RATE'
1853  call this%outputtab1%initialize_column(text, 15, alignment=tabcenter)
1854  if (this%inamedbound > 0) then
1855  text = 'NAME'
1856  call this%outputtab1%initialize_column(text, 20, alignment=tableft)
1857  end if
1858  end if
1859  ! outouttab2
1860  if (this%v_model2%is_local) then
1861  call table_cr(this%outputtab2, this%name, ' ')
1862  call this%outputtab2%table_df(this%nexg, ntabcol, this%gwfmodel2%iout, &
1863  transient=.true.)
1864  text = 'NUMBER'
1865  call this%outputtab2%initialize_column(text, 10, alignment=tabcenter)
1866  text = 'CELLID'
1867  call this%outputtab2%initialize_column(text, 20, alignment=tableft)
1868  text = 'RATE'
1869  call this%outputtab2%initialize_column(text, 15, alignment=tabcenter)
1870  if (this%inamedbound > 0) then
1871  text = 'NAME'
1872  call this%outputtab2%initialize_column(text, 20, alignment=tableft)
1873  end if
1874  end if
1875  end if
1876  !
1877  ! -- Return
1878  return
1879  end subroutine allocate_arrays
1880 
1881  !> @ brief Define observations
1882  !!
1883  !! Define the observations associated with this object
1884  !<
1885  subroutine gwf_gwf_df_obs(this)
1886  ! -- dummy
1887  class(gwfexchangetype) :: this !< GwfExchangeType
1888  ! -- local
1889  integer(I4B) :: indx
1890  !
1891  ! -- Store obs type and assign procedure pointer
1892  ! for gwf-gwf observation type.
1893  call this%obs%StoreObsType('flow-ja-face', .true., indx)
1894  this%obs%obsData(indx)%ProcessIdPtr => gwf_gwf_process_obsid
1895  !
1896  ! -- Return
1897  return
1898  end subroutine gwf_gwf_df_obs
1899 
1900  !> @ brief Read and prepare observations
1901  !!
1902  !! Handle observation exchanges exchange-boundary names.
1903  !<
1904  subroutine gwf_gwf_rp_obs(this)
1905  ! -- modules
1906  use constantsmodule, only: dzero
1907  ! -- dummy
1908  class(gwfexchangetype) :: this !< GwfExchangeType
1909  ! -- local
1910  integer(I4B) :: i
1911  integer(I4B) :: j
1912  class(observetype), pointer :: obsrv => null()
1913  character(len=LENBOUNDNAME) :: bname
1914  logical :: jfound
1915  ! -- formats
1916 10 format('Exchange "', a, '" for observation "', a, &
1917  '" is invalid in package "', a, '"')
1918 20 format('Exchange id "', i0, '" for observation "', a, &
1919  '" is invalid in package "', a, '"')
1920  !
1921  do i = 1, this%obs%npakobs
1922  obsrv => this%obs%pakobs(i)%obsrv
1923  !
1924  ! -- indxbnds needs to be reset each stress period because
1925  ! list of boundaries can change each stress period.
1926  ! -- Not true for exchanges, but leave this in for now anyway.
1927  call obsrv%ResetObsIndex()
1928  obsrv%BndFound = .false.
1929  !
1930  bname = obsrv%FeatureName
1931  if (bname /= '') then
1932  ! -- Observation location(s) is(are) based on a boundary name.
1933  ! Iterate through all boundaries to identify and store
1934  ! corresponding index(indices) in bound array.
1935  jfound = .false.
1936  do j = 1, this%nexg
1937  if (this%boundname(j) == bname) then
1938  jfound = .true.
1939  obsrv%BndFound = .true.
1940  obsrv%CurrentTimeStepEndValue = dzero
1941  call obsrv%AddObsIndex(j)
1942  end if
1943  end do
1944  if (.not. jfound) then
1945  write (errmsg, 10) trim(bname), trim(obsrv%ObsTypeId), trim(this%name)
1946  call store_error(errmsg)
1947  end if
1948  else
1949  ! -- Observation location is a single exchange number
1950  if (obsrv%intPak1 <= this%nexg .and. obsrv%intPak1 > 0) then
1951  jfound = .true.
1952  obsrv%BndFound = .true.
1953  obsrv%CurrentTimeStepEndValue = dzero
1954  call obsrv%AddObsIndex(obsrv%intPak1)
1955  else
1956  jfound = .false.
1957  end if
1958  if (.not. jfound) then
1959  write (errmsg, 20) obsrv%intPak1, trim(obsrv%ObsTypeId), trim(this%name)
1960  call store_error(errmsg)
1961  end if
1962  end if
1963  end do
1964  !
1965  ! -- write summary of error messages
1966  if (count_errors() > 0) then
1967  call store_error_filename(this%obs%inputFilename)
1968  end if
1969  !
1970  ! -- Return
1971  return
1972  end subroutine gwf_gwf_rp_obs
1973 
1974  !> @ brief Final processing
1975  !!
1976  !! Conduct any final processing
1977  !<
1978  subroutine gwf_gwf_fp(this)
1979  ! -- dummy
1980  class(gwfexchangetype) :: this !< GwfExchangeType
1981  !
1982  ! -- Return
1983  return
1984  end subroutine gwf_gwf_fp
1985 
1986  !> @ brief Calculate flow
1987  !!
1988  !! Calculate the flow for the specified exchange and node numbers
1989  !<
1990  function qcalc(this, iexg, n1, n2)
1991  ! -- return
1992  real(dp) :: qcalc
1993  ! -- dummy
1994  class(gwfexchangetype) :: this !< GwfExchangeType
1995  integer(I4B), intent(in) :: iexg
1996  integer(I4B), intent(in) :: n1
1997  integer(I4B), intent(in) :: n2
1998  ! -- local
1999  !
2000  ! -- Calculate flow between nodes in the two models
2001  qcalc = this%cond(iexg) * (this%gwfmodel2%x(n2) - this%gwfmodel1%x(n1))
2002  !
2003  ! -- Return
2004  return
2005  end function qcalc
2006 
2007  !> @ brief Set symmetric flag
2008  !!
2009  !! Return flag indicating whether or not this exchange will cause the
2010  !! coefficient matrix to be asymmetric.
2011  !<
2012  function gwf_gwf_get_iasym(this) result(iasym)
2013  ! -- dummy
2014  class(gwfexchangetype) :: this !< GwfExchangeType
2015  ! -- local
2016  integer(I4B) :: iasym
2017  !
2018  ! -- Start by setting iasym to zero
2019  iasym = 0
2020  !
2021  ! -- Groundwater flow
2022  if (this%inewton /= 0) iasym = 1
2023  !
2024  ! -- GNC
2025  if (this%ingnc > 0) then
2026  if (this%gnc%iasym /= 0) iasym = 1
2027  end if
2028  !
2029  ! -- Return
2030  return
2031  end function gwf_gwf_get_iasym
2032 
2033  !> @brief Return true when this exchange provides matrix
2034  !! coefficients for solving @param model
2035  !<
2036  function gwf_gwf_connects_model(this, model) result(is_connected)
2037  ! -- dummy
2038  class(gwfexchangetype) :: this !< GwfExchangeType
2039  class(basemodeltype), pointer, intent(in) :: model !< the model to which the exchange might hold a connection
2040  ! -- return
2041  logical(LGP) :: is_connected !< true, when connected
2042  !
2043  is_connected = .false.
2044  !
2045  ! only connected when model is GwfModelType of course
2046  select type (model)
2047  class is (gwfmodeltype)
2048  if (associated(this%gwfmodel1, model)) then
2049  is_connected = .true.
2050  else if (associated(this%gwfmodel2, model)) then
2051  is_connected = .true.
2052  end if
2053  end select
2054  !
2055  ! -- Return
2056  return
2057  end function gwf_gwf_connects_model
2058 
2059  !> @brief Should interface model be used for this exchange
2060  !<
2061  function use_interface_model(this) result(use_im)
2063  ! -- dummy
2064  class(gwfexchangetype) :: this !< GwfExchangeType
2065  ! -- return
2066  logical(LGP) :: use_im !< true when interface model should be used
2067  ! -- local
2068  integer(I4B) :: inbuy_m1
2069 
2070  use_im = this%DisConnExchangeType%use_interface_model()
2071  use_im = use_im .or. (this%ixt3d > 0)
2072 
2073  inbuy_m1 = 0
2074  select type (m => this%v_model1)
2075  class is (virtualgwfmodeltype)
2076  inbuy_m1 = m%inbuy%get()
2077  end select
2078  use_im = use_im .or. (inbuy_m1 > 0)
2079  !
2080  ! -- Return
2081  return
2082  end function
2083 
2084  !> @ brief Save simulated flow observations
2085  !!
2086  !! Save the simulated flows for each exchange
2087  !<
2088  subroutine gwf_gwf_save_simvals(this)
2089  ! -- modules
2090  use simvariablesmodule, only: errmsg
2091  use constantsmodule, only: dzero
2092  use observemodule, only: observetype
2093  ! -- dummy
2094  class(gwfexchangetype), intent(inout) :: this
2095  ! -- local
2096  integer(I4B) :: i
2097  integer(I4B) :: j
2098  integer(I4B) :: n1
2099  integer(I4B) :: n2
2100  integer(I4B) :: iexg
2101  real(DP) :: v
2102  type(observetype), pointer :: obsrv => null()
2103  !
2104  ! -- Write simulated values for all gwf-gwf observations
2105  if (this%obs%npakobs > 0) then
2106  call this%obs%obs_bd_clear()
2107  do i = 1, this%obs%npakobs
2108  obsrv => this%obs%pakobs(i)%obsrv
2109  do j = 1, obsrv%indxbnds_count
2110  iexg = obsrv%indxbnds(j)
2111  v = dzero
2112  select case (obsrv%ObsTypeId)
2113  case ('FLOW-JA-FACE')
2114  n1 = this%nodem1(iexg)
2115  n2 = this%nodem2(iexg)
2116  v = this%simvals(iexg)
2117  case default
2118  errmsg = 'Unrecognized observation type: '// &
2119  trim(obsrv%ObsTypeId)
2120  call store_error(errmsg)
2121  call store_error_filename(this%obs%inputFilename)
2122  end select
2123  call this%obs%SaveOneSimval(obsrv, v)
2124  end do
2125  end do
2126  end if
2127  !
2128  ! -- Return
2129  return
2130  end subroutine gwf_gwf_save_simvals
2131 
2132  !> @ brief Obs ID processor
2133  !!
2134  !! Process observations for this exchange
2135  !<
2136  subroutine gwf_gwf_process_obsid(obsrv, dis, inunitobs, iout)
2137  ! -- modules
2138  use constantsmodule, only: linelength
2139  use inputoutputmodule, only: urword
2140  use observemodule, only: observetype
2141  use basedismodule, only: disbasetype
2142  ! -- dummy
2143  type(observetype), intent(inout) :: obsrv
2144  class(disbasetype), intent(in) :: dis
2145  integer(I4B), intent(in) :: inunitobs
2146  integer(I4B), intent(in) :: iout
2147  ! -- local
2148  integer(I4B) :: n, iexg, istat
2149  integer(I4B) :: icol, istart, istop
2150  real(DP) :: r
2151  character(len=LINELENGTH) :: string
2152  !
2153  string = obsrv%IDstring
2154  icol = 1
2155  ! -- get exchange index
2156  call urword(string, icol, istart, istop, 1, n, r, iout, inunitobs)
2157  read (string(istart:istop), '(i10)', iostat=istat) iexg
2158  if (istat == 0) then
2159  obsrv%intPak1 = iexg
2160  else
2161  ! Integer can't be read from string; it's presumed to be an exchange
2162  ! boundary name (already converted to uppercase)
2163  obsrv%FeatureName = trim(adjustl(string))
2164  ! -- Observation may require summing rates from multiple exchange
2165  ! boundaries, so assign intPak1 as a value that indicates observation
2166  ! is for a named exchange boundary or group of exchange boundaries.
2167  obsrv%intPak1 = namedboundflag
2168  end if
2169  !
2170  ! -- Return
2171  return
2172  end subroutine gwf_gwf_process_obsid
2173 
2174  !> @ brief Cast polymorphic object as exchange
2175  !!
2176  !! Cast polymorphic object as exchange
2177  !<
2178  function castasgwfexchange(obj) result(res)
2179  implicit none
2180  ! -- dummy
2181  class(*), pointer, intent(inout) :: obj
2182  ! -- return
2183  class(gwfexchangetype), pointer :: res
2184  !
2185  res => null()
2186  if (.not. associated(obj)) return
2187  !
2188  select type (obj)
2189  class is (gwfexchangetype)
2190  res => obj
2191  end select
2192  !
2193  ! -- Return
2194  return
2195  end function castasgwfexchange
2196 
2197  !> @ brief Get exchange from list
2198  !!
2199  !! Return an exchange from the list for specified index
2200  !<
2201  function getgwfexchangefromlist(list, idx) result(res)
2202  implicit none
2203  ! -- dummy
2204  type(listtype), intent(inout) :: list
2205  integer(I4B), intent(in) :: idx
2206  ! -- return
2207  class(gwfexchangetype), pointer :: res
2208  ! -- local
2209  class(*), pointer :: obj
2210  !
2211  obj => list%GetItem(idx)
2212  res => castasgwfexchange(obj)
2213  !
2214  ! -- Return
2215  return
2216  end function getgwfexchangefromlist
2217 
2218 end module gwfgwfexchangemodule
2219 
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 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
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:67
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 dpio180
real constant
Definition: Constants.f90:129
real(dp), parameter dem6
real constant 1e-6
Definition: Constants.f90:108
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
real(dp), parameter done
real constant 1
Definition: Constants.f90:75
subroutine, public gnc_cr(gncobj, name_parent, inunit, iout)
Create new GNC exchange object.
Definition: GhostNode.f90:61
This module contains stateless conductance functions.
real(dp) function, public thksatnm(ibdn, ibdm, ictn, ictm, iupstream, ihc, hn, hm, satn, satm, topn, topm, botn, botm)
Calculate wetted cell thickness at interface between two cells.
real(dp) function, public condmean(k1, k2, thick1, thick2, cl1, cl2, width, iavgmeth)
Calculate the conductance between two cells.
real(dp) function, public hcond(ibdn, ibdm, ictn, ictm, iupstream, ihc, icellavg, condsat, hn, hm, satn, satm, hkn, hkm, topn, topm, botn, botm, cln, clm, fawidth)
Horizontal conductance between two cells.
real(dp) function, public vcond(ibdn, ibdm, ictn, ictm, inewton, ivarcv, idewatcv, condsat, hn, hm, vkn, vkm, satn, satm, topn, topm, botn, botm, flowarea)
Vertical conductance between two cells.
subroutine, public exg_mvr_cr(exg_mvr, name_parent, inunit, iout, dis)
This module contains the GwfGwfExchangeModule Module.
Definition: exg-gwfgwf.f90:10
integer(i4b) function gwf_gwf_get_iasym(this)
@ brief Set symmetric flag
subroutine gwf_gwf_fp(this)
@ brief Final processing
subroutine gwf_gwf_cq(this, icnvg, isuppress_output, isolnid)
@ brief Calculate flow
Definition: exg-gwfgwf.f90:697
class(gwfexchangetype) function, pointer, public getgwfexchangefromlist(list, idx)
@ brief Get exchange from list
subroutine gwf_gwf_process_obsid(obsrv, dis, inunitobs, iout)
@ brief Obs ID processor
subroutine rewet(this, kiter)
@ brief Rewet
subroutine gwf_gwf_add_to_flowja(this)
Add exchange flow to each model flowja diagonal position so that residual is calculated correctly.
Definition: exg-gwfgwf.f90:753
subroutine gwf_gwf_ac(this, sparse)
@ brief Add connections
Definition: exg-gwfgwf.f90:373
subroutine gwf_gwf_save_simvals(this)
@ brief Save simulated flow observations
subroutine calc_cond_sat(this)
logical(lgp) function use_interface_model(this)
Should interface model be used for this exchange.
subroutine gwf_gwf_ar(this)
@ brief Allocate and read
Definition: exg-gwfgwf.f90:433
subroutine gwf_gwf_bdsav(this)
@ brief Budget save
subroutine gwf_gwf_ad(this)
@ brief Advance
Definition: exg-gwfgwf.f90:477
subroutine gwf_gwf_fn(this, kiter, matrix_sln)
@ brief Fill Newton
Definition: exg-gwfgwf.f90:587
subroutine gwf_gwf_fc(this, kiter, matrix_sln, rhs_sln, inwtflag)
@ brief Fill coefficients
Definition: exg-gwfgwf.f90:516
subroutine gwf_gwf_bd(this, icnvg, isuppress_output, isolnid)
@ brief Budget
Definition: exg-gwfgwf.f90:904
subroutine allocate_scalars(this)
@ brief Allocate scalars
subroutine gwf_gwf_da(this)
@ brief Deallocate
subroutine gwf_gwf_rp(this)
@ brief Read and prepare
Definition: exg-gwfgwf.f90:454
real(dp) function qcalc(this, iexg, n1, n2)
@ brief Calculate flow
subroutine gwf_gwf_df(this)
@ brief Define GWF GWF exchange
Definition: exg-gwfgwf.f90:210
subroutine gwf_gwf_df_obs(this)
@ brief Define observations
logical(lgp) function gwf_gwf_connects_model(this, model)
Return true when this exchange provides matrix coefficients for solving.
subroutine gwf_gwf_set_flow_to_npf(this)
Set flow rates to the edges in the models.
Definition: exg-gwfgwf.f90:790
subroutine gwf_gwf_ot(this)
@ brief Output
subroutine allocate_arrays(this)
@ brief Allocate arrays
subroutine validate_exchange(this)
validate exchange data after reading
Definition: exg-gwfgwf.f90:280
class(gwfexchangetype) function, pointer, public castasgwfexchange(obj)
@ brief Cast polymorphic object as exchange
subroutine gwf_gwf_rp_obs(this)
@ brief Read and prepare observations
subroutine, public gwfexchange_create(filename, name, id, m1_id, m2_id, input_mempath)
@ brief Create GWF GWF exchange
Definition: exg-gwfgwf.f90:122
subroutine gwf_gwf_mc(this, matrix_sln)
@ brief Map connections
Definition: exg-gwfgwf.f90:403
subroutine gwf_gwf_cf(this, kiter)
@ brief Calculate coefficients
Definition: exg-gwfgwf.f90:495
subroutine gwf_gwf_bdsav_model(this, model)
subroutine gwf_gwf_calc_simvals(this)
Calculate flow rates for the exchanges and store them in a member array.
Definition: exg-gwfgwf.f90:720
subroutine gwf_gwf_chd_bd(this)
@ brief gwf-gwf-chd-bd
Definition: exg-gwfgwf.f90:953
subroutine read_mvr(this, iout)
@ brief Read mover
subroutine condcalc(this)
@ brief Calculate the conductance
subroutine read_gnc(this)
@ brief Read ghost nodes
subroutine source_options(this, iout)
@ brief Source options
Definition: gwf.f90:1
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 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
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
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
real(dp) function squadraticsaturationderivative(top, bot, x, eps)
@ brief Derivative of the quadratic saturation function
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
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...
Extends model mover for exchanges to also handle the.
Derived type for GwfExchangeType.
Definition: exg-gwfgwf.f90:47
A generic heterogeneous doubly-linked list.
Definition: List.f90:10