MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
mawmodule Module Reference

Data Types

type  mawtype
 

Functions/Subroutines

subroutine, public maw_create (packobj, id, ibcnum, inunit, iout, namemodel, pakname)
 Create a New Multi-Aquifer Well (MAW) Package. More...
 
subroutine maw_allocate_scalars (this)
 Allocate scalar members. More...
 
subroutine maw_allocate_well_conn_arrays (this)
 Allocate well arrays. More...
 
subroutine maw_allocate_arrays (this)
 Allocate arrays. More...
 
subroutine maw_read_wells (this)
 Read the packagedata for this package. More...
 
subroutine maw_read_well_connections (this)
 Read the dimensions for this package. More...
 
subroutine maw_read_dimensions (this)
 Read the dimensions for this package. More...
 
subroutine maw_read_initial_attr (this)
 Read the initial parameters for this package. More...
 
subroutine maw_set_stressperiod (this, imaw, iheadlimit_warning)
 Set a stress period attribute for mawweslls(imaw) using keywords. More...
 
subroutine maw_set_attribute_error (this, imaw, keyword, msg)
 Issue a parameter error for mawweslls(imaw) More...
 
subroutine maw_check_attributes (this)
 Issue parameter errors for mawwells(imaw) More...
 
subroutine maw_ac (this, moffset, sparse)
 Add package connection to matrix. More...
 
subroutine maw_mc (this, moffset, matrix_sln)
 Map package connection to matrix. More...
 
subroutine maw_read_options (this, option, found)
 Set options specific to MawType. More...
 
subroutine maw_ar (this)
 Allocate and Read. More...
 
subroutine maw_rp (this)
 Read and Prepare. More...
 
subroutine maw_ad (this)
 Add package connection to matrix. More...
 
subroutine maw_cf (this)
 Formulate the HCOF and RHS terms. More...
 
subroutine maw_fc (this, rhs, ia, idxglo, matrix_sln)
 Copy rhs and hcof into solution rhs and amat. More...
 
subroutine maw_fn (this, rhs, ia, idxglo, matrix_sln)
 Fill newton terms. More...
 
subroutine maw_nur (this, neqpak, x, xtemp, dx, inewtonur, dxmax, locmax)
 Calculate under-relaxation of groundwater flow model MAW Package heads for current outer iteration using the well bottom. More...
 
subroutine maw_cq (this, x, flowja, iadv)
 Calculate flows. More...
 
subroutine maw_ot_model_flows (this, icbcfl, ibudfl, icbcun, imap)
 Write flows to binary file and/or print flows to budget. More...
 
subroutine maw_ot_package_flows (this, icbcfl, ibudfl)
 Output MAW package flow terms. More...
 
subroutine maw_ot_dv (this, idvsave, idvprint)
 Save maw-calculated values to binary file. More...
 
subroutine maw_ot_bdsummary (this, kstp, kper, iout, ibudfl)
 Write MAW budget to listing file. More...
 
subroutine maw_da (this)
 Deallocate memory. More...
 
subroutine define_listlabel (this)
 Define the list heading that is written to iout when PRINT_INPUT option is used. More...
 
subroutine maw_set_pointers (this, neq, ibound, xnew, xold, flowja)
 Set pointers to model arrays and variables so that a package has has access to these things. More...
 
logical function maw_obs_supported (this)
 Return true because MAW package supports observations. More...
 
subroutine maw_df_obs (this)
 Store observation type supported by MAW package. More...
 
subroutine maw_bd_obs (this)
 Calculate observations this time step and call ObsTypeSaveOneSimval for each MawType observation. More...
 
subroutine maw_rp_obs (this)
 Process each observation. More...
 
subroutine maw_process_obsid (obsrv, dis, inunitobs, iout)
 This procedure is pointed to by ObsDataTypeProcesssIdPtr. It processes the ID string of an observation definition for MAW package observations. More...
 
subroutine maw_redflow_csv_init (this, fname)
 Initialize the auto flow reduce csv output file. More...
 
subroutine maw_redflow_csv_write (this)
 MAW reduced flows only when & where they occur. More...
 
subroutine maw_calculate_satcond (this, i, j, node)
 Calculate the appropriate saturated conductance to use based on aquifer and multi-aquifer well characteristics. More...
 
subroutine maw_calculate_saturation (this, n, j, node, sat)
 Calculate the saturation between the aquifer maw well_head. More...
 
subroutine maw_calculate_conn_terms (this, n, j, icflow, cmaw, cterm, term, flow, term2)
 Calculate matrix terms for a multi-aquifer well connection. Terms for fc and fn methods are calculated based on whether term2 is passed Arguments are as follows: n : maw well number j : connection number for well n icflow : flag indicating that flow should be corrected cmaw : maw-gwf conducance cterm : correction term for flow to dry cell term : xxx flow : calculated flow for this connection, positive into well term2 : xxx. More...
 
subroutine maw_calculate_wellq (this, n, hmaw, q)
 Calculate well pumping rate based on constraints. More...
 
subroutine maw_calculate_qpot (this, n, qnet)
 Calculate groundwater inflow to a maw well. More...
 
subroutine maw_cfupdate (this)
 Update MAW satcond and package rhs and hcof. More...
 
subroutine maw_setup_budobj (this)
 Set up the budget object that stores all the maw flows The terms listed here must correspond in number and order to the ones listed in the maw_fill_budobj routine. More...
 
subroutine maw_fill_budobj (this)
 Copy flow terms into thisbudobj. More...
 
subroutine maw_setup_tableobj (this)
 Set up the table object that is used to write the maw head data. More...
 
integer(i4b) function get_jpos (this, n, j)
 Get position of value in connection data. More...
 
integer(i4b) function get_gwfnode (this, n, j)
 Get the gwfnode for connection. More...
 
subroutine maw_activate_density (this)
 Activate density terms. More...
 
subroutine maw_activate_viscosity (this)
 Activate viscosity terms. More...
 
subroutine maw_calculate_density_exchange (this, iconn, hmaw, hgwf, cond, bmaw, flow, hcofterm, rhsterm)
 Calculate the groundwater-maw density exchange terms. More...
 

Variables

character(len=lenftype) ftype = 'MAW'
 
character(len=lenpackagename) text = ' MAW'
 

Function/Subroutine Documentation

◆ define_listlabel()

subroutine mawmodule::define_listlabel ( class(mawtype), intent(inout)  this)

Definition at line 2931 of file gwf-maw.f90.

2932  class(MawType), intent(inout) :: this
2933  !
2934  ! -- create the header list label
2935  this%listlabel = trim(this%filtyp)//' NO.'
2936  if (this%dis%ndim == 3) then
2937  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
2938  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
2939  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
2940  elseif (this%dis%ndim == 2) then
2941  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
2942  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
2943  else
2944  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
2945  end if
2946  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'STRESS RATE'
2947  if (this%inamedbound == 1) then
2948  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
2949  end if
2950  !
2951  ! -- Return
2952  return

◆ get_gwfnode()

integer(i4b) function mawmodule::get_gwfnode ( class(mawtype this,
integer(i4b), intent(in)  n,
integer(i4b), intent(in)  j 
)
private

Definition at line 4648 of file gwf-maw.f90.

4649  ! -- return variable
4650  integer(I4B) :: igwfnode
4651  ! -- dummy
4652  class(MawType) :: this
4653  integer(I4B), intent(in) :: n
4654  integer(I4B), intent(in) :: j
4655  ! -- local
4656  integer(I4B) :: jpos
4657  !
4658  ! -- set jpos
4659  jpos = this%get_jpos(n, j)
4660  igwfnode = this%gwfnodes(jpos)
4661  !
4662  ! -- Return
4663  return

◆ get_jpos()

integer(i4b) function mawmodule::get_jpos ( class(mawtype this,
integer(i4b), intent(in)  n,
integer(i4b), intent(in)  j 
)

Definition at line 4630 of file gwf-maw.f90.

4631  ! -- return variable
4632  integer(I4B) :: jpos
4633  ! -- dummy
4634  class(MawType) :: this
4635  integer(I4B), intent(in) :: n
4636  integer(I4B), intent(in) :: j
4637  ! -- local
4638  !
4639  ! -- set jpos
4640  jpos = this%iaconn(n) + j - 1
4641  !
4642  ! -- Return
4643  return

◆ maw_ac()

subroutine mawmodule::maw_ac ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  moffset,
type(sparsematrix), intent(inout)  sparse 
)

Definition at line 1587 of file gwf-maw.f90.

1588  use sparsemodule, only: sparsematrix
1589  ! -- dummy
1590  class(MawType), intent(inout) :: this
1591  integer(I4B), intent(in) :: moffset
1592  type(sparsematrix), intent(inout) :: sparse
1593  ! -- local
1594  integer(I4B) :: j
1595  integer(I4B) :: n
1596  integer(I4B) :: jj
1597  integer(I4B) :: jglo
1598  integer(I4B) :: nglo
1599  ! -- format
1600  !
1601  ! -- Add package rows to sparse
1602  do n = 1, this%nmawwells
1603  nglo = moffset + this%dis%nodes + this%ioffset + n
1604  call sparse%addconnection(nglo, nglo, 1)
1605  do j = 1, this%ngwfnodes(n)
1606  jj = this%get_gwfnode(n, j)
1607  jglo = jj + moffset
1608  call sparse%addconnection(nglo, jglo, 1)
1609  call sparse%addconnection(jglo, nglo, 1)
1610  end do
1611 
1612  end do
1613  !
1614  ! -- Return
1615  return

◆ maw_activate_density()

subroutine mawmodule::maw_activate_density ( class(mawtype), intent(inout)  this)
private

Definition at line 4668 of file gwf-maw.f90.

4669  ! -- dummy
4670  class(MawType), intent(inout) :: this
4671  ! -- local
4672  integer(I4B) :: i, j
4673  ! -- formats
4674  !
4675  ! -- Set idense and reallocate denseterms to be of size MAXBOUND
4676  this%idense = 1
4677  call mem_reallocate(this%denseterms, 3, this%MAXBOUND, 'DENSETERMS', &
4678  this%memoryPath)
4679  do i = 1, this%maxbound
4680  do j = 1, 3
4681  this%denseterms(j, i) = dzero
4682  end do
4683  end do
4684  write (this%iout, '(/1x,a)') 'DENSITY TERMS HAVE BEEN ACTIVATED FOR MAW &
4685  &PACKAGE: '//trim(adjustl(this%packName))
4686  !
4687  ! -- Return
4688  return

◆ maw_activate_viscosity()

subroutine mawmodule::maw_activate_viscosity ( class(mawtype), intent(inout)  this)
private

Method to activate addition of viscosity terms for a MAW package reach.

Parameters
[in,out]thisMawType object

Definition at line 4695 of file gwf-maw.f90.

4696  ! -- modules
4698  ! -- dummy variables
4699  class(MawType), intent(inout) :: this !< MawType object
4700  ! -- local variables
4701  integer(I4B) :: i
4702  integer(I4B) :: j
4703  !
4704  ! -- Set ivsc and reallocate viscratios to be of size MAXBOUND
4705  this%ivsc = 1
4706  call mem_reallocate(this%viscratios, 2, this%MAXBOUND, 'VISCRATIOS', &
4707  this%memoryPath)
4708  do i = 1, this%maxbound
4709  do j = 1, 2
4710  this%viscratios(j, i) = done
4711  end do
4712  end do
4713  write (this%iout, '(/1x,a)') 'VISCOSITY HAS BEEN ACTIVATED FOR MAW &
4714  &PACKAGE: '//trim(adjustl(this%packName))
4715  !
4716  ! -- Return
4717  return

◆ maw_ad()

subroutine mawmodule::maw_ad ( class(mawtype this)

Definition at line 2124 of file gwf-maw.f90.

2125  use tdismodule, only: kper, kstp
2126  ! -- dummy
2127  class(MawType) :: this
2128  ! -- local
2129  integer(I4B) :: n
2130  integer(I4B) :: j
2131  integer(I4B) :: jj
2132  integer(I4B) :: ibnd
2133  !
2134  ! -- Advance the time series
2135  call this%TsManager%ad()
2136  !
2137  ! -- update auxiliary variables by copying from the derived-type time
2138  ! series variable into the bndpackage auxvar variable so that this
2139  ! information is properly written to the GWF budget file
2140  if (this%naux > 0) then
2141  ibnd = 1
2142  do n = 1, this%nmawwells
2143  do j = 1, this%ngwfnodes(n)
2144  do jj = 1, this%naux
2145  if (this%noupdateauxvar(jj) /= 0) cycle
2146  this%auxvar(jj, ibnd) = this%mauxvar(jj, n)
2147  end do
2148  ibnd = ibnd + 1
2149  end do
2150  end do
2151  end if
2152  !
2153  ! -- copy xnew into xold
2154  do n = 1, this%nmawwells
2155  this%xoldpak(n) = this%xnewpak(n)
2156  this%xoldsto(n) = this%xsto(n)
2157  if (this%iboundpak(n) < 0) then
2158  this%xnewpak(n) = this%well_head(n)
2159  end if
2160  end do
2161  !
2162  !--use the appropriate xoldsto if initial heads are above the
2163  ! specified flowing well discharge elevation
2164  if (kper == 1 .and. kstp == 1) then
2165  do n = 1, this%nmawwells
2166  if (this%fwcond(n) > dzero) then
2167  if (this%xoldsto(n) > this%fwelev(n)) then
2168  this%xoldsto(n) = this%fwelev(n)
2169  end if
2170  end if
2171  end do
2172  end if
2173  !
2174  ! -- reset ishutoffcnt (equivalent to kiter) to zero
2175  this%ishutoffcnt = 0
2176  !
2177  ! -- pakmvrobj ad
2178  if (this%imover == 1) then
2179  call this%pakmvrobj%ad()
2180  end if
2181  !
2182  ! -- For each observation, push simulated value and corresponding
2183  ! simulation time from "current" to "preceding" and reset
2184  ! "current" value.
2185  call this%obs%obs_ad()
2186  !
2187  ! -- Return
2188  return
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

◆ maw_allocate_arrays()

subroutine mawmodule::maw_allocate_arrays ( class(mawtype), intent(inout)  this)

Definition at line 529 of file gwf-maw.f90.

530  ! -- modules
532  ! -- dummy
533  class(MawType), intent(inout) :: this
534  ! -- local
535  !
536  ! -- call standard BndType allocate scalars
537  call this%BndType%allocate_arrays()
538  !
539  ! -- Return
540  return

◆ maw_allocate_scalars()

subroutine mawmodule::maw_allocate_scalars ( class(mawtype), intent(inout)  this)
private

Definition at line 273 of file gwf-maw.f90.

274  ! -- modules
276  ! -- dummy
277  class(MawType), intent(inout) :: this
278  !
279  ! -- call standard BndType allocate scalars
280  call this%BndType%allocate_scalars()
281  !
282  ! -- allocate the object and assign values to object variables
283  call mem_allocate(this%correct_flow, 'CORRECT_FLOW', this%memoryPath)
284  call mem_allocate(this%iprhed, 'IPRHED', this%memoryPath)
285  call mem_allocate(this%iheadout, 'IHEADOUT', this%memoryPath)
286  call mem_allocate(this%ibudgetout, 'IBUDGETOUT', this%memoryPath)
287  call mem_allocate(this%ibudcsv, 'IBUDCSV', this%memoryPath)
288  call mem_allocate(this%iflowingwells, 'IFLOWINGWELLS', this%memoryPath)
289  call mem_allocate(this%imawiss, 'IMAWISS', this%memoryPath)
290  call mem_allocate(this%imawissopt, 'IMAWISSOPT', this%memoryPath)
291  call mem_allocate(this%nmawwells, 'NMAWWELLS', this%memoryPath)
292  call mem_allocate(this%check_attr, 'CHECK_ATTR', this%memoryPath)
293  call mem_allocate(this%ishutoffcnt, 'ISHUTOFFCNT', this%memoryPath)
294  call mem_allocate(this%ieffradopt, 'IEFFRADOPT', this%memoryPath)
295  call mem_allocate(this%ioutredflowcsv, 'IOUTREDFLOWCSV', this%memoryPath) !for writing reduced MAW flows to csv file
296  call mem_allocate(this%satomega, 'SATOMEGA', this%memoryPath)
297  call mem_allocate(this%bditems, 'BDITEMS', this%memoryPath)
298  call mem_allocate(this%theta, 'THETA', this%memoryPath)
299  call mem_allocate(this%kappa, 'KAPPA', this%memoryPath)
300  call mem_allocate(this%cbcauxitems, 'CBCAUXITEMS', this%memoryPath)
301  call mem_allocate(this%idense, 'IDENSE', this%memoryPath)
302  !
303  ! -- Set values
304  this%correct_flow = .false.
305  this%nmawwells = 0
306  this%iprhed = 0
307  this%iheadout = 0
308  this%ibudgetout = 0
309  this%ibudcsv = 0
310  this%iflowingwells = 0
311  this%imawiss = 0
312  this%imawissopt = 0
313  this%ieffradopt = 0
314  this%ioutredflowcsv = 0
315  this%satomega = dzero
316  this%bditems = 8
317  this%theta = dp7
318  this%kappa = dem4
319  this%cbcauxitems = 1
320  this%idense = 0
321  this%ivsc = 0
322  !
323  ! -- Return
324  return

◆ maw_allocate_well_conn_arrays()

subroutine mawmodule::maw_allocate_well_conn_arrays ( class(mawtype), intent(inout)  this)

Definition at line 329 of file gwf-maw.f90.

330  ! -- modules
332  ! -- dummy
333  class(MawType), intent(inout) :: this
334  ! -- local
335  integer(I4B) :: j
336  integer(I4B) :: n
337  integer(I4B) :: jj
338  !
339  ! -- allocate character array for budget text
340  call mem_allocate(this%cmawbudget, lenbudtxt, this%bditems, 'CMAWBUDGET', &
341  this%memoryPath)
342  !
343  !-- fill cmawbudget
344  this%cmawbudget(1) = ' GWF'
345  this%cmawbudget(2) = ' RATE'
346  this%cmawbudget(3) = ' STORAGE'
347  this%cmawbudget(4) = ' CONSTANT'
348  this%cmawbudget(5) = ' FW-RATE'
349  this%cmawbudget(6) = ' FROM-MVR'
350  this%cmawbudget(7) = ' RATE-TO-MVR'
351  this%cmawbudget(8) = ' FW-RATE-TO-MVR'
352  !
353  ! -- allocate character arrays
354  call mem_allocate(this%cmawname, lenboundname, this%nmawwells, 'CMAWNAME', &
355  this%memoryPath)
356  call mem_allocate(this%status, 8, this%nmawwells, 'STATUS', this%memoryPath)
357  !
358  ! -- allocate well data pointers in memory manager
359  call mem_allocate(this%ngwfnodes, this%nmawwells, 'NGWFNODES', &
360  this%memoryPath)
361  call mem_allocate(this%ieqn, this%nmawwells, 'IEQN', this%memoryPath)
362  call mem_allocate(this%ishutoff, this%nmawwells, 'ISHUTOFF', this%memoryPath)
363  call mem_allocate(this%ifwdischarge, this%nmawwells, 'IFWDISCHARGE', &
364  this%memoryPath)
365  call mem_allocate(this%strt, this%nmawwells, 'STRT', this%memoryPath)
366  call mem_allocate(this%radius, this%nmawwells, 'RADIUS', this%memoryPath)
367  call mem_allocate(this%area, this%nmawwells, 'AREA', this%memoryPath)
368  call mem_allocate(this%pumpelev, this%nmawwells, 'PUMPELEV', this%memoryPath)
369  call mem_allocate(this%bot, this%nmawwells, 'BOT', this%memoryPath)
370  call mem_allocate(this%ratesim, this%nmawwells, 'RATESIM', this%memoryPath)
371  call mem_allocate(this%reduction_length, this%nmawwells, 'REDUCTION_LENGTH', &
372  this%memoryPath)
373  call mem_allocate(this%fwelev, this%nmawwells, 'FWELEV', this%memoryPath)
374  call mem_allocate(this%fwcond, this%nmawwells, 'FWCONDS', this%memoryPath)
375  call mem_allocate(this%fwrlen, this%nmawwells, 'FWRLEN', this%memoryPath)
376  call mem_allocate(this%fwcondsim, this%nmawwells, 'FWCONDSIM', &
377  this%memoryPath)
378  call mem_allocate(this%xsto, this%nmawwells, 'XSTO', this%memoryPath)
379  call mem_allocate(this%xoldsto, this%nmawwells, 'XOLDSTO', this%memoryPath)
380  call mem_allocate(this%shutoffmin, this%nmawwells, 'SHUTOFFMIN', &
381  this%memoryPath)
382  call mem_allocate(this%shutoffmax, this%nmawwells, 'SHUTOFFMAX', &
383  this%memoryPath)
384  call mem_allocate(this%shutofflevel, this%nmawwells, 'SHUTOFFLEVEL', &
385  this%memoryPath)
386  call mem_allocate(this%shutoffweight, this%nmawwells, 'SHUTOFFWEIGHT', &
387  this%memoryPath)
388  call mem_allocate(this%shutoffdq, this%nmawwells, 'SHUTOFFDQ', &
389  this%memoryPath)
390  call mem_allocate(this%shutoffqold, this%nmawwells, 'SHUTOFFQOLD', &
391  this%memoryPath)
392  !
393  ! -- timeseries aware variables
394  call mem_allocate(this%rate, this%nmawwells, 'RATE', this%memoryPath)
395  call mem_allocate(this%well_head, this%nmawwells, 'WELL_HEAD', &
396  this%memoryPath)
397  if (this%naux > 0) then
398  jj = this%naux
399  else
400  jj = 1
401  end if
402  call mem_allocate(this%mauxvar, jj, this%nmawwells, 'MAUXVAR', &
403  this%memoryPath)
404  !
405  ! -- allocate and initialize dbuff
406  if (this%iheadout > 0) then
407  call mem_allocate(this%dbuff, this%nmawwells, 'DBUFF', this%memoryPath)
408  else
409  call mem_allocate(this%dbuff, 0, 'DBUFF', this%memoryPath)
410  end if
411  !
412  ! -- allocate iaconn
413  call mem_allocate(this%iaconn, this%nmawwells + 1, 'IACONN', this%memoryPath)
414  !
415  ! -- allocate imap
416  call mem_allocate(this%imap, this%MAXBOUND, 'IMAP', this%memoryPath)
417  !
418  ! -- allocate connection data
419  call mem_allocate(this%gwfnodes, this%maxbound, 'GWFNODES', this%memoryPath)
420  call mem_allocate(this%sradius, this%maxbound, 'SRADIUS', this%memoryPath)
421  call mem_allocate(this%hk, this%maxbound, 'HK', this%memoryPath)
422  call mem_allocate(this%satcond, this%maxbound, 'SATCOND', this%memoryPath)
423  call mem_allocate(this%simcond, this%maxbound, 'SIMCOND', this%memoryPath)
424  call mem_allocate(this%topscrn, this%maxbound, 'TOPSCRN', this%memoryPath)
425  call mem_allocate(this%botscrn, this%maxbound, 'BOTSCRN', this%memoryPath)
426  !
427  ! -- allocate qleak
428  call mem_allocate(this%qleak, this%maxbound, 'QLEAK', this%memoryPath)
429  !
430  ! -- initialize well data
431  do n = 1, this%nmawwells
432  this%status(n) = 'ACTIVE'
433  this%ngwfnodes(n) = 0
434  this%ieqn(n) = 0
435  this%ishutoff(n) = 0
436  this%ifwdischarge(n) = 0
437  this%strt(n) = dep20
438  this%radius(n) = dep20
439  this%area(n) = dzero
440  this%pumpelev(n) = dep20
441  this%bot(n) = dep20
442  this%ratesim(n) = dzero
443  this%reduction_length(n) = dep20
444  this%fwelev(n) = dzero
445  this%fwcond(n) = dzero
446  this%fwrlen(n) = dzero
447  this%fwcondsim(n) = dzero
448  this%xsto(n) = dzero
449  this%xoldsto(n) = dzero
450  this%shutoffmin(n) = dzero
451  this%shutoffmax(n) = dzero
452  this%shutofflevel(n) = dep20
453  this%shutoffweight(n) = done
454  this%shutoffdq(n) = done
455  this%shutoffqold(n) = done
456  !
457  ! -- timeseries aware variables
458  this%rate(n) = dzero
459  this%well_head(n) = dzero
460  do jj = 1, max(1, this%naux)
461  this%mauxvar(jj, n) = dzero
462  end do
463  !
464  ! -- dbuff
465  if (this%iheadout > 0) then
466  this%dbuff(n) = dzero
467  end if
468  end do
469  !
470  ! -- initialize iaconn
471  do n = 1, this%nmawwells + 1
472  this%iaconn(n) = 0
473  end do
474  !
475  ! -- allocate character array for budget text
476  call mem_allocate(this%cauxcbc, lenauxname, this%cbcauxitems, 'CAUXCBC', &
477  this%memoryPath)
478  !
479  ! -- allocate and initialize qauxcbc
480  call mem_allocate(this%qauxcbc, this%cbcauxitems, 'QAUXCBC', this%memoryPath)
481  do j = 1, this%cbcauxitems
482  this%qauxcbc(j) = dzero
483  end do
484  !
485  ! -- allocate flowing well data
486  if (this%iflowingwells /= 0) then
487  call mem_allocate(this%qfw, this%nmawwells, 'QFW', this%memoryPath)
488  else
489  call mem_allocate(this%qfw, 1, 'QFW', this%memoryPath)
490  end if
491  call mem_allocate(this%qout, this%nmawwells, 'QOUT', this%memoryPath)
492  call mem_allocate(this%qsto, this%nmawwells, 'QSTO', this%memoryPath)
493  call mem_allocate(this%qconst, this%nmawwells, 'QCONST', this%memoryPath)
494  !
495  ! -- initialize flowing well, storage, and constant flow terms
496  do n = 1, this%nmawwells
497  if (this%iflowingwells > 0) then
498  this%qfw(n) = dzero
499  end if
500  this%qsto(n) = dzero
501  this%qconst(n) = dzero
502  end do
503  !
504  ! -- initialize connection data
505  do j = 1, this%maxbound
506  this%imap(j) = 0
507  this%gwfnodes(j) = 0
508  this%sradius(j) = dzero
509  this%hk(j) = dzero
510  this%satcond(j) = dzero
511  this%simcond(j) = dzero
512  this%topscrn(j) = dzero
513  this%botscrn(j) = dzero
514  this%qleak(j) = dzero
515  end do
516  !
517  ! -- allocate denseterms to size 0
518  call mem_allocate(this%denseterms, 3, 0, 'DENSETERMS', this%memoryPath)
519  !
520  ! -- allocate viscratios to size 0
521  call mem_allocate(this%viscratios, 2, 0, 'VISCRATIOS', this%memoryPath)
522  !
523  ! -- Return
524  return

◆ maw_ar()

subroutine mawmodule::maw_ar ( class(mawtype), intent(inout)  this)

Create new MAW package and point bndobj to the new package

Definition at line 1804 of file gwf-maw.f90.

1805  ! -- dummy
1806  class(MawType), intent(inout) :: this
1807  ! -- local
1808  ! -- format
1809  !
1810  call this%obs%obs_ar()
1811  !
1812  ! -- set omega value used for saturation calculations
1813  if (this%inewton > 0) then
1814  this%satomega = dem6
1815  end if
1816  !
1817  ! -- Allocate connection arrays in MAW and in package superclass
1818  call this%maw_allocate_arrays()
1819  !
1820  ! -- read optional initial package parameters
1821  call this%read_initial_attr()
1822  !
1823  ! -- setup pakmvrobj
1824  if (this%imover /= 0) then
1825  allocate (this%pakmvrobj)
1826  call this%pakmvrobj%ar(this%nmawwells, this%nmawwells, this%memoryPath)
1827  end if
1828  !
1829  ! -- Return
1830  return

◆ maw_bd_obs()

subroutine mawmodule::maw_bd_obs ( class(mawtype this)
private

Definition at line 3082 of file gwf-maw.f90.

3083  ! -- dummy
3084  class(MawType) :: this
3085  ! -- local
3086  integer(I4B) :: i
3087  integer(I4B) :: j
3088  integer(I4B) :: jj
3089  integer(I4B) :: n
3090  integer(I4B) :: nn
3091  integer(I4B) :: jpos
3092  real(DP) :: cmaw
3093  real(DP) :: hmaw
3094  real(DP) :: v
3095  real(DP) :: qfact
3096  type(ObserveType), pointer :: obsrv => null()
3097  !
3098  ! Calculate, save, and write simulated values for all MAW observations
3099  if (this%obs%npakobs > 0) then
3100  call this%obs%obs_bd_clear()
3101  do i = 1, this%obs%npakobs
3102  obsrv => this%obs%pakobs(i)%obsrv
3103  do j = 1, obsrv%indxbnds_count
3104  v = dnodata
3105  jj = obsrv%indxbnds(j)
3106  select case (obsrv%ObsTypeId)
3107  case ('HEAD')
3108  if (this%iboundpak(jj) /= 0) then
3109  v = this%xnewpak(jj)
3110  end if
3111  case ('FROM-MVR')
3112  if (this%iboundpak(jj) /= 0) then
3113  if (this%imover == 1) then
3114  v = this%pakmvrobj%get_qfrommvr(jj)
3115  end if
3116  end if
3117  case ('MAW')
3118  n = this%imap(jj)
3119  if (this%iboundpak(n) /= 0) then
3120  v = this%qleak(jj)
3121  end if
3122  case ('RATE')
3123  if (this%iboundpak(jj) /= 0) then
3124  v = this%ratesim(jj)
3125  if (v < dzero .and. this%qout(jj) < dzero) then
3126  qfact = v / this%qout(jj)
3127  if (this%imover == 1) then
3128  v = v + this%pakmvrobj%get_qtomvr(jj) * qfact
3129  end if
3130  end if
3131  end if
3132  case ('RATE-TO-MVR')
3133  if (this%iboundpak(jj) /= 0) then
3134  if (this%imover == 1) then
3135  v = this%ratesim(jj)
3136  qfact = dzero
3137  if (v < dzero .and. this%qout(jj) < dzero) then
3138  qfact = v / this%qout(jj)
3139  end if
3140  v = this%pakmvrobj%get_qtomvr(jj) * qfact
3141  if (v > dzero) then
3142  v = -v
3143  end if
3144  end if
3145  end if
3146  case ('FW-RATE')
3147  if (this%iboundpak(jj) /= 0 .and. this%iflowingwells > 0) then
3148  hmaw = this%xnewpak(jj)
3149  cmaw = this%fwcondsim(jj)
3150  v = cmaw * (this%fwelev(jj) - hmaw)
3151  if (v < dzero .and. this%qout(jj) < dzero) then
3152  qfact = v / this%qout(jj)
3153  if (this%imover == 1) then
3154  v = v + this%pakmvrobj%get_qtomvr(jj) * qfact
3155  end if
3156  end if
3157  end if
3158  case ('FW-TO-MVR')
3159  if (this%iboundpak(jj) /= 0 .and. this%iflowingwells > 0) then
3160  if (this%imover == 1) then
3161  hmaw = this%xnewpak(jj)
3162  cmaw = this%fwcondsim(jj)
3163  v = cmaw * (this%fwelev(jj) - hmaw)
3164  qfact = dzero
3165  if (v < dzero .and. this%qout(jj) < dzero) then
3166  qfact = v / this%qout(jj)
3167  end if
3168  v = this%pakmvrobj%get_qtomvr(jj) * qfact
3169  if (v > dzero) then
3170  v = -v
3171  end if
3172  end if
3173  end if
3174  case ('STORAGE')
3175  if (this%iboundpak(jj) /= 0 .and. this%imawissopt /= 1) then
3176  v = this%qsto(jj)
3177  end if
3178  case ('CONSTANT')
3179  if (this%iboundpak(jj) /= 0) then
3180  v = this%qconst(jj)
3181  end if
3182  case ('CONDUCTANCE')
3183  n = this%imap(jj)
3184  if (this%iboundpak(n) /= 0) then
3185  nn = jj - this%iaconn(n) + 1
3186  jpos = this%get_jpos(n, nn)
3187  v = this%simcond(jpos)
3188  end if
3189  case ('FW-CONDUCTANCE')
3190  if (this%iboundpak(jj) /= 0) then
3191  v = this%fwcondsim(jj)
3192  end if
3193  case default
3194  errmsg = 'Unrecognized observation type: '//trim(obsrv%ObsTypeId)
3195  call store_error(errmsg)
3196  end select
3197  call this%obs%SaveOneSimval(obsrv, v)
3198  end do
3199  end do
3200  !
3201  ! -- write summary of error messages
3202  if (count_errors() > 0) then
3203  call store_error_unit(this%inunit)
3204  end if
3205  end if
3206  !
3207  ! -- Write the MAW reduced flows to csv file entries for this step
3208  if (this%ioutredflowcsv > 0) then
3209  call this%maw_redflow_csv_write()
3210  end if
3211  !
3212  ! -- Return
3213  return
Here is the call graph for this function:

◆ maw_calculate_conn_terms()

subroutine mawmodule::maw_calculate_conn_terms ( class(mawtype this,
integer(i4b), intent(in)  n,
integer(i4b), intent(in)  j,
integer(i4b), intent(inout)  icflow,
real(dp), intent(inout)  cmaw,
real(dp), intent(inout)  cterm,
real(dp), intent(inout)  term,
real(dp), intent(inout)  flow,
real(dp), intent(inout), optional  term2 
)
private

Definition at line 3700 of file gwf-maw.f90.

3702  ! -- dummy
3703  class(MawType) :: this
3704  integer(I4B), intent(in) :: n
3705  integer(I4B), intent(in) :: j
3706  integer(I4B), intent(inout) :: icflow
3707  real(DP), intent(inout) :: cmaw
3708  real(DP), intent(inout) :: cterm
3709  real(DP), intent(inout) :: term
3710  real(DP), intent(inout) :: flow
3711  real(DP), intent(inout), optional :: term2
3712  ! -- local
3713  logical(LGP) :: correct_flow
3714  integer(I4B) :: inewton
3715  integer(I4B) :: jpos
3716  integer(I4B) :: igwfnode
3717  real(DP) :: hmaw
3718  real(DP) :: hgwf
3719  real(DP) :: hups
3720  real(DP) :: hdowns
3721  real(DP) :: sat
3722  real(DP) :: tmaw
3723  real(DP) :: bmaw
3724  real(DP) :: en
3725  real(DP) :: hbar
3726  real(DP) :: drterm
3727  real(DP) :: dhbarterm
3728  real(DP) :: vscratio
3729  !
3730  ! -- initialize terms
3731  cterm = dzero
3732  vscratio = done
3733  icflow = 0
3734  if (present(term2)) then
3735  inewton = 1
3736  else
3737  inewton = 0
3738  end if
3739  !
3740  ! -- set common terms
3741  jpos = this%get_jpos(n, j)
3742  igwfnode = this%get_gwfnode(n, j)
3743  hgwf = this%xnew(igwfnode)
3744  hmaw = this%xnewpak(n)
3745  tmaw = this%topscrn(jpos)
3746  bmaw = this%botscrn(jpos)
3747  !
3748  ! -- if vsc active, select appropriate viscosity ratio
3749  if (this%ivsc == 1) then
3750  ! flow out of well (flow is negative)
3751  if (flow < 0) then
3752  vscratio = this%viscratios(1, igwfnode)
3753  else
3754  vscratio = this%viscratios(2, igwfnode)
3755  end if
3756  end if
3757  !
3758  ! -- calculate saturation
3759  call this%maw_calculate_saturation(n, j, igwfnode, sat)
3760  cmaw = this%satcond(jpos) * vscratio * sat
3761  !
3762  ! -- set upstream head, term, and term2 if returning newton terms
3763  if (inewton == 1) then
3764  term = dzero
3765  term2 = dzero
3766  hups = hmaw
3767  if (hgwf > hups) then
3768  hups = hgwf
3769  end if
3770  !
3771  ! -- calculate the derivative of saturation
3772  drterm = squadraticsaturationderivative(tmaw, bmaw, hups, this%satomega)
3773  else
3774  term = cmaw
3775  end if
3776  !
3777  ! -- calculate correction term if flow_correction option specified
3778  if (this%correct_flow) then
3779  !
3780  ! -- set bmaw, determine en, and set correct_flow flag
3781  en = max(bmaw, this%dis%bot(igwfnode))
3782  correct_flow = .false.
3783  if (hmaw < en) then
3784  correct_flow = .true.
3785  end if
3786  if (hgwf < en .and. this%icelltype(igwfnode) /= 0) then
3787  correct_flow = .true.
3788  end if
3789  !
3790  ! -- if flow should be corrected because hgwf or hmaw is below bottom
3791  ! then calculate correction term (cterm)
3792  if (correct_flow) then
3793  icflow = 1
3794  hdowns = min(hmaw, hgwf)
3795  hbar = squadratic0sp(hdowns, en, this%satomega)
3796  if (hgwf > hmaw) then
3797  cterm = cmaw * (hmaw - hbar)
3798  else
3799  cterm = cmaw * (hbar - hgwf)
3800  end if
3801  end if
3802  !
3803  ! -- if newton formulation then calculate newton terms
3804  if (inewton /= 0) then
3805  !
3806  ! -- maw is upstream
3807  if (hmaw > hgwf) then
3808  hbar = squadratic0sp(hgwf, en, this%satomega)
3809  term = drterm * this%satcond(jpos) * vscratio * (hbar - hmaw)
3810  dhbarterm = squadratic0spderivative(hgwf, en, this%satomega)
3811  term2 = cmaw * (dhbarterm - done)
3812  !
3813  ! -- gwf is upstream
3814  else
3815  hbar = squadratic0sp(hmaw, en, this%satomega)
3816  term = -drterm * this%satcond(jpos) * vscratio * (hgwf - hbar)
3817  dhbarterm = squadratic0spderivative(hmaw, en, this%satomega)
3818  term2 = cmaw * (done - dhbarterm)
3819  end if
3820  end if
3821  else
3822  !
3823  ! -- flow is not corrected, so calculate term for newton formulation
3824  if (inewton /= 0) then
3825  term = drterm * this%satcond(jpos) * vscratio * (hgwf - hmaw)
3826  end if
3827  end if
3828  !
3829  ! -- calculate flow relative to maw for fc and bd
3830  flow = dzero
3831  if (inewton == 0) then
3832  flow = term * (hgwf - hmaw) + cterm
3833  end if
3834  !
3835  ! -- add density part here
3836  if (this%idense /= 0 .and. inewton == 0) then
3837  call this%maw_calculate_density_exchange(jpos, hmaw, hgwf, cmaw, &
3838  bmaw, flow, term, cterm)
3839  end if
3840  !
3841  ! -- Return
3842  return
Here is the call graph for this function:

◆ maw_calculate_density_exchange()

subroutine mawmodule::maw_calculate_density_exchange ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  iconn,
real(dp), intent(in)  hmaw,
real(dp), intent(in)  hgwf,
real(dp), intent(in)  cond,
real(dp), intent(in)  bmaw,
real(dp), intent(inout)  flow,
real(dp), intent(inout)  hcofterm,
real(dp), intent(inout)  rhsterm 
)

Arguments are as follows: iconn : maw-gwf connection number hmaw : maw head hgwf : gwf head cond : conductance bmaw : bottom elevation of this connection flow : calculated flow, updated here with density terms, + into maw hcofterm : head coefficient term rhsterm : right-hand-side value, updated here with density terms

Member variable used here denseterms : shape (3, MAXBOUND), filled by buoyancy package col 1 is relative density of maw (densemaw / denseref) col 2 is relative density of gwf cell (densegwf / denseref) col 3 is elevation of gwf cell

Upon return, amat and rhs for maw row should be updated as: amat(idiag) = amat(idiag) - hcofterm rhs(n) = rhs(n) + rhsterm

Definition at line 4742 of file gwf-maw.f90.

4744  ! -- dummy
4745  class(MawType), intent(inout) :: this
4746  integer(I4B), intent(in) :: iconn
4747  real(DP), intent(in) :: hmaw
4748  real(DP), intent(in) :: hgwf
4749  real(DP), intent(in) :: cond
4750  real(DP), intent(in) :: bmaw
4751  real(DP), intent(inout) :: flow
4752  real(DP), intent(inout) :: hcofterm
4753  real(DP), intent(inout) :: rhsterm
4754  ! -- local
4755  real(DP) :: t
4756  real(DP) :: havg
4757  real(DP) :: rdensemaw
4758  real(DP) :: rdensegwf
4759  real(DP) :: rdenseavg
4760  real(DP) :: elevavg
4761  ! -- formats
4762  !
4763  ! -- assign relative density terms, return if zero which means not avail yet
4764  rdensemaw = this%denseterms(1, iconn)
4765  rdensegwf = this%denseterms(2, iconn)
4766  if (rdensegwf == dzero) return
4767  !
4768  ! -- update rhsterm with density contribution
4769  if (hmaw > bmaw .and. hgwf > bmaw) then
4770  !
4771  ! -- hmaw and hgwf both above bmaw
4772  rdenseavg = dhalf * (rdensemaw + rdensegwf)
4773  !
4774  ! -- update rhsterm with first density term
4775  t = cond * (rdenseavg - done) * (hgwf - hmaw)
4776  rhsterm = rhsterm + t
4777  flow = flow + t
4778  !
4779  ! -- update rhterm with second density term
4780  havg = dhalf * (hgwf + hmaw)
4781  elevavg = this%denseterms(3, iconn)
4782  t = cond * (havg - elevavg) * (rdensegwf - rdensemaw)
4783  rhsterm = rhsterm + t
4784  flow = flow + t
4785  else if (hmaw > bmaw) then
4786  !
4787  ! -- if only hmaw is above bmaw, then increase correction term by density
4788  t = (rdensemaw - done) * rhsterm
4789  rhsterm = rhsterm + t
4790  !
4791  else if (hgwf > bmaw) then
4792  !
4793  ! -- if only hgwf is above bmaw, then increase correction term by density
4794  t = (rdensegwf - done) * rhsterm
4795  rhsterm = rhsterm + t
4796  !
4797  else
4798  !
4799  ! -- Flow should be zero so do nothing
4800  end if
4801  !
4802  ! -- Return
4803  return

◆ maw_calculate_qpot()

subroutine mawmodule::maw_calculate_qpot ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  n,
real(dp), intent(inout)  qnet 
)
private

Definition at line 4015 of file gwf-maw.f90.

4016  use tdismodule, only: delt
4017  ! -- dummy
4018  class(MawType), intent(inout) :: this
4019  integer(I4B), intent(in) :: n
4020  real(DP), intent(inout) :: qnet
4021  ! -- local
4022  integer(I4B) :: j
4023  integer(I4B) :: jpos
4024  integer(I4B) :: igwfnode
4025  real(DP) :: bt
4026  real(DP) :: tp
4027  real(DP) :: scale
4028  real(DP) :: cfw
4029  real(DP) :: hdterm
4030  real(DP) :: sat
4031  real(DP) :: cmaw
4032  real(DP) :: hgwf
4033  real(DP) :: bmaw
4034  real(DP) :: h_temp
4035  real(DP) :: hv
4036  real(DP) :: vscratio
4037  ! -- format
4038  !
4039  ! -- initialize qnet and h_temp
4040  qnet = dzero
4041  vscratio = done
4042  h_temp = this%shutofflevel(n)
4043  !
4044  ! -- if vsc active, select appropriate viscosity ratio
4045  if (this%ivsc == 1) then
4046  ! flow out of well (flow is negative)
4047  if (qnet < 0) then
4048  vscratio = this%viscratios(1, igwfnode)
4049  else
4050  vscratio = this%viscratios(2, igwfnode)
4051  end if
4052  end if
4053  !
4054  ! -- calculate discharge to flowing wells
4055  if (this%iflowingwells > 0) then
4056  if (this%fwcond(n) > dzero) then
4057  bt = this%fwelev(n)
4058  tp = bt + this%fwrlen(n)
4059  scale = sqsaturation(tp, bt, h_temp)
4060  cfw = scale * this%fwcond(n) * this%viscratios(2, n)
4061  this%ifwdischarge(n) = 0
4062  if (cfw > dzero) then
4063  this%ifwdischarge(n) = 1
4064  this%xsto(n) = bt
4065  end if
4066  qnet = qnet + cfw * (bt - h_temp)
4067  end if
4068  end if
4069  !
4070  ! -- calculate maw storage changes
4071  if (this%imawiss /= 1) then
4072  if (this%ifwdischarge(n) /= 1) then
4073  hdterm = this%xoldsto(n) - h_temp
4074  else
4075  hdterm = this%xoldsto(n) - this%fwelev(n)
4076  end if
4077  qnet = qnet - (this%area(n) * hdterm / delt)
4078  end if
4079  !
4080  ! -- calculate inflow from aquifer
4081  do j = 1, this%ngwfnodes(n)
4082  jpos = this%get_jpos(n, j)
4083  igwfnode = this%get_gwfnode(n, j)
4084  call this%maw_calculate_saturation(n, j, igwfnode, sat)
4085  cmaw = this%satcond(jpos) * vscratio * sat
4086  hgwf = this%xnew(igwfnode)
4087  bmaw = this%botscrn(jpos)
4088  hv = h_temp
4089  if (hv < bmaw) then
4090  hv = bmaw
4091  end if
4092  if (hgwf < bmaw) then
4093  hgwf = bmaw
4094  end if
4095  qnet = qnet + cmaw * (hgwf - hv)
4096  end do
4097  !
4098  ! -- Return
4099  return
real(dp), pointer, public delt
length of the current time step
Definition: tdis.f90:29
Here is the call graph for this function:

◆ maw_calculate_satcond()

subroutine mawmodule::maw_calculate_satcond ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  i,
integer(i4b), intent(in)  j,
integer(i4b), intent(in)  node 
)

Definition at line 3461 of file gwf-maw.f90.

3462  ! -- dummy
3463  class(MawType), intent(inout) :: this
3464  integer(I4B), intent(in) :: i
3465  integer(I4B), intent(in) :: j
3466  integer(I4B), intent(in) :: node
3467  ! -- local
3468  integer(I4B) :: iTcontrastErr
3469  integer(I4B) :: jpos
3470  real(DP) :: c
3471  real(DP) :: k11
3472  real(DP) :: k22
3473  real(DP) :: sqrtk11k22
3474  real(DP) :: hks
3475  real(DP) :: area
3476  real(DP) :: eradius
3477  real(DP) :: topw
3478  real(DP) :: botw
3479  real(DP) :: tthkw
3480  real(DP) :: tthka
3481  real(DP) :: Tcontrast
3482  real(DP) :: skin
3483  real(DP) :: ravg
3484  real(DP) :: slen
3485  real(DP) :: pavg
3486  real(DP) :: gwfsat
3487  real(DP) :: gwftop
3488  real(DP) :: gwfbot
3489  real(DP) :: lc1
3490  real(DP) :: lc2
3491  real(DP) :: dx
3492  real(DP) :: dy
3493  real(DP) :: Txx
3494  real(DP) :: Tyy
3495  real(DP) :: T2pi
3496  real(DP) :: yx4
3497  real(DP) :: xy4
3498  ! -- formats
3499  !
3500  ! -- initialize conductance variables
3501  itcontrasterr = 0
3502  lc1 = dzero
3503  lc2 = dzero
3504  !
3505  ! -- calculate connection position
3506  jpos = this%get_jpos(i, j)
3507  !
3508  ! -- set K11 and K22
3509  k11 = this%gwfk11(node)
3510  if (this%gwfik22 == 0) then
3511  k22 = this%gwfk11(node)
3512  else
3513  k22 = this%gwfk22(node)
3514  end if
3515  sqrtk11k22 = sqrt(k11 * k22)
3516  !
3517  ! -- set gwftop, gwfbot, and gwfsat
3518  gwftop = this%dis%top(node)
3519  gwfbot = this%dis%bot(node)
3520  tthka = gwftop - gwfbot
3521  gwfsat = this%gwfsat(node)
3522  !
3523  ! -- set top and bottom of well screen
3524  c = dzero
3525  topw = this%topscrn(jpos)
3526  botw = this%botscrn(jpos)
3527  tthkw = topw - botw
3528  !
3529  ! -- scale screen thickness using gwfsat (for NPF Package THICKSTRT)
3530  if (gwftop == topw .and. gwfbot == botw) then
3531  if (this%icelltype(node) == 0) then
3532  tthkw = tthkw * gwfsat
3533  tthka = tthka * gwfsat
3534  end if
3535  end if
3536  !
3537  ! -- calculate the aquifer transmissivity (T2pi)
3538  t2pi = dtwopi * tthka * sqrtk11k22
3539  !
3540  ! -- calculate effective radius
3541  if (this%dis%ndim == 3 .and. this%ieffradopt /= 0) then
3542  txx = k11 * tthka
3543  tyy = k22 * tthka
3544  dx = sqrt(this%dis%area(node))
3545  dy = dx
3546  yx4 = (tyy / txx)**dquarter
3547  xy4 = (txx / tyy)**dquarter
3548  eradius = 0.28_dp * ((yx4 * dx)**dtwo + &
3549  (xy4 * dy)**dtwo)**dhalf / (yx4 + xy4)
3550  else
3551  area = this%dis%area(node)
3552  eradius = sqrt(area / (deight * dpi))
3553  end if
3554  !
3555  ! -- conductance calculations
3556  ! -- Thiem equation (1) and cumulative Thiem and skin equations (3)
3557  if (this%ieqn(i) == 1 .or. this%ieqn(i) == 3) then
3558  lc1 = log(eradius / this%radius(i)) / t2pi
3559  end if
3560  !
3561  ! -- skin equation (2) and cumulative Thiem and skin equations (3)
3562  if (this%ieqn(i) == 2 .or. this%ieqn(i) == 3) then
3563  hks = this%hk(jpos)
3564  if (tthkw * hks > dzero) then
3565  tcontrast = (sqrtk11k22 * tthka) / (hks * tthkw)
3566  skin = (tcontrast - done) * log(this%sradius(jpos) / this%radius(i))
3567  !
3568  ! -- trap invalid transmissvity contrast if using skin equation (2).
3569  ! Not trapped for cumulative Thiem and skin equations (3)
3570  ! because the MNW2 package allowed this condition (for
3571  ! backward compatibility with the MNW2 package for
3572  ! MODFLOW-2005, MODFLOW-NWT, and MODFLOW-USG).
3573  if (tcontrast <= 1 .and. this%ieqn(i) == 2) then
3574  itcontrasterr = 1
3575  write (errmsg, '(a,g0,a,1x,i0,1x,a,1x,i0,a,4(1x,a))') &
3576  'Invalid calculated transmissivity contrast (', tcontrast, &
3577  ') for maw well', i, 'connection', j, '.', 'This happens when the', &
3578  'skin transmissivity equals or exceeds the aquifer transmissivity.', &
3579  'Consider decreasing HK_SKIN for the connection or using the', &
3580  'CUMULATIVE or MEAN conductance equations.'
3581  call store_error(errmsg)
3582  else
3583  lc2 = skin / t2pi
3584  end if
3585  end if
3586  end if
3587  ! -- conductance using screen elevations, hk, well radius,
3588  ! and screen radius
3589  if (this%ieqn(i) == 4) then
3590  hks = this%hk(jpos)
3591  ravg = dhalf * (this%radius(i) + this%sradius(jpos))
3592  slen = this%sradius(jpos) - this%radius(i)
3593  pavg = dtwopi * ravg
3594  c = hks * pavg * tthkw / slen
3595  end if
3596  !
3597  ! -- calculate final conductance for Theim (1), Skin (2), and
3598  ! and cumulative Thiem and skin equations (3)
3599  if (this%ieqn(i) < 4) then
3600  if (lc1 + lc2 /= dzero) then
3601  c = done / (lc1 + lc2)
3602  else
3603  c = -dnodata
3604  end if
3605  end if
3606  !
3607  ! -- ensure that the conductance is not negative. Only write error message
3608  ! if error condition has not occurred for skin calculations (LC2)
3609  if (c < dzero .and. itcontrasterr == 0) then
3610  write (errmsg, '(a,g0,a,1x,i0,1x,a,1x,i0,a,4(1x,a))') &
3611  'Invalid calculated negative conductance (', c, &
3612  ') for maw well', i, 'connection', j, '.', 'this happens when the', &
3613  'skin transmissivity equals or exceeds the aquifer transmissivity.', &
3614  'consider decreasing hk_skin for the connection or using the', &
3615  'mean conductance equation.'
3616  call store_error(errmsg)
3617  end if
3618  !
3619  ! -- set saturated conductance
3620  this%satcond(jpos) = c
3621  !
3622  ! -- Return
3623  return
Here is the call graph for this function:

◆ maw_calculate_saturation()

subroutine mawmodule::maw_calculate_saturation ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  n,
integer(i4b), intent(in)  j,
integer(i4b), intent(in)  node,
real(dp), intent(inout)  sat 
)
private

Definition at line 3628 of file gwf-maw.f90.

3629  ! -- dummy
3630  class(MawType), intent(inout) :: this
3631  integer(I4B), intent(in) :: n
3632  integer(I4B), intent(in) :: j
3633  integer(I4B), intent(in) :: node
3634  real(DP), intent(inout) :: sat
3635  ! -- local
3636  integer(I4B) :: jpos
3637  real(DP) :: h_temp
3638  real(DP) :: hwell
3639  real(DP) :: topw
3640  real(DP) :: botw
3641  ! -- formats
3642  !
3643  ! -- initialize saturation
3644  sat = dzero
3645  !
3646  ! -- calculate current saturation for convertible cells
3647  if (this%icelltype(node) /= 0) then
3648  !
3649  ! -- set hwell
3650  hwell = this%xnewpak(n)
3651  !
3652  ! -- set connection position
3653  jpos = this%get_jpos(n, j)
3654  !
3655  ! -- set top and bottom of the well connection
3656  topw = this%topscrn(jpos)
3657  botw = this%botscrn(jpos)
3658  !
3659  ! -- calculate appropriate saturation
3660  if (this%inewton /= 1) then
3661  h_temp = this%xnew(node)
3662  if (h_temp < botw) then
3663  h_temp = botw
3664  end if
3665  if (hwell < botw) then
3666  hwell = botw
3667  end if
3668  h_temp = dhalf * (h_temp + hwell)
3669  else
3670  h_temp = this%xnew(node)
3671  if (hwell > h_temp) then
3672  h_temp = hwell
3673  end if
3674  if (h_temp < botw) then
3675  h_temp = botw
3676  end if
3677  end if
3678  ! -- calculate saturation
3679  sat = squadraticsaturation(topw, botw, h_temp, this%satomega)
3680  else
3681  sat = done
3682  end if
3683  !
3684  ! -- Return
3685  return
Here is the call graph for this function:

◆ maw_calculate_wellq()

subroutine mawmodule::maw_calculate_wellq ( class(mawtype this,
integer(i4b), intent(in)  n,
real(dp), intent(in)  hmaw,
real(dp), intent(inout)  q 
)
private

Definition at line 3847 of file gwf-maw.f90.

3848  ! -- dummy
3849  class(MawType) :: this
3850  integer(I4B), intent(in) :: n
3851  real(DP), intent(in) :: hmaw
3852  real(DP), intent(inout) :: q
3853  ! -- local
3854  real(DP) :: scale
3855  real(DP) :: tp
3856  real(DP) :: bt
3857  real(DP) :: rate
3858  real(DP) :: weight
3859  real(DP) :: dq
3860  !
3861  ! -- Initialize q
3862  q = dzero
3863  !
3864  ! -- Assign rate as the user-provided base pumping rate
3865  rate = this%rate(n)
3866  !
3867  ! -- Assign q differently depending on whether this is an extraction well
3868  ! (rate < 0) or an injection well (rate > 0).
3869  if (rate < dzero) then
3870  !
3871  ! -- If well shut off is activated, then turn off well if necessary,
3872  ! or if shut off is not activated then check to see if rate scaling
3873  ! is on.
3874  if (this%shutofflevel(n) /= dep20) then
3875  call this%maw_calculate_qpot(n, q)
3876  if (q < dzero) q = dzero
3877  if (q > -rate) q = -rate
3878 
3879  if (this%ishutoffcnt == 1) then
3880  this%shutoffweight(n) = done
3881  this%shutoffdq(n) = dzero
3882  this%shutoffqold(n) = q
3883  end if
3884 
3885  dq = q - this%shutoffqold(n)
3886  weight = this%shutoffweight(n)
3887  !
3888  ! -- for flip-flop condition, decrease factor
3889  if (this%shutoffdq(n) * dq < dzero) then
3890  weight = this%theta * this%shutoffweight(n)
3891  !
3892  ! -- when change is of same sign, increase factor
3893  else
3894  weight = this%shutoffweight(n) + this%kappa
3895  end if
3896  if (weight > done) weight = done
3897 
3898  q = this%shutoffqold(n) + weight * dq
3899 
3900  this%shutoffqold(n) = q
3901  this%shutoffdq(n) = dq
3902  this%shutoffweight(n) = weight
3903  !
3904  ! -- If shutoffmin and shutoffmax are specified then apply
3905  ! additional checks for when to shut off the well.
3906  if (this%shutoffmin(n) > dzero) then
3907  if (hmaw < this%shutofflevel(n)) then
3908  !
3909  ! -- calculate adjusted well rate subject to constraints
3910  ! -- well is shutoff
3911  if (this%ishutoff(n) /= 0) then
3912  q = dzero
3913  !
3914  ! --- well is not shut off
3915  else
3916  ! -- turn off well if q is less than the minimum rate and
3917  ! reset the ishutoff flag if at least on iteration 3
3918  if (q < this%shutoffmin(n)) then
3919  if (this%ishutoffcnt > 2) then
3920  this%ishutoff(n) = 1
3921  end if
3922  q = dzero
3923  !
3924  ! -- leave well on and use the specified rate
3925  ! or the potential rate
3926  end if
3927  end if
3928  !
3929  ! -- try to use the specified rate or the potential rate
3930  else
3931  if (q > this%shutoffmax(n)) then
3932  if (this%ishutoffcnt <= 2) then
3933  this%ishutoff(n) = 0
3934  end if
3935  end if
3936  if (this%ishutoff(n) /= 0) then
3937  q = dzero
3938  end if
3939  end if
3940  end if
3941 
3942  if (q /= dzero) q = -q
3943 
3944  else
3945  scale = done
3946  !
3947  ! -- Apply rate scaling by reducing pumpage when hmaw is less than the
3948  ! sum of maw pump elevation (pumpelev) and the specified reduction
3949  ! length. The rate will go to zero as hmaw drops to the pump
3950  ! elevation.
3951  if (this%reduction_length(n) /= dep20) then
3952  bt = this%pumpelev(n)
3953  tp = bt + this%reduction_length(n)
3954  scale = sqsaturation(tp, bt, hmaw)
3955  end if
3956  q = scale * rate
3957  end if
3958  !
3959  else
3960  !
3961  ! -- Handle the injection case (rate > 0) differently than extraction.
3962  q = rate
3963  if (this%shutofflevel(n) /= dep20) then
3964  call this%maw_calculate_qpot(n, q)
3965  q = -q
3966  if (q < dzero) q = dzero
3967  if (q > rate) q = rate
3968 
3969  if (this%ishutoffcnt == 1) then
3970  this%shutoffweight(n) = done
3971  this%shutoffdq(n) = dzero
3972  this%shutoffqold(n) = q
3973  end if
3974 
3975  dq = q - this%shutoffqold(n)
3976  weight = this%shutoffweight(n)
3977  !
3978  ! -- for flip-flop condition, decrease factor
3979  if (this%shutoffdq(n) * dq < dzero) then
3980  weight = this%theta * this%shutoffweight(n)
3981  !
3982  ! -- when change is of same sign, increase factor
3983  else
3984  weight = this%shutoffweight(n) + this%kappa
3985  end if
3986  if (weight > done) weight = done
3987 
3988  q = this%shutoffqold(n) + weight * dq
3989 
3990  this%shutoffqold(n) = q
3991  this%shutoffdq(n) = dq
3992  this%shutoffweight(n) = weight
3993 
3994  else
3995  scale = done
3996  !
3997  ! -- Apply rate scaling for an injection well by reducting the
3998  ! injection rate as hmaw rises above the pump elevation. The rate
3999  ! will approach zero as hmaw approaches pumpelev + reduction_length.
4000  if (this%reduction_length(n) /= dep20) then
4001  bt = this%pumpelev(n)
4002  tp = bt + this%reduction_length(n)
4003  scale = done - sqsaturation(tp, bt, hmaw)
4004  end if
4005  q = scale * rate
4006  end if
4007  end if
4008  !
4009  ! -- Return
4010  return
Here is the call graph for this function:

◆ maw_cf()

subroutine mawmodule::maw_cf ( class(mawtype this)

Skip if no multi-aquifer wells, otherwise, calculate hcof and rhs

Definition at line 2195 of file gwf-maw.f90.

2196  ! -- dummy
2197  class(MawType) :: this
2198  ! -- local
2199  !
2200  ! -- Calculate maw conductance and update package RHS and HCOF
2201  call this%maw_cfupdate()
2202  !
2203  ! -- Return
2204  return

◆ maw_cfupdate()

subroutine mawmodule::maw_cfupdate ( class(mawtype this)

Definition at line 4104 of file gwf-maw.f90.

4105  class(MawType) :: this
4106  ! -- dummy
4107  ! -- local
4108  integer(I4B) :: j
4109  integer(I4B) :: n
4110  integer(I4B) :: jpos
4111  integer(I4B) :: icflow
4112  integer(I4B) :: ibnd
4113  real(DP) :: flow
4114  real(DP) :: cmaw
4115  real(DP) :: hmaw
4116  real(DP) :: cterm
4117  real(DP) :: term
4118  !
4119  ! -- Return if no maw wells
4120  if (this%nbound .eq. 0) return
4121  !
4122  ! -- Update shutoff count
4123  this%ishutoffcnt = this%ishutoffcnt + 1
4124  !
4125  ! -- Calculate hcof and rhs for each maw entry
4126  ibnd = 1
4127  do n = 1, this%nmawwells
4128  hmaw = this%xnewpak(n)
4129  do j = 1, this%ngwfnodes(n)
4130  jpos = this%get_jpos(n, j)
4131  this%hcof(ibnd) = dzero
4132  this%rhs(ibnd) = dzero
4133  !
4134  ! -- set bound, hcof, and rhs components
4135  !
4136  ! -- use connection method so the gwf-maw budget flows
4137  ! are consistent with the maw-gwf budget flows
4138  if (this%iboundpak(n) == 0) then
4139  cmaw = dzero
4140  term = dzero
4141  cterm = dzero
4142  else
4143  call this%maw_calculate_conn_terms(n, j, icflow, cmaw, cterm, &
4144  term, flow)
4145  end if
4146  this%simcond(jpos) = cmaw
4147  this%bound(2, ibnd) = cmaw
4148  this%hcof(ibnd) = -term
4149  this%rhs(ibnd) = -term * hmaw + cterm
4150  !
4151  ! -- increment boundary number
4152  ibnd = ibnd + 1
4153  end do
4154  end do
4155  !
4156  ! -- Return
4157  return

◆ maw_check_attributes()

subroutine mawmodule::maw_check_attributes ( class(mawtype), intent(inout)  this)

Definition at line 1514 of file gwf-maw.f90.

1515  use simmodule, only: store_error
1516  ! -- dummy
1517  class(MawType), intent(inout) :: this
1518  ! -- local
1519  character(len=LINELENGTH) :: cgwfnode
1520  integer(I4B) :: idx
1521  integer(I4B) :: n
1522  integer(I4B) :: j
1523  integer(I4B) :: jpos
1524  ! -- formats
1525  !
1526  idx = 1
1527  do n = 1, this%nmawwells
1528  if (this%ngwfnodes(n) < 1) then
1529  call this%maw_set_attribute_error(n, 'NGWFNODES', 'must be greater '// &
1530  'than 0.')
1531  end if
1532  if (this%radius(n) == dep20) then
1533  call this%maw_set_attribute_error(n, 'RADIUS', 'has not been specified.')
1534  end if
1535  if (this%shutoffmin(n) > dzero) then
1536  if (this%shutoffmin(n) >= this%shutoffmax(n)) then
1537  call this%maw_set_attribute_error(n, 'SHUT_OFF', 'shutoffmax must '// &
1538  'be greater than shutoffmin.')
1539  end if
1540  end if
1541  do j = 1, this%ngwfnodes(n)
1542  !
1543  ! -- calculate jpos
1544  jpos = this%get_jpos(n, j)
1545  !
1546  ! -- write gwfnode number
1547  write (cgwfnode, '(a,i0,a)') 'gwfnode(', j, ')'
1548  !
1549  ! -- connection screen data
1550  if (this%botscrn(jpos) >= this%topscrn(jpos)) then
1551  call this%maw_set_attribute_error(n, 'SCREEN_TOP', 'screen bottom '// &
1552  'must be less than screen top. '// &
1553  trim(cgwfnode))
1554  end if
1555  !
1556  ! -- connection skin hydraulic conductivity
1557  if (this%ieqn(n) == 2 .OR. this%ieqn(n) == 3 .OR. &
1558  this%ieqn(n) == 4) then
1559  if (this%hk(jpos) <= dzero) then
1560  call this%maw_set_attribute_error(n, 'HK_SKIN', 'skin hyraulic '// &
1561  'conductivity must be greater '// &
1562  'than zero. '//trim(cgwfnode))
1563  end if
1564  else if (this%ieqn(n) == 0) then
1565  !
1566  ! -- saturated conductance
1567  if (this%satcond(jpos) < dzero) then
1568  call this%maw_set_attribute_error(n, 'HK_SKIN', &
1569  'skin hyraulic conductivity '// &
1570  'must be greater than or '// &
1571  'equal to zero when using '// &
1572  'SPECIFIED condeqn. '// &
1573  trim(cgwfnode))
1574  end if
1575  end if
1576  idx = idx + 1
1577  end do
1578  end do
1579  ! -- reset check_attr
1580  this%check_attr = 0
1581  ! -- Return
1582  return
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
Here is the call graph for this function:

◆ maw_cq()

subroutine mawmodule::maw_cq ( class(mawtype), intent(inout)  this,
real(dp), dimension(:), intent(in)  x,
real(dp), dimension(:), intent(inout), contiguous  flowja,
integer(i4b), intent(in), optional  iadv 
)
private

Definition at line 2572 of file gwf-maw.f90.

2573  ! -- modules
2574  use tdismodule, only: delt
2575  use constantsmodule, only: lenboundname
2576  use budgetmodule, only: budgettype
2577  ! -- dummy
2578  class(MawType), intent(inout) :: this
2579  real(DP), dimension(:), intent(in) :: x
2580  real(DP), dimension(:), contiguous, intent(inout) :: flowja
2581  integer(I4B), optional, intent(in) :: iadv
2582  ! -- local
2583  real(DP) :: rrate
2584  ! -- for budget
2585  integer(I4B) :: j
2586  integer(I4B) :: n
2587  integer(I4B) :: ibnd
2588  real(DP) :: hmaw
2589  real(DP) :: cfw
2590  ! -- for observations
2591  ! -- formats
2592  !
2593  ! -- recalculate package HCOF and RHS terms with latest groundwater and
2594  ! maw heads prior to calling base budget functionality
2595  call this%maw_cfupdate()
2596  !
2597  ! -- call base functionality in bnd_cq. This will calculate maw-gwf flows
2598  ! and put them into this%simvals
2599  call this%BndType%bnd_cq(x, flowja, iadv=1)
2600  !
2601  ! -- calculate maw budget flow and storage terms
2602  do n = 1, this%nmawwells
2603  this%qout(n) = dzero
2604  this%qsto(n) = dzero
2605  if (this%iflowingwells > 0) then
2606  this%qfw(n) = dzero
2607  end if
2608  if (this%iboundpak(n) == 0) then
2609  cycle
2610  end if
2611  !
2612  ! -- set hmaw and xsto
2613  hmaw = this%xnewpak(n)
2614  this%xsto(n) = hmaw
2615  !
2616  ! -- add pumping rate to active maw well
2617  rrate = this%ratesim(n)
2618  !
2619  ! -- If flow is out of maw set qout to rrate.
2620  if (rrate < dzero) then
2621  this%qout(n) = rrate
2622  end if
2623  !
2624  ! -- add flowing well
2625  if (this%iflowingwells > 0) then
2626  if (this%fwcond(n) > dzero) then
2627  cfw = this%fwcondsim(n)
2628  this%xsto(n) = this%fwelev(n)
2629  rrate = cfw * (this%fwelev(n) - hmaw)
2630  this%qfw(n) = rrate
2631  !
2632  ! -- Subtract flowing well rrate from qout.
2633  this%qout(n) = this%qout(n) + rrate
2634  end if
2635  end if
2636  !
2637  ! -- Calculate qsto
2638  if (this%imawiss /= 1) then
2639  rrate = -this%area(n) * (this%xsto(n) - this%xoldsto(n)) / delt
2640  this%qsto(n) = rrate
2641  end if
2642  end do
2643  !
2644  ! -- gwf and constant flow
2645  ibnd = 1
2646  do n = 1, this%nmawwells
2647  hmaw = this%xnewpak(n)
2648  this%qconst(n) = dzero
2649  do j = 1, this%ngwfnodes(n)
2650  rrate = -this%simvals(ibnd)
2651  this%qleak(ibnd) = rrate
2652  if (this%iboundpak(n) < 0) then
2653  this%qconst(n) = this%qconst(n) - rrate
2654  !
2655  ! -- If flow is out increment qout by -rrate.
2656  if (-rrate < dzero) then
2657  this%qout(n) = this%qout(n) - rrate
2658  end if
2659  end if
2660  !
2661  ! -- increment ibnd counter
2662  ibnd = ibnd + 1
2663  end do
2664  !
2665  ! -- add additional flow terms to constant head term
2666  if (this%iboundpak(n) < 0) then
2667  !
2668  ! -- add well pumping rate
2669  this%qconst(n) = this%qconst(n) - this%ratesim(n)
2670  !
2671  ! -- add flowing well rate
2672  if (this%iflowingwells > 0) then
2673  this%qconst(n) = this%qconst(n) - this%qfw(n)
2674  end if
2675  !
2676  ! -- add storage term
2677  if (this%imawiss /= 1) then
2678  this%qconst(n) = this%qconst(n) - this%qsto(n)
2679  end if
2680  end if
2681  end do
2682  !
2683  ! -- fill the budget object
2684  call this%maw_fill_budobj()
2685  !
2686  ! -- Return
2687  return
This module contains the BudgetModule.
Definition: Budget.f90:20
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:35
Derived type for the Budget object.
Definition: Budget.f90:39

◆ maw_create()

subroutine, public mawmodule::maw_create ( class(bndtype), pointer  packobj,
integer(i4b), intent(in)  id,
integer(i4b), intent(in)  ibcnum,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout,
character(len=*), intent(in)  namemodel,
character(len=*), intent(in)  pakname 
)

After creating the package object point bndobj to the new package

Definition at line 233 of file gwf-maw.f90.

234  ! -- dummy
235  class(BndType), pointer :: packobj
236  integer(I4B), intent(in) :: id
237  integer(I4B), intent(in) :: ibcnum
238  integer(I4B), intent(in) :: inunit
239  integer(I4B), intent(in) :: iout
240  character(len=*), intent(in) :: namemodel
241  character(len=*), intent(in) :: pakname
242  type(MawType), pointer :: mawobj
243  !
244  ! -- allocate the object and assign values to object variables
245  allocate (mawobj)
246  packobj => mawobj
247  !
248  ! -- create name and memory path
249  call packobj%set_names(ibcnum, namemodel, pakname, ftype)
250  packobj%text = text
251  !
252  ! -- allocate scalars
253  call mawobj%maw_allocate_scalars()
254  !
255  ! -- initialize package
256  call packobj%pack_initialize()
257  !
258  packobj%inunit = inunit
259  packobj%iout = iout
260  packobj%id = id
261  packobj%ibcnum = ibcnum
262  packobj%ncolbnd = 4
263  packobj%iscloc = 0 ! not supported
264  packobj%isadvpak = 1
265  packobj%ictMemPath = create_mem_path(namemodel, 'NPF')
266  !
267  ! -- Return
268  return
Here is the call graph for this function:
Here is the caller graph for this function:

◆ maw_da()

subroutine mawmodule::maw_da ( class(mawtype this)

Definition at line 2811 of file gwf-maw.f90.

2812  ! -- modules
2814  ! -- dummy
2815  class(MawType) :: this
2816  ! -- local
2817  !
2818  ! -- budobj
2819  call this%budobj%budgetobject_da()
2820  deallocate (this%budobj)
2821  nullify (this%budobj)
2822  !
2823  ! -- head table
2824  if (this%iprhed > 0) then
2825  call this%headtab%table_da()
2826  deallocate (this%headtab)
2827  nullify (this%headtab)
2828  end if
2829  !
2830  ! -- character arrays
2831  call mem_deallocate(this%cmawbudget, 'CMAWBUDGET', this%memoryPath)
2832  call mem_deallocate(this%cmawname, 'CMAWNAME', this%memoryPath)
2833  call mem_deallocate(this%status, 'STATUS', this%memoryPath)
2834  !
2835  ! -- deallocate well data pointers in memory manager
2836  call mem_deallocate(this%ngwfnodes)
2837  call mem_deallocate(this%ieqn)
2838  call mem_deallocate(this%ishutoff)
2839  call mem_deallocate(this%ifwdischarge)
2840  call mem_deallocate(this%strt)
2841  call mem_deallocate(this%radius)
2842  call mem_deallocate(this%area)
2843  call mem_deallocate(this%pumpelev)
2844  call mem_deallocate(this%bot)
2845  call mem_deallocate(this%ratesim)
2846  call mem_deallocate(this%reduction_length)
2847  call mem_deallocate(this%fwelev)
2848  call mem_deallocate(this%fwcond)
2849  call mem_deallocate(this%fwrlen)
2850  call mem_deallocate(this%fwcondsim)
2851  call mem_deallocate(this%xsto)
2852  call mem_deallocate(this%xoldsto)
2853  call mem_deallocate(this%shutoffmin)
2854  call mem_deallocate(this%shutoffmax)
2855  call mem_deallocate(this%shutofflevel)
2856  call mem_deallocate(this%shutoffweight)
2857  call mem_deallocate(this%shutoffdq)
2858  call mem_deallocate(this%shutoffqold)
2859  !
2860  ! -- timeseries aware variables
2861  call mem_deallocate(this%mauxvar)
2862  call mem_deallocate(this%rate)
2863  call mem_deallocate(this%well_head)
2864  !
2865  ! -- connection data
2866  call mem_deallocate(this%iaconn)
2867  call mem_deallocate(this%gwfnodes)
2868  call mem_deallocate(this%sradius)
2869  call mem_deallocate(this%hk)
2870  call mem_deallocate(this%satcond)
2871  call mem_deallocate(this%simcond)
2872  call mem_deallocate(this%topscrn)
2873  call mem_deallocate(this%botscrn)
2874  !
2875  ! -- imap vector
2876  call mem_deallocate(this%imap)
2877  call mem_deallocate(this%dbuff)
2878  call mem_deallocate(this%cauxcbc, 'CAUXCBC', this%memoryPath)
2879  call mem_deallocate(this%qauxcbc)
2880  call mem_deallocate(this%qleak)
2881  call mem_deallocate(this%qfw)
2882  call mem_deallocate(this%qout)
2883  call mem_deallocate(this%qsto)
2884  call mem_deallocate(this%qconst)
2885  call mem_deallocate(this%denseterms)
2886  call mem_deallocate(this%viscratios)
2887  call mem_deallocate(this%idxlocnode)
2888  call mem_deallocate(this%idxdglo)
2889  call mem_deallocate(this%idxoffdglo)
2890  call mem_deallocate(this%idxsymdglo)
2891  call mem_deallocate(this%idxsymoffdglo)
2892  call mem_deallocate(this%xoldpak)
2893  !
2894  ! -- nullify pointers
2895  call mem_deallocate(this%xnewpak, 'HEAD', this%memoryPath)
2896  !
2897  ! -- scalars
2898  call mem_deallocate(this%correct_flow)
2899  call mem_deallocate(this%iprhed)
2900  call mem_deallocate(this%iheadout)
2901  call mem_deallocate(this%ibudgetout)
2902  call mem_deallocate(this%ibudcsv)
2903  call mem_deallocate(this%iflowingwells)
2904  call mem_deallocate(this%imawiss)
2905  call mem_deallocate(this%imawissopt)
2906  call mem_deallocate(this%nmawwells)
2907  call mem_deallocate(this%check_attr)
2908  call mem_deallocate(this%ishutoffcnt)
2909  call mem_deallocate(this%ieffradopt)
2910  call mem_deallocate(this%ioutredflowcsv)
2911  call mem_deallocate(this%satomega)
2912  call mem_deallocate(this%bditems)
2913  call mem_deallocate(this%theta)
2914  call mem_deallocate(this%kappa)
2915  call mem_deallocate(this%cbcauxitems)
2916  call mem_deallocate(this%idense)
2917  !
2918  ! -- pointers to gwf variables
2919  nullify (this%gwfiss)
2920  !
2921  ! -- call standard BndType deallocate
2922  call this%BndType%bnd_da()
2923  !
2924  ! -- Return
2925  return

◆ maw_df_obs()

subroutine mawmodule::maw_df_obs ( class(mawtype this)
private

Overrides BndTypebnd_df_obs

Definition at line 3014 of file gwf-maw.f90.

3015  ! -- dummy
3016  class(MawType) :: this
3017  ! -- local
3018  integer(I4B) :: indx
3019  !
3020  ! -- Store obs type and assign procedure pointer
3021  ! for head observation type.
3022  call this%obs%StoreObsType('head', .false., indx)
3023  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3024  !
3025  ! -- Store obs type and assign procedure pointer
3026  ! for frommvr observation type.
3027  call this%obs%StoreObsType('from-mvr', .false., indx)
3028  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3029  !
3030  ! -- Store obs type and assign procedure pointer
3031  ! for conn-rate observation type.
3032  call this%obs%StoreObsType('maw', .true., indx)
3033  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3034  !
3035  ! -- Store obs type and assign procedure pointer
3036  ! for rate observation type.
3037  call this%obs%StoreObsType('rate', .true., indx)
3038  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3039  !
3040  ! -- Store obs type and assign procedure pointer
3041  ! for rate-to-mvr observation type.
3042  call this%obs%StoreObsType('rate-to-mvr', .true., indx)
3043  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3044  !
3045  ! -- Store obs type and assign procedure pointer
3046  ! for fw-rate observation type.
3047  call this%obs%StoreObsType('fw-rate', .true., indx)
3048  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3049  !
3050  ! -- Store obs type and assign procedure pointer
3051  ! for rate-to-mvr observation type.
3052  call this%obs%StoreObsType('fw-to-mvr', .true., indx)
3053  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3054  !
3055  ! -- Store obs type and assign procedure pointer
3056  ! for storage observation type.
3057  call this%obs%StoreObsType('storage', .true., indx)
3058  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3059  !
3060  ! -- Store obs type and assign procedure pointer
3061  ! for constant observation type.
3062  call this%obs%StoreObsType('constant', .true., indx)
3063  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3064  !
3065  ! -- Store obs type and assign procedure pointer
3066  ! for cond observation type.
3067  call this%obs%StoreObsType('conductance', .true., indx)
3068  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3069  !
3070  ! -- Store obs type and assign procedure pointer
3071  ! for fw-conductance observation type.
3072  call this%obs%StoreObsType('fw-conductance', .true., indx)
3073  this%obs%obsData(indx)%ProcessIdPtr => maw_process_obsid
3074  !
3075  ! -- Return
3076  return
Here is the call graph for this function:

◆ maw_fc()

subroutine mawmodule::maw_fc ( class(mawtype this,
real(dp), dimension(:), intent(inout)  rhs,
integer(i4b), dimension(:), intent(in)  ia,
integer(i4b), dimension(:), intent(in)  idxglo,
class(matrixbasetype), pointer  matrix_sln 
)
private

Definition at line 2209 of file gwf-maw.f90.

2210  ! -- modules
2211  use tdismodule, only: delt
2212  ! -- dummy
2213  class(MawType) :: this
2214  real(DP), dimension(:), intent(inout) :: rhs
2215  integer(I4B), dimension(:), intent(in) :: ia
2216  integer(I4B), dimension(:), intent(in) :: idxglo
2217  class(MatrixBaseType), pointer :: matrix_sln
2218  ! -- local
2219  integer(I4B) :: j
2220  integer(I4B) :: n
2221  integer(I4B) :: idx
2222  integer(I4B) :: iloc
2223  integer(I4B) :: isymloc
2224  integer(I4B) :: igwfnode
2225  integer(I4B) :: iposd
2226  integer(I4B) :: iposoffd
2227  integer(I4B) :: isymnode
2228  integer(I4B) :: ipossymd
2229  integer(I4B) :: ipossymoffd
2230  integer(I4B) :: jpos
2231  integer(I4B) :: icflow
2232  real(DP) :: hmaw
2233  real(DP) :: hgwf
2234  real(DP) :: cfw
2235  real(DP) :: cmaw
2236  real(DP) :: cterm
2237  real(DP) :: term
2238  real(DP) :: scale
2239  real(DP) :: tp
2240  real(DP) :: bt
2241  real(DP) :: rate
2242  real(DP) :: ratefw
2243  real(DP) :: flow
2244  !
2245  ! -- pakmvrobj fc
2246  if (this%imover == 1) then
2247  call this%pakmvrobj%fc()
2248  end if
2249  !
2250  ! -- Copy package rhs and hcof into solution rhs and amat
2251  idx = 1
2252  do n = 1, this%nmawwells
2253  iloc = this%idxlocnode(n)
2254  !
2255  ! -- update head value for constant head maw wells
2256  if (this%iboundpak(n) < 0) then
2257  this%xnewpak(n) = this%well_head(n)
2258  end if
2259  hmaw = this%xnewpak(n)
2260  !
2261  ! -- add pumping rate to active or constant maw well
2262  if (this%iboundpak(n) == 0) then
2263  this%ratesim(n) = dzero
2264  else
2265  call this%maw_calculate_wellq(n, hmaw, rate)
2266  this%ratesim(n) = rate
2267  rhs(iloc) = rhs(iloc) - rate
2268  !
2269  ! -- location of diagonal for maw row
2270  iposd = this%idxdglo(idx)
2271  !
2272  ! -- add flowing well
2273  this%xsto(n) = hmaw
2274  ratefw = dzero
2275  if (this%iflowingwells > 0) then
2276  if (this%fwcond(n) > dzero) then
2277  bt = this%fwelev(n)
2278  tp = bt + this%fwrlen(n)
2279  scale = sqsaturation(tp, bt, hmaw)
2280  cfw = scale * this%fwcond(n)
2281  this%ifwdischarge(n) = 0
2282  if (cfw > dzero) then
2283  this%ifwdischarge(n) = 1
2284  this%xsto(n) = bt
2285  end if
2286  this%fwcondsim(n) = cfw
2287  call matrix_sln%add_value_pos(iposd, -cfw)
2288  rhs(iloc) = rhs(iloc) - cfw * bt
2289  ratefw = cfw * (bt - hmaw)
2290  end if
2291  end if
2292  !
2293  ! -- add maw storage changes
2294  if (this%imawiss /= 1) then
2295  if (this%ifwdischarge(n) /= 1) then
2296  call matrix_sln%add_value_pos(iposd, -this%area(n) / delt)
2297  rhs(iloc) = rhs(iloc) - (this%area(n) * this%xoldsto(n) / delt)
2298  else
2299  cterm = this%xoldsto(n) - this%fwelev(n)
2300  rhs(iloc) = rhs(iloc) - (this%area(n) * cterm / delt)
2301  end if
2302  end if
2303  !
2304  ! -- If mover is active, add receiver water to rhs and
2305  ! store available water (as positive value)
2306  if (this%imover == 1) then
2307  rhs(iloc) = rhs(iloc) - this%pakmvrobj%get_qfrommvr(n)
2308  !
2309  ! -- add pumping rate to mover if not injection
2310  if (rate < 0) then
2311  call this%pakmvrobj%accumulate_qformvr(n, -rate) !pumped water
2312  end if
2313  !
2314  ! -- add flowing well flow to mover
2315  call this%pakmvrobj%accumulate_qformvr(n, -ratefw) !flowing water
2316  end if
2317  !
2318  end if
2319  !
2320  ! -- process each maw/gwf connection
2321  do j = 1, this%ngwfnodes(n)
2322  if (this%iboundpak(n) /= 0) then
2323  jpos = this%get_jpos(n, j)
2324  igwfnode = this%get_gwfnode(n, j)
2325  hgwf = this%xnew(igwfnode)
2326  !
2327  ! -- calculate connection terms
2328  call this%maw_calculate_conn_terms(n, j, icflow, cmaw, cterm, term, &
2329  flow)
2330  this%simcond(jpos) = cmaw
2331  !
2332  ! -- add to maw row
2333  iposd = this%idxdglo(idx)
2334  iposoffd = this%idxoffdglo(idx)
2335  call matrix_sln%add_value_pos(iposd, -term)
2336  call matrix_sln%set_value_pos(iposoffd, term)
2337  !
2338  ! -- add correction term
2339  rhs(iloc) = rhs(iloc) - cterm
2340  !
2341  ! -- add to gwf row for maw connection
2342  isymnode = this%get_gwfnode(n, j)
2343  isymloc = ia(isymnode)
2344  ipossymd = this%idxsymdglo(idx)
2345  ipossymoffd = this%idxsymoffdglo(idx)
2346  call matrix_sln%add_value_pos(ipossymd, -term)
2347  call matrix_sln%set_value_pos(ipossymoffd, term)
2348  !
2349  ! -- add correction term to gwf row
2350  rhs(isymnode) = rhs(isymnode) + cterm
2351  end if
2352  !
2353  ! -- increment maw connection counter
2354  idx = idx + 1
2355  end do
2356  end do
2357  !
2358  ! -- Return
2359  return
Here is the call graph for this function:

◆ maw_fill_budobj()

subroutine mawmodule::maw_fill_budobj ( class(mawtype this)

terms include a combination of the following: gwf rate [flowing_well] [storage] constant_flow [frommvr tomvr tomvrcf [tomvrfw]] [aux]

Definition at line 4369 of file gwf-maw.f90.

4370  ! -- modules
4371  ! -- dummy
4372  class(MawType) :: this
4373  ! -- local
4374  integer(I4B) :: naux
4375  integer(I4B) :: j
4376  integer(I4B) :: n
4377  integer(I4B) :: n2
4378  integer(I4B) :: jpos
4379  integer(I4B) :: idx
4380  integer(I4B) :: ibnd
4381  real(DP) :: q
4382  real(DP) :: tmaw
4383  real(DP) :: bmaw
4384  real(DP) :: sat
4385  real(DP) :: qfact
4386  real(DP) :: q2
4387  real(DP) :: b
4388  real(DP) :: v
4389  ! -- formats
4390  !
4391  ! -- initialize counter
4392  idx = 0
4393  !
4394  ! -- GWF (LEAKAGE) and connection surface area (aux)
4395  idx = idx + 1
4396  call this%budobj%budterm(idx)%reset(this%maxbound)
4397  ibnd = 1
4398  do n = 1, this%nmawwells
4399  do j = 1, this%ngwfnodes(n)
4400  jpos = this%get_jpos(n, j)
4401  n2 = this%get_gwfnode(n, j)
4402  tmaw = this%topscrn(jpos)
4403  bmaw = this%botscrn(jpos)
4404  call this%maw_calculate_saturation(n, j, n2, sat)
4405  this%qauxcbc(1) = dtwo * dpi * this%radius(n) * sat * (tmaw - bmaw)
4406  q = this%qleak(ibnd)
4407  call this%budobj%budterm(idx)%update_term(n, n2, q, this%qauxcbc)
4408  ibnd = ibnd + 1
4409  end do
4410  end do
4411  !
4412  ! -- RATE (WITHDRAWAL RATE)
4413  idx = idx + 1
4414  call this%budobj%budterm(idx)%reset(this%nmawwells)
4415  do n = 1, this%nmawwells
4416  q = this%ratesim(n)
4417  !
4418  ! -- adjust if well rate is an outflow
4419  if (this%imover == 1 .and. q < dzero) then
4420  qfact = done
4421  if (this%qout(n) < dzero) then
4422  qfact = q / this%qout(n)
4423  end if
4424  q = q + qfact * this%pakmvrobj%get_qtomvr(n)
4425  end if
4426  call this%budobj%budterm(idx)%update_term(n, n, q)
4427  end do
4428  !
4429  ! -- FLOWING WELL
4430  if (this%iflowingwells > 0) then
4431  idx = idx + 1
4432  call this%budobj%budterm(idx)%reset(this%nmawwells)
4433  do n = 1, this%nmawwells
4434  q = this%qfw(n)
4435  if (this%imover == 1) then
4436  qfact = done
4437  !
4438  ! -- adjust if well rate is an outflow
4439  if (this%qout(n) < dzero) then
4440  qfact = q / this%qout(n)
4441  end if
4442  q = q + qfact * this%pakmvrobj%get_qtomvr(n)
4443  end if
4444  call this%budobj%budterm(idx)%update_term(n, n, q)
4445  end do
4446  end if
4447  !
4448  ! -- STORAGE (AND VOLUME AS AUX)
4449  idx = idx + 1
4450  call this%budobj%budterm(idx)%reset(this%nmawwells)
4451  do n = 1, this%nmawwells
4452  b = this%xsto(n) - this%bot(n)
4453  if (b < dzero) then
4454  b = dzero
4455  end if
4456  v = this%area(n) * b
4457  if (this%imawissopt /= 1) then
4458  q = this%qsto(n)
4459  else
4460  q = dzero
4461  end if
4462  this%qauxcbc(1) = v
4463  call this%budobj%budterm(idx)%update_term(n, n, q, this%qauxcbc)
4464  end do
4465  !
4466  ! -- CONSTANT FLOW
4467  idx = idx + 1
4468  call this%budobj%budterm(idx)%reset(this%nmawwells)
4469  do n = 1, this%nmawwells
4470  q = this%qconst(n)
4471  !
4472  ! -- adjust if constant-flow rate is an outflow
4473  if (this%imover == 1 .and. q < dzero) then
4474  qfact = done
4475  if (this%qout(n) < dzero) then
4476  qfact = q / this%qout(n)
4477  end if
4478  q = q + qfact * this%pakmvrobj%get_qtomvr(n)
4479  end if
4480  call this%budobj%budterm(idx)%update_term(n, n, q)
4481  end do
4482  !
4483  ! -- MOVER
4484  if (this%imover == 1) then
4485  !
4486  ! -- FROM MOVER
4487  idx = idx + 1
4488  call this%budobj%budterm(idx)%reset(this%nmawwells)
4489  do n = 1, this%nmawwells
4490  if (this%iboundpak(n) == 0) then
4491  q = dzero
4492  else
4493  q = this%pakmvrobj%get_qfrommvr(n)
4494  end if
4495  call this%budobj%budterm(idx)%update_term(n, n, q)
4496  end do
4497  !
4498  ! -- RATE TO MOVER
4499  idx = idx + 1
4500  call this%budobj%budterm(idx)%reset(this%nmawwells)
4501  do n = 1, this%nmawwells
4502  q = this%pakmvrobj%get_qtomvr(n)
4503  if (q > dzero) then
4504  q = -q
4505  q2 = this%ratesim(n)
4506  !
4507  ! -- adjust TO MOVER if well rate is outflow
4508  if (q2 < dzero) then
4509  qfact = q2 / this%qout(n)
4510  q = q * qfact
4511  else
4512  q = dzero
4513  end if
4514  end if
4515  call this%budobj%budterm(idx)%update_term(n, n, q)
4516  end do
4517  !
4518  ! -- CONSTANT TO MOVER
4519  idx = idx + 1
4520  call this%budobj%budterm(idx)%reset(this%nmawwells)
4521  do n = 1, this%nmawwells
4522  q = this%pakmvrobj%get_qtomvr(n)
4523  if (q > dzero) then
4524  q = -q
4525  q2 = this%qconst(n)
4526  ! -- adjust TO MOVER if well rate is outflow
4527  if (q2 < dzero) then
4528  qfact = q2 / this%qout(n)
4529  q = q * qfact
4530  else
4531  q = dzero
4532  end if
4533  end if
4534  call this%budobj%budterm(idx)%update_term(n, n, q)
4535  end do
4536  !
4537  ! -- FLOWING WELL TO MOVER
4538  if (this%iflowingwells > 0) then
4539  idx = idx + 1
4540  call this%budobj%budterm(idx)%reset(this%nmawwells)
4541  do n = 1, this%nmawwells
4542  q = this%pakmvrobj%get_qtomvr(n)
4543  if (q > dzero) then
4544  q = -q
4545  q2 = this%ratesim(n)
4546  !
4547  ! -- adjust TO MOVER if well rate is outflow
4548  qfact = done
4549  if (this%qout(n) < dzero) then
4550  qfact = this%qfw(n) / this%qout(n)
4551  end if
4552  q = q * qfact
4553  end if
4554  call this%budobj%budterm(idx)%update_term(n, n, q)
4555  end do
4556  end if
4557 
4558  end if
4559  !
4560  ! -- AUXILIARY VARIABLES
4561  naux = this%naux
4562  if (naux > 0) then
4563  idx = idx + 1
4564  call this%budobj%budterm(idx)%reset(this%nmawwells)
4565  do n = 1, this%nmawwells
4566  q = dzero
4567  call this%budobj%budterm(idx)%update_term(n, n, q, this%auxvar(:, n))
4568  end do
4569  end if
4570  !
4571  ! --Terms are filled, now accumulate them for this time step
4572  call this%budobj%accumulate_terms()
4573  !
4574  ! -- Return
4575  return

◆ maw_fn()

subroutine mawmodule::maw_fn ( class(mawtype this,
real(dp), dimension(:), intent(inout)  rhs,
integer(i4b), dimension(:), intent(in)  ia,
integer(i4b), dimension(:), intent(in)  idxglo,
class(matrixbasetype), pointer  matrix_sln 
)

Definition at line 2364 of file gwf-maw.f90.

2365  ! -- dummy
2366  class(MawType) :: this
2367  real(DP), dimension(:), intent(inout) :: rhs
2368  integer(I4B), dimension(:), intent(in) :: ia
2369  integer(I4B), dimension(:), intent(in) :: idxglo
2370  class(MatrixBaseType), pointer :: matrix_sln
2371  ! -- local
2372  integer(I4B) :: j
2373  integer(I4B) :: n
2374  integer(I4B) :: idx
2375  integer(I4B) :: iloc
2376  integer(I4B) :: isymloc
2377  integer(I4B) :: igwfnode
2378  integer(I4B) :: iposd
2379  integer(I4B) :: iposoffd
2380  integer(I4B) :: isymnode
2381  integer(I4B) :: ipossymd
2382  integer(I4B) :: ipossymoffd
2383  integer(I4B) :: jpos
2384  integer(I4B) :: icflow
2385  real(DP) :: hmaw
2386  real(DP) :: hgwf
2387  real(DP) :: scale
2388  real(DP) :: tp
2389  real(DP) :: bt
2390  real(DP) :: cfw
2391  real(DP) :: rate
2392  real(DP) :: rate2
2393  real(DP) :: rterm
2394  real(DP) :: derv
2395  real(DP) :: drterm
2396  real(DP) :: cmaw
2397  real(DP) :: cterm
2398  real(DP) :: term
2399  real(DP) :: flow
2400  real(DP) :: term2
2401  real(DP) :: rhsterm
2402  !
2403  ! -- Calculate Newton-Raphson corrections
2404  idx = 1
2405  do n = 1, this%nmawwells
2406  iloc = this%idxlocnode(n)
2407  hmaw = this%xnewpak(n)
2408  !
2409  ! -- add pumping rate to active or constant maw well
2410  if (this%iboundpak(n) /= 0) then
2411  iposd = this%idxdglo(idx)
2412  scale = done
2413  drterm = dzero
2414  rate = this%ratesim(n)
2415  !
2416  !-- calculate final derivative for pumping rate
2417  call this%maw_calculate_wellq(n, hmaw + dem4, rate2)
2418  drterm = (rate2 - rate) / dem4
2419  !
2420  !-- fill amat and rhs with newton-raphson terms
2421  call matrix_sln%add_value_pos(iposd, drterm)
2422  rhs(iloc) = rhs(iloc) + drterm * hmaw
2423  !
2424  ! -- add flowing well
2425  if (this%iflowingwells > 0) then
2426  if (this%fwcond(n) > dzero) then
2427  bt = this%fwelev(n)
2428  tp = bt + this%fwrlen(n)
2429  scale = sqsaturation(tp, bt, hmaw)
2430  cfw = scale * this%fwcond(n)
2431  this%ifwdischarge(n) = 0
2432  if (cfw > dzero) then
2433  this%ifwdischarge(n) = 1
2434  end if
2435  this%fwcondsim(n) = cfw
2436  rate = cfw * (bt - hmaw)
2437  rterm = -cfw * hmaw
2438  !
2439  ! --calculate derivative for flowing well
2440  if (hmaw < tp) then
2441  derv = sqsaturationderivative(tp, bt, hmaw)
2442  drterm = -(cfw + this%fwcond(n) * derv * (hmaw - bt))
2443  !
2444  ! -- fill amat and rhs with newton-raphson terms
2445  call matrix_sln%add_value_pos(iposd, &
2446  -this%fwcond(n) * derv * (hmaw - bt))
2447  rhs(iloc) = rhs(iloc) - rterm + drterm * hmaw
2448  end if
2449  end if
2450  end if
2451  end if
2452  !
2453  ! -- process each maw/gwf connection
2454  do j = 1, this%ngwfnodes(n)
2455  if (this%iboundpak(n) /= 0) then
2456  jpos = this%get_jpos(n, j)
2457  igwfnode = this%get_gwfnode(n, j)
2458  hgwf = this%xnew(igwfnode)
2459  !
2460  ! -- add to maw row
2461  iposd = this%idxdglo(idx)
2462  iposoffd = this%idxoffdglo(idx)
2463  !
2464  ! -- add to gwf row for maw connection
2465  isymnode = this%get_gwfnode(n, j)
2466  isymloc = ia(isymnode)
2467  ipossymd = this%idxsymdglo(idx)
2468  ipossymoffd = this%idxsymoffdglo(idx)
2469  !
2470  ! -- calculate newton terms
2471  call this%maw_calculate_conn_terms(n, j, icflow, cmaw, cterm, term, &
2472  flow, term2)
2473  !
2474  ! -- maw is upstream
2475  if (hmaw > hgwf) then
2476  if (icflow /= 0) then
2477  rhsterm = term2 * hgwf + term * hmaw
2478  rhs(iloc) = rhs(iloc) + rhsterm
2479  rhs(isymnode) = rhs(isymnode) - rhsterm
2480  if (this%iboundpak(n) > 0) then
2481  call matrix_sln%add_value_pos(iposd, term)
2482  call matrix_sln%add_value_pos(iposoffd, term2)
2483  end if
2484  call matrix_sln%add_value_pos(ipossymd, -term2)
2485  call matrix_sln%add_value_pos(ipossymoffd, -term)
2486  else
2487  rhs(iloc) = rhs(iloc) + term * hmaw
2488  rhs(isymnode) = rhs(isymnode) - term * hmaw
2489  call matrix_sln%add_value_pos(iposd, term)
2490  if (this%ibound(igwfnode) > 0) then
2491  call matrix_sln%add_value_pos(ipossymoffd, -term)
2492  end if
2493  end if
2494  !
2495  ! -- gwf is upstream
2496  else
2497  if (icflow /= 0) then
2498  rhsterm = term2 * hmaw + term * hgwf
2499  rhs(iloc) = rhs(iloc) + rhsterm
2500  rhs(isymnode) = rhs(isymnode) - rhsterm
2501  if (this%iboundpak(n) > 0) then
2502  call matrix_sln%add_value_pos(iposd, term2)
2503  call matrix_sln%add_value_pos(iposoffd, term)
2504  end if
2505  call matrix_sln%add_value_pos(ipossymd, -term)
2506  call matrix_sln%add_value_pos(ipossymoffd, -term2)
2507  else
2508  rhs(iloc) = rhs(iloc) + term * hgwf
2509  rhs(isymnode) = rhs(isymnode) - term * hgwf
2510  if (this%iboundpak(n) > 0) then
2511  call matrix_sln%add_value_pos(iposoffd, term)
2512  end if
2513  call matrix_sln%add_value_pos(ipossymd, -term)
2514  end if
2515  end if
2516  end if
2517  !
2518  ! -- increment maw connection counter
2519  idx = idx + 1
2520  end do
2521  end do
2522  !
2523  ! -- Return
2524  return
Here is the call graph for this function:

◆ maw_mc()

subroutine mawmodule::maw_mc ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  moffset,
class(matrixbasetype), pointer  matrix_sln 
)

Definition at line 1620 of file gwf-maw.f90.

1621  use sparsemodule, only: sparsematrix
1623  ! -- dummy
1624  class(MawType), intent(inout) :: this
1625  integer(I4B), intent(in) :: moffset
1626  class(MatrixBaseType), pointer :: matrix_sln
1627  ! -- local
1628  integer(I4B) :: n
1629  integer(I4B) :: j
1630  integer(I4B) :: ii
1631  integer(I4B) :: iglo
1632  integer(I4B) :: jglo
1633  integer(I4B) :: ipos
1634  ! -- format
1635  !
1636  ! -- allocate connection mapping vectors
1637  call mem_allocate(this%idxlocnode, this%nmawwells, 'IDXLOCNODE', &
1638  this%memoryPath)
1639  call mem_allocate(this%idxdglo, this%maxbound, 'IDXDGLO', this%memoryPath)
1640  call mem_allocate(this%idxoffdglo, this%maxbound, 'IDXOFFDGLO', &
1641  this%memoryPath)
1642  call mem_allocate(this%idxsymdglo, this%maxbound, 'IDXSYMDGLO', &
1643  this%memoryPath)
1644  call mem_allocate(this%idxsymoffdglo, this%maxbound, 'IDXSYMOFFDGLO', &
1645  this%memoryPath)
1646  !
1647  ! -- Find the position of each connection in the global ia, ja structure
1648  ! and store them in idxglo. idxglo allows this model to insert or
1649  ! retrieve values into or from the global A matrix
1650  ! -- maw rows
1651  ipos = 1
1652  do n = 1, this%nmawwells
1653  iglo = moffset + this%dis%nodes + this%ioffset + n
1654  this%idxlocnode(n) = this%dis%nodes + this%ioffset + n
1655  do ii = 1, this%ngwfnodes(n)
1656  j = this%get_gwfnode(n, ii)
1657  jglo = j + moffset
1658  this%idxdglo(ipos) = matrix_sln%get_position_diag(iglo)
1659  this%idxoffdglo(ipos) = matrix_sln%get_position(iglo, jglo)
1660  ipos = ipos + 1
1661  end do
1662  end do
1663  ! -- maw contributions gwf portion of global matrix
1664  ipos = 1
1665  do n = 1, this%nmawwells
1666  do ii = 1, this%ngwfnodes(n)
1667  iglo = this%get_gwfnode(n, ii) + moffset
1668  jglo = moffset + this%dis%nodes + this%ioffset + n
1669  this%idxsymdglo(ipos) = matrix_sln%get_position_diag(iglo)
1670  this%idxsymoffdglo(ipos) = matrix_sln%get_position(iglo, jglo)
1671  ipos = ipos + 1
1672  end do
1673  end do
1674  !
1675  ! -- Return
1676  return

◆ maw_nur()

subroutine mawmodule::maw_nur ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  neqpak,
real(dp), dimension(neqpak), intent(inout)  x,
real(dp), dimension(neqpak), intent(in)  xtemp,
real(dp), dimension(neqpak), intent(inout)  dx,
integer(i4b), intent(inout)  inewtonur,
real(dp), intent(inout)  dxmax,
integer(i4b), intent(inout)  locmax 
)
private

Definition at line 2530 of file gwf-maw.f90.

2531  ! -- dummy
2532  class(MawType), intent(inout) :: this
2533  integer(I4B), intent(in) :: neqpak
2534  real(DP), dimension(neqpak), intent(inout) :: x
2535  real(DP), dimension(neqpak), intent(in) :: xtemp
2536  real(DP), dimension(neqpak), intent(inout) :: dx
2537  integer(I4B), intent(inout) :: inewtonur
2538  real(DP), intent(inout) :: dxmax
2539  integer(I4B), intent(inout) :: locmax
2540  ! -- local
2541  integer(I4B) :: n
2542  real(DP) :: botw
2543  real(DP) :: xx
2544  real(DP) :: dxx
2545  !
2546  ! -- Newton-Raphson under-relaxation
2547  do n = 1, this%nmawwells
2548  if (this%iboundpak(n) < 1) cycle
2549  botw = this%bot(n)
2550  !
2551  ! -- only apply Newton-Raphson under-relaxation if
2552  ! solution head is below the bottom of the well
2553  if (x(n) < botw) then
2554  inewtonur = 1
2555  xx = xtemp(n) * (done - dp9) + botw * dp9
2556  dxx = x(n) - xx
2557  if (abs(dxx) > abs(dxmax)) then
2558  locmax = n
2559  dxmax = dxx
2560  end if
2561  x(n) = xx
2562  dx(n) = dzero
2563  end if
2564  end do
2565  !
2566  ! -- return
2567  return

◆ maw_obs_supported()

logical function mawmodule::maw_obs_supported ( class(mawtype this)

Overrides BndTypebnd_obs_supported()

Definition at line 3001 of file gwf-maw.f90.

3002  class(MawType) :: this
3003  !
3004  maw_obs_supported = .true.
3005  !
3006  ! -- Return
3007  return

◆ maw_ot_bdsummary()

subroutine mawmodule::maw_ot_bdsummary ( class(mawtype this,
integer(i4b), intent(in)  kstp,
integer(i4b), intent(in)  kper,
integer(i4b), intent(in)  iout,
integer(i4b), intent(in)  ibudfl 
)
Parameters
thisMawType object
[in]kstptime step number
[in]kperperiod number
[in]ioutflag and unit number for the model listing file
[in]ibudflflag indicating budget should be written

Definition at line 2793 of file gwf-maw.f90.

2794  ! -- module
2795  use tdismodule, only: totim, delt
2796  ! -- dummy
2797  class(MawType) :: this !< MawType object
2798  integer(I4B), intent(in) :: kstp !< time step number
2799  integer(I4B), intent(in) :: kper !< period number
2800  integer(I4B), intent(in) :: iout !< flag and unit number for the model listing file
2801  integer(I4B), intent(in) :: ibudfl !< flag indicating budget should be written
2802  !
2803  call this%budobj%write_budtable(kstp, kper, iout, ibudfl, totim, delt)
2804  !
2805  ! -- Return
2806  return
real(dp), pointer, public totim
time relative to start of simulation
Definition: tdis.f90:32

◆ maw_ot_dv()

subroutine mawmodule::maw_ot_dv ( class(mawtype this,
integer(i4b), intent(in)  idvsave,
integer(i4b), intent(in)  idvprint 
)

Definition at line 2735 of file gwf-maw.f90.

2736  use tdismodule, only: kstp, kper, pertim, totim
2737  use constantsmodule, only: dhnoflo, dhdry
2738  use inputoutputmodule, only: ulasav
2739  class(MawType) :: this
2740  integer(I4B), intent(in) :: idvsave
2741  integer(I4B), intent(in) :: idvprint
2742  integer(I4B) :: ibinun
2743  integer(I4B) :: n
2744  real(DP) :: v
2745  real(DP) :: d
2746  !
2747  ! -- set unit number for binary dependent variable output
2748  ibinun = 0
2749  if (this%iheadout /= 0) then
2750  ibinun = this%iheadout
2751  end if
2752  if (idvsave == 0) ibinun = 0
2753  !
2754  ! -- write maw binary output
2755  if (ibinun > 0) then
2756  do n = 1, this%nmawwells
2757  v = this%xnewpak(n)
2758  d = v - this%bot(n)
2759  if (this%iboundpak(n) == 0) then
2760  v = dhnoflo
2761  else if (d <= dzero) then
2762  v = dhdry
2763  end if
2764  this%dbuff(n) = v
2765  end do
2766  call ulasav(this%dbuff, ' HEAD', &
2767  kstp, kper, pertim, totim, &
2768  this%nmawwells, 1, 1, ibinun)
2769  end if
2770  !
2771  ! -- write maw head table
2772  if (idvprint /= 0 .and. this%iprhed /= 0) then
2773  !
2774  ! -- set table kstp and kper
2775  call this%headtab%set_kstpkper(kstp, kper)
2776  !
2777  ! -- fill stage data
2778  do n = 1, this%nmawwells
2779  if (this%inamedbound == 1) then
2780  call this%headtab%add_term(this%cmawname(n))
2781  end if
2782  call this%headtab%add_term(n)
2783  call this%headtab%add_term(this%xnewpak(n))
2784  end do
2785  end if
2786  !
2787  ! -- Return
2788  return
real(dp), parameter dhdry
real dry cell constant
Definition: Constants.f90:93
real(dp), parameter dhnoflo
real no flow constant
Definition: Constants.f90:92
subroutine, public ulasav(buf, text, kstp, kper, pertim, totim, ncol, nrow, ilay, ichn)
Save 1 layer array on disk.
real(dp), pointer, public pertim
time relative to start of stress period
Definition: tdis.f90:30
Here is the call graph for this function:

◆ maw_ot_model_flows()

subroutine mawmodule::maw_ot_model_flows ( class(mawtype this,
integer(i4b), intent(in)  icbcfl,
integer(i4b), intent(in)  ibudfl,
integer(i4b), intent(in)  icbcun,
integer(i4b), dimension(:), intent(in), optional  imap 
)

Definition at line 2692 of file gwf-maw.f90.

2693  ! -- dummy
2694  class(MawType) :: this
2695  integer(I4B), intent(in) :: icbcfl
2696  integer(I4B), intent(in) :: ibudfl
2697  integer(I4B), intent(in) :: icbcun
2698  integer(I4B), dimension(:), optional, intent(in) :: imap
2699  !
2700  ! -- write the flows from the budobj
2701  call this%BndType%bnd_ot_model_flows(icbcfl, ibudfl, icbcun, this%imap)

◆ maw_ot_package_flows()

subroutine mawmodule::maw_ot_package_flows ( class(mawtype this,
integer(i4b), intent(in)  icbcfl,
integer(i4b), intent(in)  ibudfl 
)
private

Definition at line 2706 of file gwf-maw.f90.

2707  use tdismodule, only: kstp, kper, delt, pertim, totim
2708  class(MawType) :: this
2709  integer(I4B), intent(in) :: icbcfl
2710  integer(I4B), intent(in) :: ibudfl
2711  integer(I4B) :: ibinun
2712  !
2713  ! -- write the flows from the budobj
2714  ibinun = 0
2715  if (this%ibudgetout /= 0) then
2716  ibinun = this%ibudgetout
2717  end if
2718  if (icbcfl == 0) ibinun = 0
2719  if (ibinun > 0) then
2720  call this%budobj%save_flows(this%dis, ibinun, kstp, kper, delt, &
2721  pertim, totim, this%iout)
2722  end if
2723  !
2724  ! -- Print lake flows table
2725  if (ibudfl /= 0 .and. this%iprflow /= 0) then
2726  call this%budobj%write_flowtable(this%dis, kstp, kper)
2727  end if
2728  !
2729  ! -- Return
2730  return

◆ maw_process_obsid()

subroutine mawmodule::maw_process_obsid ( type(observetype), intent(inout)  obsrv,
class(disbasetype), intent(in)  dis,
integer(i4b), intent(in)  inunitobs,
integer(i4b), intent(in)  iout 
)

Definition at line 3352 of file gwf-maw.f90.

3353  ! -- dummy
3354  type(ObserveType), intent(inout) :: obsrv
3355  class(DisBaseType), intent(in) :: dis
3356  integer(I4B), intent(in) :: inunitobs
3357  integer(I4B), intent(in) :: iout
3358  ! -- local
3359  integer(I4B) :: nn1, nn2
3360  integer(I4B) :: icol, istart, istop
3361  character(len=LINELENGTH) :: string
3362  character(len=LENBOUNDNAME) :: bndname
3363  ! formats
3364  !
3365  string = obsrv%IDstring
3366  ! -- Extract multi-aquifer well number from string and store it.
3367  ! If 1st item is not an integer(I4B), it should be a
3368  ! maw name--deal with it.
3369  icol = 1
3370  ! -- get multi-aquifer well number or boundary name
3371  call extract_idnum_or_bndname(string, icol, istart, istop, nn1, bndname)
3372  if (nn1 == namedboundflag) then
3373  obsrv%FeatureName = bndname
3374  else
3375  if (obsrv%ObsTypeId == 'MAW' .or. &
3376  obsrv%ObsTypeId == 'CONDUCTANCE') then
3377  call extract_idnum_or_bndname(string, icol, istart, istop, nn2, bndname)
3378  if (len_trim(bndname) < 1 .and. nn2 < 0) then
3379  write (errmsg, '(a,1x,a,a,1x,a,1x,a)') &
3380  'For observation type', trim(adjustl(obsrv%ObsTypeId)), &
3381  ', ID given as an integer and not as boundname,', &
3382  'but ID2 (icon) is missing. Either change ID to valid', &
3383  'boundname or supply valid entry for ID2.'
3384  call store_error(errmsg)
3385  end if
3386  if (nn2 == namedboundflag) then
3387  obsrv%FeatureName = bndname
3388  ! -- reset nn1
3389  nn1 = nn2
3390  else
3391  obsrv%NodeNumber2 = nn2
3392  end if
3393  end if
3394  end if
3395  ! -- store multi-aquifer well number (NodeNumber)
3396  obsrv%NodeNumber = nn1
3397  !
3398  ! -- Return
3399  return
Here is the call graph for this function:
Here is the caller graph for this function:

◆ maw_read_dimensions()

subroutine mawmodule::maw_read_dimensions ( class(mawtype), intent(inout)  this)

Definition at line 1048 of file gwf-maw.f90.

1049  use constantsmodule, only: linelength
1050  ! -- dummy
1051  class(MawType), intent(inout) :: this
1052  ! -- local
1053  character(len=LENBOUNDNAME) :: keyword
1054  integer(I4B) :: ierr
1055  logical :: isfound, endOfBlock
1056  ! -- format
1057  !
1058  ! -- initialize dimensions to -1
1059  this%nmawwells = -1
1060  this%maxbound = -1
1061  !
1062  ! -- get dimensions block
1063  call this%parser%GetBlock('DIMENSIONS', isfound, ierr, &
1064  supportopenclose=.true.)
1065  !
1066  ! -- parse dimensions block if detected
1067  if (isfound) then
1068  write (this%iout, '(/1x,a)') &
1069  'PROCESSING '//trim(adjustl(this%text))//' DIMENSIONS'
1070  do
1071  call this%parser%GetNextLine(endofblock)
1072  if (endofblock) exit
1073  call this%parser%GetStringCaps(keyword)
1074  select case (keyword)
1075  case ('NMAWWELLS')
1076  this%nmawwells = this%parser%GetInteger()
1077  write (this%iout, '(4x,a,i0)') 'NMAWWELLS = ', this%nmawwells
1078  case default
1079  write (errmsg, '(3a)') &
1080  'Unknown '//trim(this%text)//' dimension: ', trim(keyword), '.'
1081  call store_error(errmsg)
1082  end select
1083  end do
1084  write (this%iout, '(1x,a)') &
1085  'END OF '//trim(adjustl(this%text))//' DIMENSIONS'
1086  else
1087  call store_error('Required dimensions block not found.', terminate=.true.)
1088  end if
1089  !
1090  ! -- verify dimensions were set correctly
1091  if (this%nmawwells < 0) then
1092  write (errmsg, '(a)') &
1093  'NMAWWELLS was not specified or was specified incorrectly.'
1094  call store_error(errmsg)
1095  end if
1096  !
1097  ! -- stop if errors were encountered in the DIMENSIONS block
1098  if (count_errors() > 0) then
1099  call this%parser%StoreErrorUnit()
1100  end if
1101  !
1102  ! -- read wells block
1103  call this%maw_read_wells()
1104  !
1105  ! -- read well_connections block
1106  call this%maw_read_well_connections()
1107  !
1108  ! -- Call define_listlabel to construct the list label that is written
1109  ! when PRINT_INPUT option is used.
1110  call this%define_listlabel()
1111  !
1112  ! -- setup the budget object
1113  call this%maw_setup_budobj()
1114  !
1115  ! -- setup the head table object
1116  call this%maw_setup_tableobj()
1117  !
1118  ! -- Return
1119  return
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:44
Here is the call graph for this function:

◆ maw_read_initial_attr()

subroutine mawmodule::maw_read_initial_attr ( class(mawtype), intent(inout)  this)

Definition at line 1124 of file gwf-maw.f90.

1125  ! -- modules
1126  use constantsmodule, only: linelength
1127  use memorymanagermodule, only: mem_setptr
1128  ! -- dummy
1129  class(MawType), intent(inout) :: this
1130  ! -- local
1131  character(len=LINELENGTH) :: title
1132  character(len=LINELENGTH) :: text
1133  integer(I4B) :: ntabcols
1134  integer(I4B) :: j
1135  integer(I4B) :: n
1136  integer(I4B) :: nn
1137  integer(I4B) :: jpos
1138  integer(I4B) :: inode
1139  integer(I4B) :: idx
1140  real(DP) :: k11
1141  real(DP) :: k22
1142  character(len=10), dimension(0:4) :: ccond
1143  character(len=30) :: nodestr
1144  ! -- data
1145  data ccond(0)/'SPECIFIED '/
1146  data ccond(1)/'THIEM '/
1147  data ccond(2)/'SKIN '/
1148  data ccond(3)/'CUMULATIVE'/
1149  data ccond(4)/'MEAN '/
1150  ! -- format
1151  character(len=*), parameter :: fmtwelln = &
1152  "(1X,//43X,'MULTI-AQUIFER WELL DATA'&
1153  &/1X,109('-'),&
1154  &/1X,7(A10,1X),A16)"
1155  character(len=*), parameter :: fmtwelld = &
1156  &"(1X,I10,1X,4(G10.3,1X),I10,1X,A10,1X,A16)"
1157  character(len=*), parameter :: fmtline = &
1158  &"(1X,119('-'),//)"
1159  character(len=*), parameter :: fmtwellcn = &
1160  "(1X,//37X,'MULTI-AQUIFER WELL CONNECTION DATA'&
1161  &/1X,119('-'),&
1162  &/1X,2(A10,1X),A20,7(A10,1X))"
1163  character(len=*), parameter :: fmtwellcd = &
1164  &"(1X,2(I10,1X),A20,1X,2(G10.3,1X),2(A10,1X),3(G10.3,1X))"
1165  !
1166  ! -- initialize xnewpak
1167  do n = 1, this%nmawwells
1168  this%xnewpak(n) = this%strt(n)
1169  this%xsto(n) = this%strt(n)
1170  end do
1171  !
1172  ! -- initialize status (iboundpak) of maw wells to active
1173  do n = 1, this%nmawwells
1174  select case (this%status(n))
1175  case ('CONSTANT')
1176  this%iboundpak(n) = -1
1177  case ('INACTIVE')
1178  this%iboundpak(n) = 0
1179  case ('ACTIVE')
1180  this%iboundpak(n) = 1
1181  end select
1182  end do
1183  !
1184  ! -- set imap and boundname for each connection
1185  if (this%inamedbound /= 0) then
1186  idx = 0
1187  do n = 1, this%nmawwells
1188  do j = 1, this%ngwfnodes(n)
1189  idx = idx + 1
1190  this%boundname(idx) = this%cmawname(n)
1191  this%imap(idx) = n
1192  end do
1193  end do
1194  else
1195  do n = 1, this%nmawwells
1196  this%cmawname(n) = ''
1197  end do
1198  end if
1199  !
1200  ! -- copy boundname into boundname_cst
1201  call this%copy_boundname()
1202  !
1203  ! -- set pointer to gwf iss and gwf hk
1204  call mem_setptr(this%gwfiss, 'ISS', create_mem_path(this%name_model))
1205  call mem_setptr(this%gwfk11, 'K11', create_mem_path(this%name_model, 'NPF'))
1206  call mem_setptr(this%gwfk22, 'K22', create_mem_path(this%name_model, 'NPF'))
1207  call mem_setptr(this%gwfik22, 'IK22', create_mem_path(this%name_model, 'NPF'))
1208  call mem_setptr(this%gwfsat, 'SAT', create_mem_path(this%name_model, 'NPF'))
1209  !
1210  ! -- qa data
1211  call this%maw_check_attributes()
1212  !
1213  ! -- Calculate the saturated conductance
1214  do n = 1, this%nmawwells
1215  !
1216  ! -- calculate saturated conductance only if CONDUCTANCE was not
1217  ! specified for each maw-gwf connection (CONDUCTANCE keyword).
1218  do j = 1, this%ngwfnodes(n)
1219  if (this%ieqn(n) /= 0) then
1220  inode = this%get_gwfnode(n, j)
1221  call this%maw_calculate_satcond(n, j, inode)
1222  end if
1223  end do
1224  end do
1225  !
1226  ! -- write summary of static well data
1227  ! -- write well data
1228  if (this%iprpak /= 0) then
1229  ntabcols = 7
1230  if (this%inamedbound /= 0) then
1231  ntabcols = ntabcols + 1
1232  end if
1233  title = trim(adjustl(this%text))//' PACKAGE ('// &
1234  trim(adjustl(this%packName))//') STATIC WELL DATA'
1235  call table_cr(this%inputtab, this%packName, title)
1236  call this%inputtab%table_df(this%nmawwells, ntabcols, this%iout)
1237  text = 'NUMBER'
1238  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1239  text = 'RADIUS'
1240  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1241  text = 'AREA'
1242  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1243  text = 'WELL BOTTOM'
1244  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1245  text = 'STARTING HEAD'
1246  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1247  text = 'NUMBER OF GWF NODES'
1248  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1249  text = 'CONDUCT. EQUATION'
1250  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1251  if (this%inamedbound /= 0) then
1252  text = 'NAME'
1253  call this%inputtab%initialize_column(text, 20, alignment=tableft)
1254  end if
1255  do n = 1, this%nmawwells
1256  call this%inputtab%add_term(n)
1257  call this%inputtab%add_term(this%radius(n))
1258  call this%inputtab%add_term(this%area(n))
1259  call this%inputtab%add_term(this%bot(n))
1260  call this%inputtab%add_term(this%strt(n))
1261  call this%inputtab%add_term(this%ngwfnodes(n))
1262  call this%inputtab%add_term(ccond(this%ieqn(n)))
1263  if (this%inamedbound /= 0) then
1264  call this%inputtab%add_term(this%cmawname(n))
1265  end if
1266  end do
1267  end if
1268  !
1269  ! -- write well connection data
1270  if (this%iprpak /= 0) then
1271  ntabcols = 10
1272  title = trim(adjustl(this%text))//' PACKAGE ('// &
1273  trim(adjustl(this%packName))//') STATIC WELL CONNECTION DATA'
1274  call table_cr(this%inputtab, this%packName, title)
1275  call this%inputtab%table_df(this%maxbound, ntabcols, this%iout)
1276  text = 'NUMBER'
1277  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1278  text = 'WELL CONNECTION'
1279  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1280  text = 'CELLID'
1281  call this%inputtab%initialize_column(text, 20, alignment=tableft)
1282  text = 'TOP OF SCREEN'
1283  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1284  text = 'BOTTOM OF SCREEN'
1285  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1286  text = 'SKIN RADIUS'
1287  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1288  text = 'SKIN K'
1289  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1290  text = 'K11'
1291  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1292  text = 'K22'
1293  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1294  text = 'SATURATED WELL CONDUCT.'
1295  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1296  !
1297  ! -- write the data to the table
1298  do n = 1, this%nmawwells
1299  do j = 1, this%ngwfnodes(n)
1300  call this%inputtab%add_term(n)
1301  call this%inputtab%add_term(j)
1302  jpos = this%get_jpos(n, j)
1303  nn = this%get_gwfnode(n, j)
1304  call this%dis%noder_to_string(nn, nodestr)
1305  call this%inputtab%add_term(nodestr)
1306  call this%inputtab%add_term(this%topscrn(jpos))
1307  call this%inputtab%add_term(this%botscrn(jpos))
1308  if (this%ieqn(n) == 2 .or. &
1309  this%ieqn(n) == 3 .or. &
1310  this%ieqn(n) == 4) then
1311  call this%inputtab%add_term(this%sradius(jpos))
1312  call this%inputtab%add_term(this%hk(jpos))
1313  else
1314  call this%inputtab%add_term(' ')
1315  call this%inputtab%add_term(' ')
1316  end if
1317  if (this%ieqn(n) == 1 .or. &
1318  this%ieqn(n) == 2 .or. &
1319  this%ieqn(n) == 3) then
1320  k11 = this%gwfk11(nn)
1321  if (this%gwfik22 == 0) then
1322  k22 = this%gwfk11(nn)
1323  else
1324  k22 = this%gwfk22(nn)
1325  end if
1326  call this%inputtab%add_term(k11)
1327  call this%inputtab%add_term(k22)
1328  else
1329  call this%inputtab%add_term(' ')
1330  call this%inputtab%add_term(' ')
1331  end if
1332  call this%inputtab%add_term(this%satcond(jpos))
1333  end do
1334  end do
1335  end if
1336  !
1337  ! -- finished with pointer to gwf hydraulic conductivity
1338  this%gwfk11 => null()
1339  this%gwfk22 => null()
1340  this%gwfik22 => null()
1341  this%gwfsat => null()
1342  !
1343  ! -- check for any error conditions
1344  if (count_errors() > 0) then
1345  call store_error_unit(this%inunit)
1346  end if
1347  !
1348  ! -- Return
1349  return
Here is the call graph for this function:

◆ maw_read_options()

subroutine mawmodule::maw_read_options ( class(mawtype), intent(inout)  this,
character(len=*), intent(inout)  option,
logical, intent(inout)  found 
)

Overrides BndTypebnd_options

Definition at line 1683 of file gwf-maw.f90.

1685  use openspecmodule, only: access, form
1687  ! -- dummy
1688  class(MawType), intent(inout) :: this
1689  character(len=*), intent(inout) :: option
1690  logical, intent(inout) :: found
1691  ! -- local
1692  character(len=MAXCHARLEN) :: fname, keyword
1693  ! -- formats
1694  character(len=*), parameter :: fmtflowingwells = &
1695  &"(4x, 'FLOWING WELLS WILL BE SIMULATED.')"
1696  character(len=*), parameter :: fmtshutdown = &
1697  &"(4x, 'SHUTDOWN ', a, ' VALUE (',g15.7,') SPECIFIED.')"
1698  character(len=*), parameter :: fmtnostoragewells = &
1699  &"(4x, 'WELL STORAGE WILL NOT BE SIMULATED.')"
1700  character(len=*), parameter :: fmtmawbin = &
1701  "(4x, 'MAW ', 1x, a, 1x, ' WILL BE SAVED TO FILE: ', a, /4x, &
1702  &'OPENED ON UNIT: ', I0)"
1703  !
1704  ! -- Check for 'FLOWING_WELLS' and set this%iflowingwells
1705  found = .true.
1706  select case (option)
1707  case ('PRINT_HEAD')
1708  this%iprhed = 1
1709  write (this%iout, '(4x,a)') &
1710  trim(adjustl(this%text))//' heads will be printed to listing file.'
1711  case ('HEAD')
1712  call this%parser%GetStringCaps(keyword)
1713  if (keyword == 'FILEOUT') then
1714  call this%parser%GetString(fname)
1715  this%iheadout = getunit()
1716  call openfile(this%iheadout, this%iout, fname, 'DATA(BINARY)', &
1717  form, access, 'REPLACE', mode_opt=mnormal)
1718  write (this%iout, fmtmawbin) 'HEAD', trim(adjustl(fname)), &
1719  this%iheadout
1720  else
1721  call store_error('Optional maw stage keyword must be '// &
1722  'followed by fileout.')
1723  end if
1724  case ('BUDGET')
1725  call this%parser%GetStringCaps(keyword)
1726  if (keyword == 'FILEOUT') then
1727  call this%parser%GetString(fname)
1728  this%ibudgetout = getunit()
1729  call openfile(this%ibudgetout, this%iout, fname, 'DATA(BINARY)', &
1730  form, access, 'REPLACE', mode_opt=mnormal)
1731  write (this%iout, fmtmawbin) 'BUDGET', trim(adjustl(fname)), &
1732  this%ibudgetout
1733  else
1734  call store_error('Optional maw budget keyword must be '// &
1735  'followed by fileout.')
1736  end if
1737  case ('BUDGETCSV')
1738  call this%parser%GetStringCaps(keyword)
1739  if (keyword == 'FILEOUT') then
1740  call this%parser%GetString(fname)
1741  this%ibudcsv = getunit()
1742  call openfile(this%ibudcsv, this%iout, fname, 'CSV', &
1743  filstat_opt='REPLACE')
1744  write (this%iout, fmtmawbin) 'BUDGET CSV', trim(adjustl(fname)), &
1745  this%ibudcsv
1746  else
1747  call store_error('OPTIONAL BUDGETCSV KEYWORD MUST BE FOLLOWED BY &
1748  &FILEOUT')
1749  end if
1750  case ('FLOWING_WELLS')
1751  this%iflowingwells = 1
1752  write (this%iout, fmtflowingwells)
1753  case ('SHUTDOWN_THETA')
1754  this%theta = this%parser%GetDouble()
1755  write (this%iout, fmtshutdown) 'THETA', this%theta
1756  case ('SHUTDOWN_KAPPA')
1757  this%kappa = this%parser%GetDouble()
1758  write (this%iout, fmtshutdown) 'KAPPA', this%kappa
1759  case ('MOVER')
1760  this%imover = 1
1761  write (this%iout, '(4x,A)') 'MOVER OPTION ENABLED'
1762  case ('NO_WELL_STORAGE')
1763  this%imawissopt = 1
1764  write (this%iout, fmtnostoragewells)
1765  case ('FLOW_CORRECTION')
1766  this%correct_flow = .true.
1767  write (this%iout, '(4x,a,/,4x,a)') &
1768  'MAW-GWF FLOW CORRECTIONS WILL BE APPLIED WHEN MAW HEADS ARE BELOW', &
1769  'OR GWF HEADS IN CONNECTED CELLS ARE BELOW THE CELL BOTTOM.'
1770  case ('MAW_FLOW_REDUCE_CSV')
1771  call this%parser%GetStringCaps(keyword)
1772  if (keyword == 'FILEOUT') then
1773  call this%parser%GetString(fname)
1774  call this%maw_redflow_csv_init(fname)
1775  else
1776  call store_error('OPTIONAL MAW_FLOW_REDUCE_CSV KEYWORD MUST BE &
1777  &FOLLOWED BY FILEOUT')
1778  end if
1779  !
1780  ! -- right now these are options that are only available in the
1781  ! development version and are not included in the documentation.
1782  ! These options are only available when IDEVELOPMODE in
1783  ! constants module is set to 1
1784  case ('DEV_PEACEMAN_EFFECTIVE_RADIUS')
1785  call this%parser%DevOpt()
1786  this%ieffradopt = 1
1787  write (this%iout, '(4x,a)') &
1788  'EFFECTIVE RADIUS FOR STRUCTURED GRIDS WILL BE CALCULATED &
1789  &USING PEACEMAN 1983'
1790  case default
1791  !
1792  ! -- No options found
1793  found = .false.
1794  end select
1795  !
1796  ! -- Return
1797  return
@ mnormal
normal output mode
Definition: Constants.f90:205
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:46
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.
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
Here is the call graph for this function:

◆ maw_read_well_connections()

subroutine mawmodule::maw_read_well_connections ( class(mawtype), intent(inout)  this)

Definition at line 800 of file gwf-maw.f90.

801  use constantsmodule, only: linelength
802  ! -- dummy
803  class(MawType), intent(inout) :: this
804  ! -- local
805  character(len=LINELENGTH) :: cellid
806  character(len=30) :: nodestr
807  logical :: isfound
808  logical :: endOfBlock
809  integer(I4B) :: ierr
810  integer(I4B) :: ival
811  integer(I4B) :: j
812  integer(I4B) :: jj
813  integer(I4B) :: n
814  integer(I4B) :: nn
815  integer(I4B) :: nn2
816  integer(I4B) :: ipos
817  integer(I4B) :: jpos
818  integer(I4B) :: ireset_scrntop
819  integer(I4B) :: ireset_scrnbot
820  integer(I4B) :: ireset_wellbot
821  real(DP) :: rval
822  real(DP) :: topnn
823  real(DP) :: botnn
824  real(DP) :: botw
825  integer(I4B), dimension(:), pointer, contiguous :: nboundchk
826  integer(I4B), dimension(:), pointer, contiguous :: iachk
827  !
828  ! -- initialize counters
829  ireset_scrntop = 0
830  ireset_scrnbot = 0
831  ireset_wellbot = 0
832  !
833  ! -- allocate and initialize local storage
834  allocate (iachk(this%nmawwells + 1))
835  iachk(1) = 1
836  do n = 1, this%nmawwells
837  iachk(n + 1) = iachk(n) + this%ngwfnodes(n)
838  end do
839  allocate (nboundchk(this%maxbound))
840  do n = 1, this%maxbound
841  nboundchk(n) = 0
842  end do
843  !
844  ! -- get well_connections block
845  call this%parser%GetBlock('CONNECTIONDATA', isfound, ierr, &
846  supportopenclose=.true.)
847  !
848  ! -- parse well_connections block if detected
849  if (isfound) then
850  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%text))// &
851  ' CONNECTIONDATA'
852  do
853  call this%parser%GetNextLine(endofblock)
854  if (endofblock) exit
855  !
856  ! -- well number
857  ival = this%parser%GetInteger()
858  n = ival
859  !
860  ! -- check for error condition
861  if (n < 1 .or. n > this%nmawwells) then
862  write (errmsg, '(a,1x,i0,a)') &
863  'IMAW must be greater than 0 and less than or equal to ', &
864  this%nmawwells, '.'
865  call store_error(errmsg)
866  cycle
867  end if
868  !
869  ! -- read connection number
870  ival = this%parser%GetInteger()
871  if (ival < 1 .or. ival > this%ngwfnodes(n)) then
872  write (errmsg, '(a,1x,i0,1x,a,1x,i0,a)') &
873  'JCONN for well ', n, &
874  'must be greater than 1 and less than or equal to ', &
875  this%ngwfnodes(n), '.'
876  call store_error(errmsg)
877  cycle
878  end if
879 
880  ipos = iachk(n) + ival - 1
881  nboundchk(ipos) = nboundchk(ipos) + 1
882 
883  j = ival
884  jpos = this%get_jpos(n, ival)
885  !
886  ! -- read gwfnodes from the line
887  call this%parser%GetCellid(this%dis%ndim, cellid)
888  nn = this%dis%noder_from_cellid(cellid, this%inunit, this%iout)
889  topnn = this%dis%top(nn)
890  botnn = this%dis%bot(nn)
891  botw = this%bot(n)
892  !
893  ! -- set gwf node number for connection
894  this%gwfnodes(jpos) = nn
895  !
896  ! -- top of screen
897  rval = this%parser%GetDouble()
898  if (this%ieqn(n) /= 4) then
899  rval = topnn
900  else
901  if (rval > topnn) then
902  ireset_scrntop = ireset_scrntop + 1
903  rval = topnn
904  end if
905  end if
906  this%topscrn(jpos) = rval
907  !
908  ! -- bottom of screen
909  rval = this%parser%GetDouble()
910  if (this%ieqn(n) /= 4) then
911  rval = botnn
912  else
913  if (rval < botnn) then
914  ireset_scrnbot = ireset_scrnbot + 1
915  rval = botnn
916  end if
917  end if
918  this%botscrn(jpos) = rval
919  !
920  ! -- adjust the bottom of the well for all conductance approaches
921  ! except for "mean"
922  if (rval < botw) then
923  if (this%ieqn(n) /= 4) then
924  ireset_wellbot = ireset_wellbot + 1
925  botw = rval
926  this%bot(n) = rval
927  else
928  write (errmsg, '(a,1x,i0,1x,a,1x,i0,1x,a,g0,a,g0,a)') &
929  'Screen bottom for maw well', n, 'connection', j, '(', &
930  this%botscrn(jpos), ') is less than the well bottom (', &
931  this%bot(n), ').'
932  call store_error(errmsg)
933  end if
934  end if
935  !
936  ! -- hydraulic conductivity or conductance
937  rval = this%parser%GetDouble()
938  if (this%ieqn(n) == 0) then
939  this%satcond(jpos) = rval
940  else if (this%ieqn(n) == 2 .OR. this%ieqn(n) == 3 .OR. &
941  this%ieqn(n) == 4) then
942  this%hk(jpos) = rval
943  end if
944  !
945  ! -- skin radius
946  rval = this%parser%GetDouble()
947  if (this%ieqn(n) == 2 .OR. this%ieqn(n) == 3 .OR. &
948  this%ieqn(n) == 4) then
949  this%sradius(jpos) = rval
950  if (this%sradius(jpos) <= this%radius(n)) then
951  write (errmsg, '(a,1x,i0,1x,a,1x,i0,1x,a,g0,a,g0,a)') &
952  'Screen radius for maw well', n, 'connection', j, '(', &
953  this%sradius(jpos), &
954  ') is less than or equal to the well radius (', &
955  this%radius(n), ').'
956  call store_error(errmsg)
957  end if
958  end if
959  end do
960  write (this%iout, '(1x,a)') &
961  'END OF '//trim(adjustl(this%text))//' CONNECTIONDATA'
962 
963  ipos = 0
964  do n = 1, this%nmawwells
965  do j = 1, this%ngwfnodes(n)
966  ipos = ipos + 1
967  !
968  ! -- check for missing or duplicate maw well connections
969  if (nboundchk(ipos) == 0) then
970  write (errmsg, '(a,1x,i0,1x,a,1x,i0,a)') &
971  'No data specified for maw well', n, 'connection', j, '.'
972  call store_error(errmsg)
973  else if (nboundchk(ipos) > 1) then
974  write (errmsg, '(a,1x,i0,1x,a,1x,i0,1x,a,1x,i0,1x,a)') &
975  'Data for maw well', n, 'connection', j, &
976  'specified', nboundchk(n), 'times.'
977  call store_error(errmsg)
978  end if
979  end do
980  end do
981  !
982  ! -- make sure that more than one connection per cell is only specified
983  ! wells using the mean conducance type
984  do n = 1, this%nmawwells
985  if (this%ieqn(n) /= 4) then
986  do j = 1, this%ngwfnodes(n)
987  nn = this%get_gwfnode(n, j)
988  do jj = 1, this%ngwfnodes(n)
989  !
990  ! -- skip current maw node
991  if (jj == j) then
992  cycle
993  end if
994  nn2 = this%get_gwfnode(n, jj)
995  if (nn2 == nn) then
996  call this%dis%noder_to_string(nn, nodestr)
997  write (errmsg, '(a,1x,i0,1x,a,1x,i0,3(1x,a))') &
998  'Only one connection can be specified for maw well', &
999  n, 'connection', j, 'to gwf cell', trim(adjustl(nodestr)), &
1000  'unless the mean condeqn is specified.'
1001  call store_error(errmsg)
1002  end if
1003  end do
1004  end do
1005  end if
1006  end do
1007  else
1008  call store_error('Required connectiondata block not found.')
1009  end if
1010  !
1011  ! -- deallocate local variable
1012  deallocate (iachk)
1013  deallocate (nboundchk)
1014  !
1015  ! -- add warning messages
1016  if (ireset_scrntop > 0) then
1017  write (warnmsg, '(a,1x,a,1x,a,1x,i0,1x,a)') &
1018  'The screen tops in multi-aquifer well package', trim(this%packName), &
1019  'were reset to the top of the connected cell', ireset_scrntop, 'times.'
1020  call store_warning(warnmsg)
1021  end if
1022  if (ireset_scrnbot > 0) then
1023  write (warnmsg, '(a,1x,a,1x,a,1x,i0,1x,a)') &
1024  'The screen bottoms in multi-aquifer well package', trim(this%packName), &
1025  'were reset to the bottom of the connected cell', ireset_scrnbot, &
1026  'times.'
1027  call store_warning(warnmsg)
1028  end if
1029  if (ireset_wellbot > 0) then
1030  write (warnmsg, '(a,1x,a,1x,a,1x,i0,1x,a)') &
1031  'The well bottoms in multi-aquifer well package', trim(this%packName), &
1032  'were reset to the bottom of the connected cell', ireset_wellbot, &
1033  'times.'
1034  call store_warning(warnmsg)
1035  end if
1036  !
1037  ! -- write summary of maw well_connection error messages
1038  if (count_errors() > 0) then
1039  call this%parser%StoreErrorUnit()
1040  end if
1041  !
1042  ! -- Return
1043  return
Here is the call graph for this function:

◆ maw_read_wells()

subroutine mawmodule::maw_read_wells ( class(mawtype), intent(inout)  this)

Definition at line 545 of file gwf-maw.f90.

546  use constantsmodule, only: linelength
548  ! -- dummy
549  class(MawType), intent(inout) :: this
550  ! -- local
551  character(len=LINELENGTH) :: text
552  character(len=LINELENGTH) :: keyword
553  character(len=LINELENGTH) :: cstr
554  character(len=LENBOUNDNAME) :: bndName
555  character(len=LENBOUNDNAME) :: bndNameTemp
556  character(len=9) :: cno
557  logical :: isfound
558  logical :: endOfBlock
559  integer(I4B) :: ival
560  integer(I4B) :: n
561  integer(I4B) :: j
562  integer(I4B) :: ii
563  integer(I4B) :: jj
564  integer(I4B) :: ieqn
565  integer(I4B) :: itmp
566  integer(I4B) :: ierr
567  integer(I4B) :: idx
568  real(DP) :: rval
569  real(DP), pointer :: bndElem => null()
570  ! -- local allocatable arrays
571  character(len=LINELENGTH), dimension(:), allocatable :: strttext
572  character(len=LENBOUNDNAME), dimension(:), allocatable :: nametxt
573  character(len=50), dimension(:, :), allocatable :: caux
574  integer(I4B), dimension(:), allocatable :: nboundchk
575  integer(I4B), dimension(:), allocatable :: wellieqn
576  integer(I4B), dimension(:), allocatable :: ngwfnodes
577  real(DP), dimension(:), allocatable :: radius
578  real(DP), dimension(:), allocatable :: bottom
579  ! -- format
580  character(len=*), parameter :: fmthdbot = &
581  "('well head (', G0, ') must be greater than or equal to the &
582  &BOTTOM_ELEVATION (', G0, ').')"
583  !
584  ! -- allocate and initialize temporary variables
585  allocate (strttext(this%nmawwells))
586  allocate (nametxt(this%nmawwells))
587  if (this%naux > 0) then
588  allocate (caux(this%naux, this%nmawwells))
589  end if
590  allocate (nboundchk(this%nmawwells))
591  allocate (wellieqn(this%nmawwells))
592  allocate (ngwfnodes(this%nmawwells))
593  allocate (radius(this%nmawwells))
594  allocate (bottom(this%nmawwells))
595  !
596  ! -- initialize temporary variables
597  do n = 1, this%nmawwells
598  nboundchk(n) = 0
599  end do
600  !
601  ! -- initialize itmp
602  itmp = 0
603  !
604  ! -- set npakeq to nmawwells
605  this%npakeq = this%nmawwells
606  !
607  ! -- read maw well data
608  ! -- get wells block
609  call this%parser%GetBlock('PACKAGEDATA', isfound, ierr, &
610  supportopenclose=.true.)
611  !
612  ! -- parse locations block if detected
613  if (isfound) then
614  write (this%iout, '(/1x,a)') &
615  'PROCESSING '//trim(adjustl(this%text))//' PACKAGEDATA'
616  do
617  call this%parser%GetNextLine(endofblock)
618  if (endofblock) exit
619  ival = this%parser%GetInteger()
620  n = ival
621 
622  if (n < 1 .or. n > this%nmawwells) then
623  write (errmsg, '(a,1x,i0,a)') &
624  'IMAW must be greater than 0 and less than or equal to', &
625  this%nmawwells, '.'
626  call store_error(errmsg)
627  cycle
628  end if
629  !
630  ! -- increment nboundchk
631  nboundchk(n) = nboundchk(n) + 1
632  !
633  ! -- radius
634  rval = this%parser%GetDouble()
635  if (rval <= dzero) then
636  write (errmsg, '(a,1x,i0,1x,a)') &
637  'Radius for well', n, 'must be greater than zero.'
638  call store_error(errmsg)
639  end if
640  radius(n) = rval
641  !
642  ! -- well bottom
643  bottom(n) = this%parser%GetDouble()
644  !
645  ! -- strt
646  call this%parser%GetString(strttext(n))
647  !
648  ! -- ieqn
649  call this%parser%GetStringCaps(keyword)
650  if (keyword == 'SPECIFIED') then
651  ieqn = 0
652  else if (keyword == 'THEIM' .or. keyword == 'THIEM') then
653  ieqn = 1
654  else if (keyword == 'SKIN') then
655  ieqn = 2
656  else if (keyword == 'CUMULATIVE') then
657  ieqn = 3
658  else if (keyword == 'MEAN') then
659  ieqn = 4
660  else
661  write (errmsg, '(a,1x,i0,1x,a)') &
662  'CONDEQN for well', n, &
663  "must be 'CUMULATIVE', 'THIEM', 'MEAN', or 'SKIN'."
664  end if
665  wellieqn(n) = ieqn
666  !
667  ! -- ngwnodes
668  ival = this%parser%GetInteger()
669  if (ival < 1) then
670  ival = 0
671  write (errmsg, '(a,1x,i0,1x,a)') &
672  'NGWFNODES for well', n, 'must be greater than zero.'
673  call store_error(errmsg)
674  end if
675 
676  if (ival > 0) then
677  ngwfnodes(n) = ival
678  end if
679  !
680  ! -- increment maxbound
681  itmp = itmp + ival
682  !
683  ! -- get aux data
684  do jj = 1, this%naux
685  call this%parser%GetString(caux(jj, n))
686  end do
687  !
688  ! -- set default bndName
689  write (cno, '(i9.9)') n
690  bndname = 'MAWWELL'//cno
691  !
692  ! -- read well name
693  if (this%inamedbound /= 0) then
694  call this%parser%GetStringCaps(bndnametemp)
695  if (bndnametemp /= '') then
696  bndname = bndnametemp
697  end if
698  end if
699  nametxt(n) = bndname
700  end do
701 
702  write (this%iout, '(1x,a)') &
703  'END OF '//trim(adjustl(this%text))//' PACKAGEDATA'
704  !
705  ! -- check for duplicate or missing wells
706  do n = 1, this%nmawwells
707  if (nboundchk(n) == 0) then
708  write (errmsg, '(a,1x,i0,a)') 'No data specified for maw well', n, '.'
709  call store_error(errmsg)
710  else if (nboundchk(n) > 1) then
711  write (errmsg, '(a,1x,i0,1x,a,1x,i0,1x,a)') &
712  'Data for maw well', n, 'specified', nboundchk(n), 'times.'
713  call store_error(errmsg)
714  end if
715  end do
716  else
717  call store_error('Required packagedata block not found.')
718  end if
719  !
720  ! -- terminate if any errors were detected
721  if (count_errors() > 0) then
722  call this%parser%StoreErrorUnit()
723  end if
724  !
725  ! -- set MAXBOUND
726  this%maxbound = itmp
727  write (this%iout, '(//4x,a,i7)') 'MAXBOUND = ', this%maxbound
728  !
729  ! -- allocate well and connection data
730  call this%maw_allocate_well_conn_arrays()
731  !
732  ! -- fill well data with data stored in temporary local arrays
733  do n = 1, this%nmawwells
734  rval = radius(n)
735  this%radius(n) = rval
736  this%area(n) = dpi * rval**dtwo
737  this%bot(n) = bottom(n)
738  this%ieqn(n) = wellieqn(n)
739  this%ngwfnodes(n) = ngwfnodes(n)
740  this%cmawname(n) = nametxt(n)
741  !
742  ! fill timeseries aware data
743  !
744  ! -- well_head and strt
745  jj = 1 ! For WELL_HEAD
746  bndelem => this%well_head(n)
747  call read_value_or_time_series_adv(strttext(n), n, jj, bndelem, &
748  this%packName, 'BND', this%tsManager, &
749  this%iprpak, 'WELL_HEAD')
750  !
751  ! -- set starting head value
752  this%strt(n) = this%well_head(n)
753  !
754  ! -- check for error condition
755  if (this%strt(n) < this%bot(n)) then
756  write (cstr, fmthdbot) this%strt(n), this%bot(n)
757  call this%maw_set_attribute_error(n, 'STRT', trim(cstr))
758  end if
759  !
760  ! -- fill aux data
761  do jj = 1, this%naux
762  text = caux(jj, n)
763  ii = n
764  bndelem => this%mauxvar(jj, ii)
765  call read_value_or_time_series_adv(text, ii, jj, bndelem, this%packName, &
766  'AUX', this%tsManager, this%iprpak, &
767  this%auxname(jj))
768  end do
769  end do
770  !
771  ! -- set iaconn and imap for each connection
772  idx = 0
773  this%iaconn(1) = 1
774  do n = 1, this%nmawwells
775  do j = 1, this%ngwfnodes(n)
776  idx = idx + 1
777  this%imap(idx) = n
778  end do
779  this%iaconn(n + 1) = idx + 1
780  end do
781  !
782  ! -- deallocate local storage
783  deallocate (strttext)
784  deallocate (nametxt)
785  if (this%naux > 0) then
786  deallocate (caux)
787  end if
788  deallocate (nboundchk)
789  deallocate (wellieqn)
790  deallocate (ngwfnodes)
791  deallocate (radius)
792  deallocate (bottom)
793  !
794  ! -- Return
795  return
subroutine, public read_value_or_time_series_adv(textInput, ii, jj, bndElem, pkgName, auxOrBnd, tsManager, iprpak, varName)
Call this subroutine from advanced packages to define timeseries link for a variable (varName).
Here is the call graph for this function:

◆ maw_redflow_csv_init()

subroutine mawmodule::maw_redflow_csv_init ( class(mawtype), intent(inout)  this,
character(len=*), intent(in)  fname 
)
private
Parameters
[in,out]thisMawType object

Definition at line 3407 of file gwf-maw.f90.

3408  ! -- dummy variables
3409  class(MawType), intent(inout) :: this !< MawType object
3410  character(len=*), intent(in) :: fname
3411  ! -- format
3412  character(len=*), parameter :: fmtredflowcsv = &
3413  "(4x, 'MAW REDUCED FLOW INFORMATION WILL BE SAVED TO FILE: ', a, /4x, &
3414  &'OPENED ON UNIT: ', I0)"
3415 
3416  this%ioutredflowcsv = getunit()
3417  call openfile(this%ioutredflowcsv, this%iout, fname, 'CSV', &
3418  filstat_opt='REPLACE')
3419  write (this%iout, fmtredflowcsv) trim(adjustl(fname)), &
3420  this%ioutredflowcsv
3421  write (this%ioutredflowcsv, '(a)') &
3422  'time,period,step,MAWnumber,rate-requested,rate-actual,maw-reduction'
3423  !
3424  ! -- Return
3425  return
Here is the call graph for this function:

◆ maw_redflow_csv_write()

subroutine mawmodule::maw_redflow_csv_write ( class(mawtype), intent(inout)  this)
private
Parameters
[in,out]thisMawType object

Definition at line 3430 of file gwf-maw.f90.

3431  ! -- modules
3432  use tdismodule, only: totim, kstp, kper
3433  ! -- dummy variables
3434  class(MawType), intent(inout) :: this !< MawType object
3435  ! -- local
3436  integer(I4B) :: n
3437  !integer(I4B) :: nodereduced
3438  !integer(I4B) :: nodeuser
3439  real(DP) :: v
3440  ! -- format
3441  do n = 1, this%nmawwells
3442  !
3443  ! -- test if node is constant or inactive
3444  if (this%status(n) .ne. 'ACTIVE') then
3445  cycle
3446  end if
3447  v = this%rate(n) - this%ratesim(n) !reductions in extraction will be negative and reductions in injection will be positive; follows convention of WEL AUTO_FLOW_REDUCE_CSV
3448  if (abs(v) > dem9) then !need to check absolute value of difference for both extraction and injection; using 1e-9 as epsilon value but could be tweaked
3449  write (this%ioutredflowcsv, '(*(G0,:,","))') &
3450  totim, kper, kstp, n, this%rate(n), this%ratesim(n), v
3451  end if
3452  end do
3453  !
3454  ! -- Return
3455  return

◆ maw_rp()

subroutine mawmodule::maw_rp ( class(mawtype), intent(inout)  this)
private

Read itmp and new boundaries if itmp > 0

Definition at line 1837 of file gwf-maw.f90.

1838  use constantsmodule, only: linelength
1839  use tdismodule, only: kper, nper
1840  ! -- dummy
1841  class(MawType), intent(inout) :: this
1842  ! -- local
1843  character(len=LINELENGTH) :: title
1844  character(len=LINELENGTH) :: line
1845  character(len=LINELENGTH) :: text
1846  character(len=16) :: csteady
1847  logical :: isfound
1848  logical :: endOfBlock
1849  integer(I4B) :: ierr
1850  integer(I4B) :: node
1851  integer(I4B) :: n
1852  integer(I4B) :: ntabcols
1853  integer(I4B) :: ntabrows
1854  integer(I4B) :: imaw
1855  integer(I4B) :: ibnd
1856  integer(I4B) :: j
1857  integer(I4B) :: jpos
1858  integer(I4B) :: iheadlimit_warning
1859  ! -- formats
1860  character(len=*), parameter :: fmtblkerr = &
1861  &"('Looking for BEGIN PERIOD iper. Found ', a, ' instead.')"
1862  character(len=*), parameter :: fmtlsp = &
1863  &"(1X,/1X,'REUSING ',A,'S FROM LAST STRESS PERIOD')"
1864  !
1865  ! -- initialize counters
1866  iheadlimit_warning = 0
1867  !
1868  ! -- set steady-state flag based on gwfiss
1869  this%imawiss = this%gwfiss
1870  !
1871  ! -- reset maw steady flag if 'STEADY-STATE' specified in the OPTIONS block
1872  if (this%imawissopt == 1) then
1873  this%imawiss = 1
1874  end if
1875  !
1876  ! -- set nbound to maxbound
1877  this%nbound = this%maxbound
1878  !
1879  ! -- Set ionper to the stress period number for which a new block of data
1880  ! will be read.
1881  if (this%inunit == 0) return
1882  !
1883  ! -- get stress period data
1884  if (this%ionper < kper) then
1885  !
1886  ! -- get period block
1887  call this%parser%GetBlock('PERIOD', isfound, ierr, &
1888  supportopenclose=.true., &
1889  blockrequired=.false.)
1890  if (isfound) then
1891  !
1892  ! -- read ionper and check for increasing period numbers
1893  call this%read_check_ionper()
1894  else
1895  !
1896  ! -- PERIOD block not found
1897  if (ierr < 0) then
1898  ! -- End of file found; data applies for remainder of simulation.
1899  this%ionper = nper + 1
1900  else
1901  ! -- Found invalid block
1902  call this%parser%GetCurrentLine(line)
1903  write (errmsg, fmtblkerr) adjustl(trim(line))
1904  call store_error(errmsg, terminate=.true.)
1905  end if
1906  end if
1907  end if
1908  !
1909  ! -- Read data if ionper == kper
1910  if (this%ionper == kper) then
1911  !
1912  ! -- setup table for period data
1913  if (this%iprpak /= 0) then
1914  !
1915  ! -- reset the input table object
1916  title = trim(adjustl(this%text))//' PACKAGE ('// &
1917  trim(adjustl(this%packName))//') DATA FOR PERIOD'
1918  write (title, '(a,1x,i6)') trim(adjustl(title)), kper
1919  call table_cr(this%inputtab, this%packName, title)
1920  call this%inputtab%table_df(1, 5, this%iout, finalize=.false.)
1921  text = 'NUMBER'
1922  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
1923  text = 'KEYWORD'
1924  call this%inputtab%initialize_column(text, 20, alignment=tableft)
1925  do n = 1, 3
1926  write (text, '(a,1x,i6)') 'VALUE', n
1927  call this%inputtab%initialize_column(text, 15, alignment=tabcenter)
1928  end do
1929  end if
1930  !
1931  ! -- set flag to check attributes
1932  this%check_attr = 1
1933  do
1934  call this%parser%GetNextLine(endofblock)
1935  if (endofblock) exit
1936 
1937  imaw = this%parser%GetInteger()
1938  if (imaw < 1 .or. imaw > this%nmawwells) then
1939  write (errmsg, '(2(a,1x),i0,a)') &
1940  'IMAW must be greater than 0 and', &
1941  'less than or equal to ', this%nmawwells, '.'
1942  call store_error(errmsg)
1943  cycle
1944  end if
1945  !
1946  ! -- set stress period data
1947  call this%maw_set_stressperiod(imaw, iheadlimit_warning)
1948  !
1949  ! -- write line to table
1950  if (this%iprpak /= 0) then
1951  call this%parser%GetCurrentLine(line)
1952  call this%inputtab%line_to_columns(line)
1953  end if
1954  end do
1955  if (this%iprpak /= 0) then
1956  call this%inputtab%finalize_table()
1957  end if
1958  !
1959  ! -- using data from the last stress period
1960  else
1961  write (this%iout, fmtlsp) trim(this%filtyp)
1962  end if
1963  !
1964  ! -- issue warning messages
1965  if (iheadlimit_warning > 0) then
1966  write (warnmsg, '(a,a,a,1x,a,1x,a)') &
1967  "HEAD_LIMIT in '", trim(this%packName), "' was below the well bottom", &
1968  "for one or more multi-aquifer well(s). This may result in", &
1969  "convergence failures for some models."
1970  call store_warning(warnmsg, substring=warnmsg(:50))
1971  end if
1972  !
1973  ! -- write summary of maw well stress period error messages
1974  if (count_errors() > 0) then
1975  call this%parser%StoreErrorUnit()
1976  end if
1977  !
1978  ! -- qa data if necessary
1979  if (this%check_attr /= 0) then
1980  call this%maw_check_attributes()
1981 
1982  ! -- write summary of stress period data for MAW
1983  if (this%iprpak == 1) then
1984  if (this%imawiss /= 0) then
1985  csteady = 'STEADY-STATE '
1986  else
1987  csteady = 'TRANSIENT '
1988  end if
1989  !
1990  ! -- reset the input table object for rate data
1991  title = trim(adjustl(this%text))//' PACKAGE ('// &
1992  trim(adjustl(this%packName))//') '//trim(adjustl(csteady))// &
1993  ' RATE DATA FOR PERIOD'
1994  write (title, '(a,1x,i6)') trim(adjustl(title)), kper
1995  ntabcols = 6
1996  call table_cr(this%inputtab, this%packName, title)
1997  call this%inputtab%table_df(this%nmawwells, ntabcols, this%iout)
1998  text = 'NUMBER'
1999  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
2000  text = 'STATUS'
2001  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2002  text = 'RATE'
2003  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2004  text = 'SPECIFIED HEAD'
2005  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2006  text = 'PUMP ELEVATION'
2007  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2008  text = 'REDUCTION LENGTH'
2009  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2010  do n = 1, this%nmawwells
2011  call this%inputtab%add_term(n)
2012  call this%inputtab%add_term(this%status(n))
2013  call this%inputtab%add_term(this%rate(n))
2014  if (this%iboundpak(n) < 0) then
2015  call this%inputtab%add_term(this%well_head(n))
2016  else
2017  call this%inputtab%add_term(' ')
2018  end if
2019  call this%inputtab%add_term(this%pumpelev(n))
2020  if (this%reduction_length(n) /= dep20) then
2021  call this%inputtab%add_term(this%reduction_length(n))
2022  else
2023  call this%inputtab%add_term(' ')
2024  end if
2025  end do
2026  !
2027  ! -- flowing wells
2028  if (this%iflowingwells > 0) then
2029  !
2030  ! -- reset the input table object for flowing well data
2031  title = trim(adjustl(this%text))//' PACKAGE ('// &
2032  trim(adjustl(this%packName))//') '//trim(adjustl(csteady))// &
2033  ' FLOWING WELL DATA FOR PERIOD'
2034  write (title, '(a,1x,i6)') trim(adjustl(title)), kper
2035  ntabcols = 4
2036  ntabrows = 0
2037  do n = 1, this%nmawwells
2038  if (this%fwcond(n) > dzero) then
2039  ntabrows = ntabrows + 1
2040  end if
2041  end do
2042  if (ntabrows > 0) then
2043  call table_cr(this%inputtab, this%packName, title)
2044  call this%inputtab%table_df(ntabrows, ntabcols, this%iout)
2045  text = 'NUMBER'
2046  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
2047  text = 'ELEVATION'
2048  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2049  text = 'CONDUCT.'
2050  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2051  text = 'REDUCTION LENGTH'
2052  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2053  do n = 1, this%nmawwells
2054  if (this%fwcond(n) > dzero) then
2055  call this%inputtab%add_term(n)
2056  call this%inputtab%add_term(this%fwelev(n))
2057  call this%inputtab%add_term(this%fwcond(n))
2058  call this%inputtab%add_term(this%fwrlen(n))
2059  end if
2060  end do
2061  end if
2062  end if
2063  !
2064  ! -- reset the input table object for shutoff data
2065  title = trim(adjustl(this%text))//' PACKAGE ('// &
2066  trim(adjustl(this%packName))//') '//trim(adjustl(csteady))// &
2067  ' WELL SHUTOFF DATA FOR PERIOD'
2068  write (title, '(a,1x,i6)') trim(adjustl(title)), kper
2069  ntabcols = 4
2070  ntabrows = 0
2071  do n = 1, this%nmawwells
2072  if (this%shutofflevel(n) /= dep20) then
2073  ntabrows = ntabrows + 1
2074  end if
2075  end do
2076  if (ntabrows > 0) then
2077  call table_cr(this%inputtab, this%packName, title)
2078  call this%inputtab%table_df(ntabrows, ntabcols, this%iout)
2079  text = 'NUMBER'
2080  call this%inputtab%initialize_column(text, 10, alignment=tabcenter)
2081  text = 'ELEVATION'
2082  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2083  text = 'MINIMUM. Q'
2084  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2085  text = 'MAXIMUM Q'
2086  call this%inputtab%initialize_column(text, 12, alignment=tabcenter)
2087  do n = 1, this%nmawwells
2088  if (this%shutofflevel(n) /= dep20) then
2089  call this%inputtab%add_term(n)
2090  call this%inputtab%add_term(this%shutofflevel(n))
2091  call this%inputtab%add_term(this%shutoffmin(n))
2092  call this%inputtab%add_term(this%shutoffmax(n))
2093  end if
2094  end do
2095  end if
2096  end if
2097  end if
2098  !
2099  ! -- fill arrays
2100  ibnd = 1
2101  do n = 1, this%nmawwells
2102  do j = 1, this%ngwfnodes(n)
2103  jpos = this%get_jpos(n, j)
2104  node = this%get_gwfnode(n, j)
2105  this%nodelist(ibnd) = node
2106  this%bound(1, ibnd) = this%xnewpak(n)
2107  this%bound(2, ibnd) = this%satcond(jpos)
2108  this%bound(3, ibnd) = this%botscrn(jpos)
2109  if (this%iboundpak(n) > 0) then
2110  this%bound(4, ibnd) = this%rate(n)
2111  else
2112  this%bound(4, ibnd) = dzero
2113  end if
2114  ibnd = ibnd + 1
2115  end do
2116  end do
2117  !
2118  ! -- Return
2119  return
integer(i4b), pointer, public nper
number of stress period
Definition: tdis.f90:21
Here is the call graph for this function:

◆ maw_rp_obs()

subroutine mawmodule::maw_rp_obs ( class(mawtype), intent(inout)  this)
private

Only done the first stress period since boundaries are fixed for the simulation

Definition at line 3221 of file gwf-maw.f90.

3222  use tdismodule, only: kper
3223  ! -- dummy
3224  class(MawType), intent(inout) :: this
3225  ! -- local
3226  integer(I4B) :: i
3227  integer(I4B) :: j
3228  integer(I4B) :: n
3229  integer(I4B) :: nn1
3230  integer(I4B) :: nn2
3231  integer(I4B) :: jj
3232  character(len=LENBOUNDNAME) :: bname
3233  logical :: jfound
3234  class(ObserveType), pointer :: obsrv => null()
3235  ! -- formats
3236 10 format('Boundary "', a, '" for observation "', a, &
3237  '" is invalid in package "', a, '"')
3238  !
3239  if (kper == 1) then
3240  do i = 1, this%obs%npakobs
3241  obsrv => this%obs%pakobs(i)%obsrv
3242  !
3243  ! -- get node number 1
3244  nn1 = obsrv%NodeNumber
3245  if (nn1 == namedboundflag) then
3246  bname = obsrv%FeatureName
3247  if (bname /= '') then
3248  ! -- Observation maw is based on a boundary name.
3249  ! Iterate through all multi-aquifer wells to identify and store
3250  ! corresponding index in bound array.
3251  jfound = .false.
3252  if (obsrv%ObsTypeId == 'MAW' .or. &
3253  obsrv%ObsTypeId == 'CONDUCTANCE') then
3254  do j = 1, this%nmawwells
3255  do jj = this%iaconn(j), this%iaconn(j + 1) - 1
3256  if (this%boundname(jj) == bname) then
3257  jfound = .true.
3258  call obsrv%AddObsIndex(jj)
3259  end if
3260  end do
3261  end do
3262  else
3263  do j = 1, this%nmawwells
3264  if (this%cmawname(j) == bname) then
3265  jfound = .true.
3266  call obsrv%AddObsIndex(j)
3267  end if
3268  end do
3269  end if
3270  if (.not. jfound) then
3271  write (errmsg, 10) &
3272  trim(bname), trim(obsrv%Name), trim(this%packName)
3273  call store_error(errmsg)
3274  end if
3275  end if
3276  else
3277  if (obsrv%indxbnds_count == 0) then
3278  if (obsrv%ObsTypeId == 'MAW' .or. &
3279  obsrv%ObsTypeId == 'CONDUCTANCE') then
3280  nn2 = obsrv%NodeNumber2
3281  j = this%iaconn(nn1) + nn2 - 1
3282  call obsrv%AddObsIndex(j)
3283  else
3284  call obsrv%AddObsIndex(nn1)
3285  end if
3286  else
3287  errmsg = 'Programming error in maw_rp_obs'
3288  call store_error(errmsg)
3289  end if
3290  end if
3291  !
3292  ! -- catch non-cumulative observation assigned to observation defined
3293  ! by a boundname that is assigned to more than one element
3294  if (obsrv%ObsTypeId == 'HEAD') then
3295  if (obsrv%indxbnds_count > 1) then
3296  write (errmsg, '(a,3(1x,a))') &
3297  trim(adjustl(obsrv%ObsTypeId)), &
3298  'for observation', trim(adjustl(obsrv%Name)), &
3299  'must be assigned to a multi-aquifer well with a unique boundname.'
3300  call store_error(errmsg)
3301  end if
3302  end if
3303  !
3304  ! -- check that index values are valid
3305  if (obsrv%ObsTypeId == 'MAW' .or. &
3306  obsrv%ObsTypeId == 'CONDUCTANCE') then
3307  do j = 1, obsrv%indxbnds_count
3308  nn1 = obsrv%indxbnds(j)
3309  n = this%imap(nn1)
3310  nn2 = nn1 - this%iaconn(n) + 1
3311  jj = this%iaconn(n + 1) - this%iaconn(n)
3312  if (nn1 < 1 .or. nn1 > this%maxbound) then
3313  write (errmsg, '(3(a,1x),i0,1x,a,i0,a)') &
3314  trim(adjustl(obsrv%ObsTypeId)), &
3315  'multi-aquifer well connection number must be greater than 0', &
3316  'and less than', jj, '(specified value is ', nn2, ').'
3317  call store_error(errmsg)
3318  end if
3319  end do
3320  else
3321  do j = 1, obsrv%indxbnds_count
3322  nn1 = obsrv%indxbnds(j)
3323  if (nn1 < 1 .or. nn1 > this%nmawwells) then
3324  write (errmsg, '(3(a,1x),i0,1x,a,i0,a)') &
3325  trim(adjustl(obsrv%ObsTypeId)), &
3326  'multi-aquifer well must be greater than 0 ', &
3327  'and less than or equal to', this%nmawwells, &
3328  '(specified value is ', nn1, ').'
3329  call store_error(errmsg)
3330  end if
3331  end do
3332  end if
3333  end do
3334  !
3335  ! -- evaluate if there are any observation errors
3336  if (count_errors() > 0) then
3337  call store_error_unit(this%inunit)
3338  end if
3339  end if
3340  !
3341  ! -- Return
3342  return
Here is the call graph for this function:

◆ maw_set_attribute_error()

subroutine mawmodule::maw_set_attribute_error ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  imaw,
character(len=*), intent(in)  keyword,
character(len=*), intent(in)  msg 
)

Definition at line 1489 of file gwf-maw.f90.

1490  use simmodule, only: store_error
1491  ! -- dummy
1492  class(MawType), intent(inout) :: this
1493  integer(I4B), intent(in) :: imaw
1494  character(len=*), intent(in) :: keyword
1495  character(len=*), intent(in) :: msg
1496  ! -- local
1497  ! -- formats
1498  !
1499  if (len(msg) == 0) then
1500  write (errmsg, '(a,1x,a,1x,i0,1x,a)') &
1501  keyword, ' for MAW well', imaw, 'has already been set.'
1502  else
1503  write (errmsg, '(a,1x,a,1x,i0,1x,a)') &
1504  keyword, ' for MAW well', imaw, msg
1505  end if
1506  call store_error(errmsg)
1507  !
1508  ! -- Return
1509  return
Here is the call graph for this function:

◆ maw_set_pointers()

subroutine mawmodule::maw_set_pointers ( class(mawtype this,
integer(i4b), pointer  neq,
integer(i4b), dimension(:), pointer, contiguous  ibound,
real(dp), dimension(:), pointer, contiguous  xnew,
real(dp), dimension(:), pointer, contiguous  xold,
real(dp), dimension(:), pointer, contiguous  flowja 
)
private

Definition at line 2958 of file gwf-maw.f90.

2959  ! -- modules
2961  ! -- dummy
2962  class(MawType) :: this
2963  integer(I4B), pointer :: neq
2964  integer(I4B), dimension(:), pointer, contiguous :: ibound
2965  real(DP), dimension(:), pointer, contiguous :: xnew
2966  real(DP), dimension(:), pointer, contiguous :: xold
2967  real(DP), dimension(:), pointer, contiguous :: flowja
2968  ! -- local
2969  integer(I4B) :: n
2970  integer(I4B) :: istart, iend
2971  !
2972  ! -- call base BndType set_pointers
2973  call this%BndType%set_pointers(neq, ibound, xnew, xold, flowja)
2974  !
2975  ! -- Set the MAW pointers
2976  !
2977  ! -- set package pointers
2978  istart = this%dis%nodes + this%ioffset + 1
2979  iend = istart + this%nmawwells - 1
2980  this%iboundpak => this%ibound(istart:iend)
2981  this%xnewpak => this%xnew(istart:iend)
2982  call mem_checkin(this%xnewpak, 'HEAD', this%memoryPath, 'X', &
2983  this%memoryPathModel)
2984  call mem_allocate(this%xoldpak, this%nmawwells, 'XOLDPAK', this%memoryPath)
2985  !
2986  ! -- initialize xnewpak
2987  do n = 1, this%nmawwells
2988  this%xnewpak(n) = dep20
2989  end do
2990  !
2991  ! -- Return
2992  return

◆ maw_set_stressperiod()

subroutine mawmodule::maw_set_stressperiod ( class(mawtype), intent(inout)  this,
integer(i4b), intent(in)  imaw,
integer(i4b), intent(inout)  iheadlimit_warning 
)

Definition at line 1354 of file gwf-maw.f90.

1355  ! -- modules
1357  ! -- dummy
1358  class(MawType), intent(inout) :: this
1359  integer(I4B), intent(in) :: imaw
1360  integer(I4B), intent(inout) :: iheadlimit_warning
1361  ! -- local
1362  character(len=LINELENGTH) :: errmsgr
1363  character(len=LINELENGTH) :: text
1364  character(len=LINELENGTH) :: cstr
1365  character(len=LINELENGTH) :: caux
1366  character(len=LINELENGTH) :: keyword
1367  integer(I4B) :: ii
1368  integer(I4B) :: jj
1369  real(DP) :: rval
1370  real(DP), pointer :: bndElem => null()
1371  integer(I4B) :: istat
1372  ! -- formats
1373  character(len=*), parameter :: fmthdbot = &
1374  &"('well head (',G0,') must be >= BOTTOM_ELEVATION (',G0, ').')"
1375  !
1376  ! -- read remainder of variables on the line
1377  call this%parser%GetStringCaps(keyword)
1378  select case (keyword)
1379  case ('STATUS')
1380  call this%parser%GetStringCaps(text)
1381  this%status(imaw) = text(1:8)
1382  select case (text)
1383  case ('CONSTANT')
1384  this%iboundpak(imaw) = -1
1385  case ('INACTIVE')
1386  this%iboundpak(imaw) = 0
1387  case ('ACTIVE')
1388  this%iboundpak(imaw) = 1
1389  case default
1390  write (errmsg, '(2a)') &
1391  'Unknown '//trim(this%text)//" maw status keyword: '", &
1392  trim(text)//"'."
1393  call store_error(errmsg)
1394  end select
1395  case ('RATE')
1396  call this%parser%GetString(text)
1397  jj = 1 ! For RATE
1398  bndelem => this%rate(imaw)
1399  call read_value_or_time_series_adv(text, imaw, jj, bndelem, &
1400  this%packName, 'BND', this%tsManager, &
1401  this%iprpak, 'RATE')
1402  case ('WELL_HEAD')
1403  call this%parser%GetString(text)
1404  jj = 1 ! For WELL_HEAD
1405  bndelem => this%well_head(imaw)
1406  call read_value_or_time_series_adv(text, imaw, jj, bndelem, &
1407  this%packName, 'BND', this%tsManager, &
1408  this%iprpak, 'WELL_HEAD')
1409  !
1410  ! -- set xnewpak to well_head
1411  this%xnewpak(imaw) = this%well_head(imaw)
1412  !
1413  ! -- check for error condition
1414  if (this%well_head(imaw) < this%bot(imaw)) then
1415  write (cstr, fmthdbot) &
1416  this%well_head(imaw), this%bot(imaw)
1417  call this%maw_set_attribute_error(imaw, 'WELL HEAD', trim(cstr))
1418  end if
1419  case ('FLOWING_WELL')
1420  this%fwelev(imaw) = this%parser%GetDouble()
1421  this%fwcond(imaw) = this%parser%GetDouble()
1422  this%fwrlen(imaw) = this%parser%GetDouble()
1423  !
1424  ! -- test for condition where flowing well data is specified but
1425  ! flowing_wells is not specified in the options block
1426  if (this%iflowingwells == 0) then
1427  this%iflowingwells = -1
1428  text = 'Flowing well data is specified in the '//trim(this%packName)// &
1429  ' package but FLOWING_WELL was not specified in the '// &
1430  'OPTIONS block.'
1431  call store_warning(text)
1432  end if
1433  case ('RATE_SCALING')
1434  rval = this%parser%GetDouble()
1435  this%pumpelev(imaw) = rval
1436  rval = this%parser%GetDouble()
1437  this%reduction_length(imaw) = rval
1438  if (rval < dzero) then
1439  call this%maw_set_attribute_error(imaw, trim(keyword), &
1440  'must be greater than or equal to 0.')
1441  end if
1442  case ('HEAD_LIMIT')
1443  call this%parser%GetString(text)
1444  if (trim(text) == 'OFF') then
1445  this%shutofflevel(imaw) = dep20
1446  else
1447  read (text, *, iostat=istat, iomsg=errmsgr) &
1448  this%shutofflevel(imaw)
1449  if (istat /= 0) then
1450  errmsg = 'Could not read HEAD_LIMIT value. '//trim(errmsgr)
1451  call store_error(errmsg)
1452  end if
1453  if (this%shutofflevel(imaw) <= this%bot(imaw)) then
1454  iheadlimit_warning = iheadlimit_warning + 1
1455  end if
1456  end if
1457  case ('SHUT_OFF')
1458  rval = this%parser%GetDouble()
1459  this%shutoffmin(imaw) = rval
1460  rval = this%parser%GetDouble()
1461  this%shutoffmax(imaw) = rval
1462  case ('AUXILIARY')
1463  call this%parser%GetStringCaps(caux)
1464  do jj = 1, this%naux
1465  if (trim(adjustl(caux)) /= trim(adjustl(this%auxname(jj)))) cycle
1466  call this%parser%GetString(text)
1467  ii = imaw
1468  bndelem => this%mauxvar(jj, ii)
1469  call read_value_or_time_series_adv(text, ii, jj, bndelem, &
1470  this%packName, 'AUX', &
1471  this%tsManager, this%iprpak, &
1472  this%auxname(jj))
1473  exit
1474  end do
1475  case default
1476  write (errmsg, '(2a)') &
1477  'Unknown '//trim(this%text)//" maw data keyword: '", &
1478  trim(keyword)//"'."
1479  call store_error(errmsg)
1480  end select
1481 
1482  !
1483  ! -- Return
1484  return
Here is the call graph for this function:

◆ maw_setup_budobj()

subroutine mawmodule::maw_setup_budobj ( class(mawtype this)
private

Definition at line 4164 of file gwf-maw.f90.

4165  ! -- modules
4166  use constantsmodule, only: lenbudtxt
4167  ! -- dummy
4168  class(MawType) :: this
4169  ! -- local
4170  integer(I4B) :: nbudterm
4171  integer(I4B) :: n, j, n2
4172  real(DP) :: q
4173  integer(I4B) :: maxlist, naux
4174  integer(I4B) :: idx
4175  character(len=LENBUDTXT) :: text
4176  character(len=LENBUDTXT), dimension(1) :: auxtxt
4177  !
4178  ! -- Determine the number of maw budget terms. These are fixed for
4179  ! the simulation and cannot change.
4180  ! gwf rate [flowing_well] storage constant_flow [frommvr tomvr tomvrcf [tomvrfw]] [aux]
4181  nbudterm = 4
4182  if (this%iflowingwells > 0) then
4183  nbudterm = nbudterm + 1
4184  end if
4185  if (this%imover == 1) then
4186  nbudterm = nbudterm + 3
4187  if (this%iflowingwells > 0) then
4188  nbudterm = nbudterm + 1
4189  end if
4190  end if
4191  if (this%naux > 0) nbudterm = nbudterm + 1
4192  !
4193  ! -- set up budobj
4194  call budgetobject_cr(this%budobj, this%packName)
4195  call this%budobj%budgetobject_df(this%nmawwells, nbudterm, 0, 0, &
4196  ibudcsv=this%ibudcsv)
4197  idx = 0
4198  !
4199  ! -- Go through and set up each budget term
4200  !
4201  ! --
4202  text = ' GWF'
4203  idx = idx + 1
4204  maxlist = this%maxbound
4205  naux = 1
4206  auxtxt(1) = ' FLOW-AREA'
4207  call this%budobj%budterm(idx)%initialize(text, &
4208  this%name_model, &
4209  this%packName, &
4210  this%name_model, &
4211  this%name_model, &
4212  maxlist, .false., .true., &
4213  naux, auxtxt)
4214  call this%budobj%budterm(idx)%reset(this%maxbound)
4215  q = dzero
4216  do n = 1, this%nmawwells
4217  do j = 1, this%ngwfnodes(n)
4218  n2 = this%get_gwfnode(n, j)
4219  call this%budobj%budterm(idx)%update_term(n, n2, q)
4220  end do
4221  end do
4222  !
4223  ! --
4224  text = ' RATE'
4225  idx = idx + 1
4226  maxlist = this%nmawwells
4227  naux = 0
4228  call this%budobj%budterm(idx)%initialize(text, &
4229  this%name_model, &
4230  this%packName, &
4231  this%name_model, &
4232  this%packName, &
4233  maxlist, .false., .false., &
4234  naux)
4235  !
4236  ! --
4237  if (this%iflowingwells > 0) then
4238  text = ' FW-RATE'
4239  idx = idx + 1
4240  maxlist = this%nmawwells
4241  naux = 0
4242  call this%budobj%budterm(idx)%initialize(text, &
4243  this%name_model, &
4244  this%packName, &
4245  this%name_model, &
4246  this%packName, &
4247  maxlist, .false., .false., &
4248  naux)
4249  end if
4250  !
4251  ! --
4252  text = ' STORAGE'
4253  idx = idx + 1
4254  maxlist = this%nmawwells
4255  naux = 1
4256  auxtxt(1) = ' VOLUME'
4257  call this%budobj%budterm(idx)%initialize(text, &
4258  this%name_model, &
4259  this%packName, &
4260  this%name_model, &
4261  this%name_model, &
4262  maxlist, .false., .true., &
4263  naux, auxtxt)
4264  !
4265  ! --
4266  text = ' CONSTANT'
4267  idx = idx + 1
4268  maxlist = this%nmawwells
4269  naux = 0
4270  call this%budobj%budterm(idx)%initialize(text, &
4271  this%name_model, &
4272  this%packName, &
4273  this%name_model, &
4274  this%packName, &
4275  maxlist, .false., .false., &
4276  naux)
4277  !
4278  ! --
4279  if (this%imover == 1) then
4280  !
4281  ! --
4282  text = ' FROM-MVR'
4283  idx = idx + 1
4284  maxlist = this%nmawwells
4285  naux = 0
4286  call this%budobj%budterm(idx)%initialize(text, &
4287  this%name_model, &
4288  this%packName, &
4289  this%name_model, &
4290  this%packName, &
4291  maxlist, .false., .false., &
4292  naux)
4293  !
4294  ! --
4295  text = ' RATE-TO-MVR'
4296  idx = idx + 1
4297  maxlist = this%nmawwells
4298  naux = 0
4299  call this%budobj%budterm(idx)%initialize(text, &
4300  this%name_model, &
4301  this%packName, &
4302  this%name_model, &
4303  this%packName, &
4304  maxlist, .false., .false., &
4305  naux)
4306  !
4307  ! -- constant-head flow to mover
4308  text = ' CONSTANT-TO-MVR'
4309  idx = idx + 1
4310  maxlist = this%nmawwells
4311  naux = 0
4312  call this%budobj%budterm(idx)%initialize(text, &
4313  this%name_model, &
4314  this%packName, &
4315  this%name_model, &
4316  this%packName, &
4317  maxlist, .false., .false., &
4318  naux)
4319  !
4320  ! -- flowing-well flow to mover
4321  if (this%iflowingwells > 0) then
4322  !
4323  ! --
4324  text = ' FW-RATE-TO-MVR'
4325  idx = idx + 1
4326  maxlist = this%nmawwells
4327  naux = 0
4328  call this%budobj%budterm(idx)%initialize(text, &
4329  this%name_model, &
4330  this%packName, &
4331  this%name_model, &
4332  this%packName, &
4333  maxlist, .false., .false., &
4334  naux)
4335  end if
4336  end if
4337  !
4338  ! -- auxiliary variable
4339  naux = this%naux
4340  if (naux > 0) then
4341  !
4342  ! --
4343  text = ' AUXILIARY'
4344  idx = idx + 1
4345  maxlist = this%maxbound
4346  call this%budobj%budterm(idx)%initialize(text, &
4347  this%name_model, &
4348  this%packName, &
4349  this%name_model, &
4350  this%packName, &
4351  maxlist, .false., .false., &
4352  naux, this%auxname)
4353  end if
4354  !
4355  ! -- if maw flow for each reach are written to the listing file
4356  if (this%iprflow /= 0) then
4357  call this%budobj%flowtable_df(this%iout)
4358  end if
4359  !
4360  ! -- Return
4361  return
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:36
Here is the call graph for this function:

◆ maw_setup_tableobj()

subroutine mawmodule::maw_setup_tableobj ( class(mawtype this)
private

The terms listed here must correspond in number and order to the ones written to the head table in the maw_ot method.

Definition at line 4583 of file gwf-maw.f90.

4584  ! -- modules
4586  ! -- dummy
4587  class(MawType) :: this
4588  ! -- local
4589  integer(I4B) :: nterms
4590  character(len=LINELENGTH) :: title
4591  character(len=LINELENGTH) :: text
4592  !
4593  ! -- setup well head table
4594  if (this%iprhed > 0) then
4595  !
4596  ! -- Determine the number of head table columns
4597  nterms = 2
4598  if (this%inamedbound == 1) nterms = nterms + 1
4599  !
4600  ! -- set up table title
4601  title = trim(adjustl(this%text))//' PACKAGE ('// &
4602  trim(adjustl(this%packName))//') HEADS FOR EACH CONTROL VOLUME'
4603  !
4604  ! -- set up head tableobj
4605  call table_cr(this%headtab, this%packName, title)
4606  call this%headtab%table_df(this%nmawwells, nterms, this%iout, &
4607  transient=.true.)
4608  !
4609  ! -- Go through and set up table budget term
4610  if (this%inamedbound == 1) then
4611  text = 'NAME'
4612  call this%headtab%initialize_column(text, 20, alignment=tableft)
4613  end if
4614  !
4615  ! -- reach number
4616  text = 'NUMBER'
4617  call this%headtab%initialize_column(text, 10, alignment=tabcenter)
4618  !
4619  ! -- reach stage
4620  text = 'HEAD'
4621  call this%headtab%initialize_column(text, 12, alignment=tabcenter)
4622  end if
4623  !
4624  ! -- Return
4625  return
Here is the call graph for this function:

Variable Documentation

◆ ftype

character(len=lenftype) mawmodule::ftype = 'MAW'

Definition at line 39 of file gwf-maw.f90.

39  character(len=LENFTYPE) :: ftype = 'MAW'

◆ text

character(len=lenpackagename) mawmodule::text = ' MAW'

Definition at line 40 of file gwf-maw.f90.

40  character(len=LENPACKAGENAME) :: text = ' MAW'