MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
swf.f90
Go to the documentation of this file.
1 !> @brief Surface Water Flow (SWF) Module
2 !<
3 module swfmodule
4 
5  use kindmodule, only: dp, i4b
9  use simvariablesmodule, only: errmsg
14  use swficmodule, only: swfictype
15  use swfdfwmodule, only: swfdfwtype
16  use swfcxsmodule, only: swfcxstype
17  use swfstomodule, only: swfstotype
19  use swfocmodule, only: swfoctype
20  use budgetmodule, only: budgettype
22 
23  implicit none
24 
25  private
26  public :: swfmodeltype
27 
28  type, abstract, extends(numericalmodeltype) :: swfmodeltype
29  type(swfictype), pointer :: ic => null() ! initial conditions package
30  type(swfdfwtype), pointer :: dfw => null() !< diffusive wave package
31  type(swfcxstype), pointer :: cxs => null() !< cross section package
32  type(swfstotype), pointer :: sto => null() !< storage package
33  type(swfobstype), pointer :: obs => null() ! observation package
34  type(swfoctype), pointer :: oc => null() !< output control package
35  type(budgettype), pointer :: budget => null() !< budget object
36  integer(I4B), pointer :: inic => null() ! unit number IC
37  integer(I4B), pointer :: indfw => null() !< unit number DFW
38  integer(I4B), pointer :: incxs => null() !< unit number CXS
39  integer(I4B), pointer :: insto => null() !< STO enabled flag
40  integer(I4B), pointer :: inobs => null() ! unit number OBS
41  integer(I4B), pointer :: inoc => null() !< unit number OC
42  integer(I4B), pointer :: iss => null() ! steady state flag
43  integer(I4B), pointer :: inewtonur => null() ! newton under relaxation flag
44  contains
45  procedure :: initialize
46  procedure :: allocate_scalars
47  procedure :: allocate_arrays
48  procedure :: model_df => swf_df
49  procedure :: model_ac => swf_ac
50  procedure :: model_mc => swf_mc
51  procedure :: model_ar => swf_ar
52  procedure :: model_rp => swf_rp
53  procedure :: model_ad => swf_ad
54  procedure :: model_nur => swf_nur
55  procedure :: model_cf => swf_cf
56  procedure :: model_fc => swf_fc
57  procedure :: model_cq => swf_cq
58  procedure :: model_bd => swf_bd
59  procedure :: model_ot => swf_ot
60  procedure :: model_da => swf_da
61  procedure :: model_bdentry => swf_bdentry
62  procedure :: swf_ot_obs
63  procedure :: swf_ot_flow
64  procedure :: swf_ot_dv
65  procedure :: swf_ot_bdsummary
66  procedure :: package_create
67  procedure :: ftype_check
68  procedure :: get_iasym => swf_get_iasym
69  procedure :: create_packages
70  procedure, private :: create_bndpkgs
71  !procedure :: log_namfile_options
72  procedure, private :: steady_period_check
73  end type swfmodeltype
74 
75  ! todo: these should be removed and entirely delegated to CHF and OLF
76  integer(I4B), parameter :: swf_nbasepkg = 9
77  integer(I4B), parameter :: swf_nmultipkg = 50
78  integer(I4B), parameter :: niunit_swf = swf_nbasepkg + swf_nmultipkg
79 
80 contains
81 
82  !> @brief Initialize common swf members
83  !<
84  subroutine initialize(this, modelftype, filename, id, modelname)
85  ! modules
87  ! dummy
88  class(swfmodeltype) :: this
89  character(len=*), intent(in) :: modelftype !< abbreviation for model type (CHF or OLF)
90  character(len=*), intent(in) :: filename !< input file
91  integer(I4B), intent(in) :: id !< consecutive model number listed in mfsim.nam
92  character(len=*), intent(in) :: modelname !< name of the model
93  ! local
94 
95  ! Set memory path before allocation in memory manager can be done
96  this%memoryPath = create_mem_path(modelname)
97 
98  ! allocate scalars
99  call this%allocate_scalars(modelname)
100 
101  ! Assign values
102  this%filename = filename
103  this%name = modelname
104  this%macronym = trim(modelftype)
105  this%id = id
106 
107  end subroutine initialize
108 
109  !> @brief Allocate memory for scalar members
110  !<
111  subroutine allocate_scalars(this, modelname)
112  ! modules
113  ! dummy
114  class(swfmodeltype) :: this
115  character(len=*), intent(in) :: modelname
116 
117  ! allocate members from parent class
118  call this%NumericalModelType%allocate_scalars(modelname)
119 
120  ! allocate members that are part of model class
121  call mem_allocate(this%inic, 'INIC', this%memoryPath)
122  call mem_allocate(this%indfw, 'INDFW', this%memoryPath)
123  call mem_allocate(this%incxs, 'INCXS', this%memoryPath)
124  call mem_allocate(this%insto, 'INSTO', this%memoryPath)
125  call mem_allocate(this%inobs, 'INOBS', this%memoryPath)
126  call mem_allocate(this%inoc, 'INOC', this%memoryPath)
127  call mem_allocate(this%iss, 'ISS', this%memoryPath)
128  call mem_allocate(this%inewtonur, 'INEWTONUR', this%memoryPath)
129 
130  ! initialize
131  this%inic = 0
132  this%indfw = 0
133  this%incxs = 0
134  this%insto = 0
135  this%inobs = 0
136  this%inoc = 0
137  this%iss = 1 !default is steady-state (i.e., no STO package)
138  this%inewtonur = 0
139 
140  end subroutine allocate_scalars
141 
142  !> @brief Allocate memory for scalar members
143  !<
144  subroutine allocate_arrays(this)
145  ! modules
146  ! dummy
147  class(swfmodeltype) :: this
148  integer(I4B) :: i
149 
150  ! allocate members from parent class
151  call this%NumericalModelType%allocate_arrays()
152 
153  if (this%indfw == 0) then
154  ! explicit model, so these must be manually allocated (not used)
155  call mem_allocate(this%x, this%dis%nodes, 'X', this%memoryPath)
156  call mem_allocate(this%rhs, this%dis%nodes, 'RHS', this%memoryPath)
157  call mem_allocate(this%ibound, this%dis%nodes, 'IBOUND', this%memoryPath)
158  do i = 1, this%dis%nodes
159  this%x(i) = dzero
160  this%rhs(i) = dzero
161  this%ibound(i) = 1
162  end do
163  end if
164 
165  end subroutine allocate_arrays
166 
167  !> @brief Define packages of the model
168  !<
169  subroutine swf_df(this)
170  ! modules
171  ! dummy
172  class(swfmodeltype) :: this
173  ! local
174  integer(I4B) :: ip
175  class(bndtype), pointer :: packobj
176 
177  ! call package df routines
178  call this%dis%dis_df()
179  call this%dfw%dfw_df(this%dis)
180  call this%oc%oc_df()
181  call this%budget%budget_df(niunit_swf, 'VOLUME', 'L**3')
182 
183  ! set model sizes
184  this%neq = this%dis%nodes
185  this%nja = this%dis%nja
186  this%ia => this%dis%con%ia
187  this%ja => this%dis%con%ja
188 
189  ! Allocate model arrays, now that neq and nja are known
190  call this%allocate_arrays()
191 
192  ! Define packages and assign iout for time series managers
193  do ip = 1, this%bndlist%Count()
194  packobj => getbndfromlist(this%bndlist, ip)
195  call packobj%bnd_df(this%dis%nodes, this%dis)
196  end do
197 
198  ! Store information needed for observations
199  call this%obs%obs_df(this%iout, this%name, 'SWF', this%dis)
200 
201  end subroutine swf_df
202 
203  !> @brief Add the internal connections of this model to the sparse matrix
204  !<
205  subroutine swf_ac(this, sparse)
206  ! modules
207  use sparsemodule, only: sparsematrix
208  ! dummy
209  class(swfmodeltype) :: this
210  type(sparsematrix), intent(inout) :: sparse
211  ! local
212  class(bndtype), pointer :: packobj
213  integer(I4B) :: ip
214 
215  ! Add the primary grid connections of this model to sparse
216  call this%dis%dis_ac(this%moffset, sparse)
217 
218  ! Add any additional connections
219  ! none
220 
221  ! Add any package connections
222  do ip = 1, this%bndlist%Count()
223  packobj => getbndfromlist(this%bndlist, ip)
224  call packobj%bnd_ac(this%moffset, sparse)
225  end do
226 
227  end subroutine swf_ac
228 
229  !> @brief Map the positions of this models connections in the
230  !< numerical solution coefficient matrix.
231  subroutine swf_mc(this, matrix_sln)
232  ! dummy
233  class(swfmodeltype) :: this
234  class(matrixbasetype), pointer :: matrix_sln
235  ! local
236  class(bndtype), pointer :: packobj
237  integer(I4B) :: ip
238 
239  ! Find the position of each connection in the global ia, ja structure
240  ! and store them in idxglo.
241  call this%dis%dis_mc(this%moffset, this%idxglo, matrix_sln)
242 
243  ! Map any additional connections
244  ! none
245 
246  ! Map any package connections
247  do ip = 1, this%bndlist%Count()
248  packobj => getbndfromlist(this%bndlist, ip)
249  call packobj%bnd_mc(this%moffset, matrix_sln)
250  end do
251 
252  end subroutine swf_mc
253 
254  !> @brief SWF Allocate and Read
255  !<
256  subroutine swf_ar(this)
257  ! dummy
258  class(swfmodeltype) :: this
259  ! locals
260  integer(I4B), dimension(:), allocatable :: itemp
261  integer(I4B) :: ip
262  class(bndtype), pointer :: packobj
263 
264  ! Allocate and read modules attached to model
265  if (this%inic > 0) call this%ic%ic_ar(this%x)
266 
267  ! need temporary integer variable to pass to dis_ar
268  ! TODO: this should be generalized so dis_ar doesn't have to have it
269  allocate (itemp(this%dis%nodes))
270 
271  ! Call dis_ar to write binary grid file
272  call this%dis%dis_ar(itemp)
273  if (this%indfw > 0) call this%dfw%dfw_ar(this%ibound, this%x)
274  if (this%insto > 0) call this%sto%sto_ar(this%dis, this%ibound)
275  if (this%inobs > 0) call this%obs%swf_obs_ar(this%ic, this%x, this%flowja)
276  deallocate (itemp)
277 
278  ! set up output control
279  if (this%indfw > 0) then
280  call this%oc%oc_ar('STAGE', this%x, this%dis, dnodata)
281  end if
282  call this%budget%set_ibudcsv(this%oc%ibudcsv)
283 
284  ! Package input files now open, so allocate and read
285  do ip = 1, this%bndlist%Count()
286  packobj => getbndfromlist(this%bndlist, ip)
287  call packobj%set_pointers(this%dis%nodes, this%ibound, this%x, &
288  this%xold, this%flowja)
289  ! Read and allocate package
290  call packobj%bnd_ar()
291  end do
292 
293  end subroutine swf_ar
294 
295  !> @brief Surface Water Flow Model Read and Prepare
296  !<
297  subroutine swf_rp(this)
298  ! modules
299  use tdismodule, only: readnewdata
300  ! dummy
301  class(swfmodeltype) :: this
302  ! local
303  class(bndtype), pointer :: packobj
304  integer(I4B) :: ip
305 
306  ! Check with TDIS on whether or not it is time to RP
307  if (.not. readnewdata) return
308 
309  ! Read and prepare
310  if (this%indfw > 0) call this%dfw%dfw_rp()
311  if (this%inoc > 0) call this%oc%oc_rp()
312  if (this%insto > 0) call this%sto%sto_rp()
313  !if (this%inmvr > 0) call this%mvr%mvr_rp()
314  do ip = 1, this%bndlist%Count()
315  packobj => getbndfromlist(this%bndlist, ip)
316  call packobj%bnd_rp()
317  call packobj%bnd_rp_obs()
318  end do
319 
320  ! Check for steady state period
321  call this%steady_period_check()
322 
323  end subroutine swf_rp
324 
325  !> @brief Surface Water Flow Model Time Step Advance
326  !<
327  subroutine swf_ad(this)
328  ! modules
330  ! dummy
331  class(swfmodeltype) :: this
332  class(bndtype), pointer :: packobj
333  ! local
334  integer(I4B) :: irestore
335  integer(I4B) :: ip, n
336 
337  ! Reset state variable
338  irestore = 0
339  if (ifailedstepretry > 0) irestore = 1
340  if (irestore == 0) then
341 
342  ! copy x into xold
343  do n = 1, this%dis%nodes
344  this%xold(n) = this%x(n)
345  end do
346  else
347 
348  ! copy xold into x if this time step is a redo
349  do n = 1, this%dis%nodes
350  this%x(n) = this%xold(n)
351  end do
352  end if
353 
354  ! Advance
355  if (this%indfw > 0) call this%dfw%dfw_ad(irestore)
356  if (this%insto > 0) call this%sto%sto_ad()
357  !if (this%inmvr > 0) call this%mvr%mvr_ad()
358  do ip = 1, this%bndlist%Count()
359  packobj => getbndfromlist(this%bndlist, ip)
360  call packobj%bnd_ad()
361  if (isimcheck > 0) then
362  call packobj%bnd_ck()
363  end if
364  end do
365 
366  ! Push simulated values to preceding time/subtime step
367  call this%obs%obs_ad()
368 
369  end subroutine swf_ad
370 
371  !> @brief Calculate coefficients
372  !<
373  subroutine swf_cf(this, kiter)
374  ! dummy
375  class(swfmodeltype) :: this
376  integer(I4B), intent(in) :: kiter
377  ! local
378  class(bndtype), pointer :: packobj
379  integer(I4B) :: ip
380 
381  ! Call package cf routines
382  !if (this%indfw > 0) call this%dfw%dfw_cf(kiter, this%dis%nodes, this%x)
383  do ip = 1, this%bndlist%Count()
384  packobj => getbndfromlist(this%bndlist, ip)
385  call packobj%bnd_cf()
386  end do
387 
388  end subroutine swf_cf
389 
390  !> @brief Fill coefficients
391  !<
392  subroutine swf_fc(this, kiter, matrix_sln, inwtflag)
393  ! dummy
394  class(swfmodeltype) :: this
395  integer(I4B), intent(in) :: kiter
396  class(matrixbasetype), pointer :: matrix_sln
397  integer(I4B), intent(in) :: inwtflag
398  ! local
399  class(bndtype), pointer :: packobj
400  integer(I4B) :: ip
401  integer(I4B) :: inwt, inwtpak
402 
403  ! newton flags
404  inwt = inwtflag
405  ! if (inwtflag == 1) inwt = this%dfw%inewton
406  ! inwtsto = inwtflag
407  ! if (this%insto > 0) then
408  ! if (inwtflag == 1) inwtsto = this%sto%inewton
409  ! end if
410  ! inwtcsub = inwtflag
411  ! if (this%incsub > 0) then
412  ! if (inwtflag == 1) inwtcsub = this%csub%inewton
413  ! end if
414 
415  ! Fill standard conductance terms
416  if (this%indfw > 0) call this%dfw%dfw_fc(kiter, matrix_sln, this%idxglo, &
417  this%rhs, this%x, this%xold)
418  ! storage
419  if (this%insto > 0) then
420  call this%sto%sto_fc(kiter, this%xold, this%x, matrix_sln, &
421  this%idxglo, this%rhs)
422  end if
423  ! if (this%inmvr > 0) call this%mvr%mvr_fc()
424  do ip = 1, this%bndlist%Count()
425  packobj => getbndfromlist(this%bndlist, ip)
426  call packobj%bnd_fc(this%rhs, this%ia, this%idxglo, matrix_sln)
427  end do
428 
429  !--Fill newton terms
430  if (this%indfw > 0) then
431  if (inwt /= 0) then
432  call this%dfw%dfw_fn(kiter, matrix_sln, this%idxglo, this%rhs, this%x)
433  end if
434  end if
435 
436  ! Fill newton terms for storage
437  ! if (this%insto > 0) then
438  ! if (inwtsto /= 0) then
439  ! call this%sto%sto_fn(kiter, this%xold, this%x, matrix_sln, &
440  ! this%idxglo, this%rhs)
441  ! end if
442  ! end if
443 
444  ! Fill Newton terms for packages
445  do ip = 1, this%bndlist%Count()
446  packobj => getbndfromlist(this%bndlist, ip)
447  inwtpak = inwtflag
448  if (inwtflag == 1) inwtpak = packobj%inewton
449  if (inwtpak /= 0) then
450  call packobj%bnd_fn(this%rhs, this%ia, this%idxglo, matrix_sln)
451  end if
452  end do
453 
454  end subroutine swf_fc
455 
456  !> @brief under-relaxation
457  !<
458  subroutine swf_nur(this, neqmod, x, xtemp, dx, inewtonur, dxmax, locmax)
459  ! modules
460  use constantsmodule, only: done, dp9
461  ! dummy
462  class(swfmodeltype) :: this
463  integer(I4B), intent(in) :: neqmod
464  real(DP), dimension(neqmod), intent(inout) :: x
465  real(DP), dimension(neqmod), intent(in) :: xtemp
466  real(DP), dimension(neqmod), intent(inout) :: dx
467  integer(I4B), intent(inout) :: inewtonur
468  real(DP), intent(inout) :: dxmax
469  integer(I4B), intent(inout) :: locmax
470  ! local
471  integer(I4B) :: i0
472  integer(I4B) :: i1
473  class(bndtype), pointer :: packobj
474  integer(I4B) :: ip
475 
476  ! apply Newton-Raphson under-relaxation if model is using
477  ! the Newton-Raphson formulation and this Newton-Raphson
478  ! under-relaxation is turned on.
479  if (this%inewton /= 0 .and. this%inewtonur /= 0) then
480  if (this%indfw > 0) then
481  call this%dfw%dfw_nur(neqmod, x, xtemp, dx, inewtonur, dxmax, locmax)
482  end if
483 
484  ! Call package nur routines
485  i0 = this%dis%nodes + 1
486  do ip = 1, this%bndlist%Count()
487  packobj => getbndfromlist(this%bndlist, ip)
488  if (packobj%npakeq > 0) then
489  i1 = i0 + packobj%npakeq - 1
490  call packobj%bnd_nur(packobj%npakeq, x(i0:i1), xtemp(i0:i1), &
491  dx(i0:i1), inewtonur, dxmax, locmax)
492  i0 = i1 + 1
493  end if
494  end do
495  end if
496 
497  end subroutine swf_nur
498 
499  !> @brief Calculate flow
500  !<
501  subroutine swf_cq(this, icnvg, isuppress_output)
502  ! modules
503  ! dummy
504  class(swfmodeltype) :: this
505  integer(I4B), intent(in) :: icnvg
506  integer(I4B), intent(in) :: isuppress_output
507  ! local
508  integer(I4B) :: i
509  integer(I4B) :: ip
510  class(bndtype), pointer :: packobj
511 
512  ! Construct the flowja array. Flowja is calculated each time, even if
513  ! output is suppressed. (flowja is positive into a cell.) The diagonal
514  ! position of the flowja array will contain the flow residual after
515  ! these routines are called, so each package is responsible for adding
516  ! its flow to this diagonal position.
517  do i = 1, this%dis%nja
518  this%flowja(i) = dzero
519  end do
520  if (this%indfw > 0) call this%dfw%dfw_cq(this%x, this%xold, this%flowja)
521  if (this%insto > 0) call this%sto%sto_cq(this%flowja, this%x, this%xold)
522 
523  ! Go through packages and call cq routines. cf() routines are called
524  ! first to regenerate non-linear terms to be consistent with the final
525  ! head solution.
526  do ip = 1, this%bndlist%Count()
527  packobj => getbndfromlist(this%bndlist, ip)
528  call packobj%bnd_cf()
529  call packobj%bnd_cq(this%x, this%flowja)
530  end do
531 
532  end subroutine swf_cq
533 
534  !> @brief Model Budget
535  !<
536  subroutine swf_bd(this, icnvg, isuppress_output)
537  ! modules
538  use sparsemodule, only: csr_diagsum
539  ! dummy
540  class(swfmodeltype) :: this
541  integer(I4B), intent(in) :: icnvg
542  integer(I4B), intent(in) :: isuppress_output
543  ! local
544  integer(I4B) :: ip
545  class(bndtype), pointer :: packobj
546 
547  ! Finalize calculation of flowja by adding face flows to the diagonal.
548  ! This results in the flow residual being stored in the diagonal
549  ! position for each cell.
550  call csr_diagsum(this%dis%con%ia, this%flowja)
551 
552  ! Budget routines (start by resetting). Sole purpose of this section
553  ! is to add in and outs to model budget. All ins and out for a model
554  ! should be added here to this%budget. In a subsequent exchange call,
555  ! exchange flows might also be added.
556  call this%budget%reset()
557  if (this%insto > 0) call this%sto%sto_bd(isuppress_output, this%budget)
558  if (this%indfw > 0) call this%dfw%dfw_bd(isuppress_output, this%budget)
559  do ip = 1, this%bndlist%Count()
560  packobj => getbndfromlist(this%bndlist, ip)
561  call packobj%bnd_bd(this%budget)
562  end do
563 
564  ! dfw velocities have to be calculated here, after swf-swf exchanges
565  ! have passed in their contributions from exg_cq()
566  if (this%indfw > 0) then
567  if (this%dfw%icalcvelocity /= 0) then
568  call this%dfw%calc_velocity(this%flowja)
569  end if
570  end if
571 
572  end subroutine swf_bd
573 
574  !> @brief Surface Water Flow Model Output
575  !<
576  subroutine swf_ot(this)
577  ! modules
578  use tdismodule, only: tdis_ot, endofperiod
579  ! dummy
580  class(swfmodeltype) :: this
581  ! local
582  integer(I4B) :: idvsave
583  integer(I4B) :: idvprint
584  integer(I4B) :: icbcfl
585  integer(I4B) :: icbcun
586  integer(I4B) :: ibudfl
587  integer(I4B) :: ipflag
588  integer(I4B) :: icnvg = 1
589 
590  ! Set write and print flags
591  idvsave = 0
592  idvprint = 0
593  icbcfl = 0
594  ibudfl = 0
595  if (this%oc%oc_save('QOUTFLOW')) idvsave = 1
596  if (this%oc%oc_print('QOUTFLOW')) idvprint = 1
597  if (this%oc%oc_save('BUDGET')) icbcfl = 1
598  if (this%oc%oc_print('BUDGET')) ibudfl = 1
599  icbcun = this%oc%oc_save_unit('BUDGET')
600 
601  ! Override ibudfl and idvprint flags for nonconvergence
602  ! and end of period
603  ibudfl = this%oc%set_print_flag('BUDGET', icnvg, endofperiod)
604  idvprint = this%oc%set_print_flag('QOUTFLOW', icnvg, endofperiod)
605 
606  ! Calculate and save observations
607  call this%swf_ot_obs()
608 
609  ! Save and print flows
610  call this%swf_ot_flow(icbcfl, ibudfl, icbcun)
611 
612  ! Save and print dependent variables
613  call this%swf_ot_dv(idvsave, idvprint, ipflag)
614 
615  ! Print budget summaries
616  call this%swf_ot_bdsummary(ibudfl, ipflag)
617 
618  ! Timing Output; if any dependent variables or budgets
619  ! are printed, then ipflag is set to 1.
620  if (ipflag == 1) call tdis_ot(this%iout)
621 
622  end subroutine swf_ot
623 
624  !> @brief Surface Water Flow Model output observations
625  !<
626  subroutine swf_ot_obs(this)
627  class(swfmodeltype) :: this
628  class(bndtype), pointer :: packobj
629  integer(I4B) :: ip
630 
631  ! Calculate and save SWF observations
632  call this%obs%obs_bd()
633  call this%obs%obs_ot()
634 
635  ! Calculate and save dfw observations
636  if (this%indfw > 0) then
637  call this%dfw%dfw_bd_obs()
638  call this%dfw%obs%obs_ot()
639  end if
640 
641  ! Calculate and save package observations
642  do ip = 1, this%bndlist%Count()
643  packobj => getbndfromlist(this%bndlist, ip)
644  call packobj%bnd_bd_obs()
645  call packobj%bnd_ot_obs()
646  end do
647 
648  end subroutine swf_ot_obs
649 
650  !> @brief Surface Water Flow Model output flows
651  !<
652  subroutine swf_ot_flow(this, icbcfl, ibudfl, icbcun)
653  class(swfmodeltype) :: this
654  integer(I4B), intent(in) :: icbcfl
655  integer(I4B), intent(in) :: ibudfl
656  integer(I4B), intent(in) :: icbcun
657  class(bndtype), pointer :: packobj
658  integer(I4B) :: ip
659 
660  ! Save SWF flows
661  if (this%insto > 0) then
662  call this%sto%sto_save_model_flows(icbcfl, icbcun)
663  end if
664  if (this%indfw > 0) then
665  call this%dfw%dfw_save_model_flows(this%flowja, icbcfl, icbcun)
666  end if
667  do ip = 1, this%bndlist%Count()
668  packobj => getbndfromlist(this%bndlist, ip)
669  call packobj%bnd_ot_model_flows(icbcfl=icbcfl, ibudfl=0, icbcun=icbcun)
670  end do
671 
672  ! Save advanced package flows
673  do ip = 1, this%bndlist%Count()
674  packobj => getbndfromlist(this%bndlist, ip)
675  call packobj%bnd_ot_package_flows(icbcfl=icbcfl, ibudfl=0)
676  end do
677  ! if (this%inmvr > 0) then
678  ! call this%mvr%mvr_ot_saveflow(icbcfl, ibudfl)
679  ! end if
680 
681  ! Print SWF flows
682  if (this%indfw > 0) then
683  call this%dfw%dfw_print_model_flows(ibudfl, this%flowja)
684  end if
685  do ip = 1, this%bndlist%Count()
686  packobj => getbndfromlist(this%bndlist, ip)
687  call packobj%bnd_ot_model_flows(icbcfl=icbcfl, ibudfl=ibudfl, icbcun=0)
688  end do
689 
690  ! Print advanced package flows
691  do ip = 1, this%bndlist%Count()
692  packobj => getbndfromlist(this%bndlist, ip)
693  call packobj%bnd_ot_package_flows(icbcfl=0, ibudfl=ibudfl)
694  end do
695  ! if (this%inmvr > 0) then
696  ! call this%mvr%mvr_ot_printflow(icbcfl, ibudfl)
697  ! end if
698 
699  end subroutine swf_ot_flow
700 
701  !> @brief Surface Water Flow Model output dependent variable
702  !<
703  subroutine swf_ot_dv(this, idvsave, idvprint, ipflag)
704  class(swfmodeltype) :: this
705  integer(I4B), intent(in) :: idvsave
706  integer(I4B), intent(in) :: idvprint
707  integer(I4B), intent(inout) :: ipflag
708  class(bndtype), pointer :: packobj
709  integer(I4B) :: ip
710 
711  ! Print advanced package dependent variables
712  do ip = 1, this%bndlist%Count()
713  packobj => getbndfromlist(this%bndlist, ip)
714  call packobj%bnd_ot_dv(idvsave, idvprint)
715  end do
716  !
717  ! save stage and print stage (if implemented)
718  call this%oc%oc_ot(ipflag)
719 
720  end subroutine swf_ot_dv
721 
722  !> @brief Surface Water Flow Model output budget summary
723  !<
724  subroutine swf_ot_bdsummary(this, ibudfl, ipflag)
725  use tdismodule, only: kstp, kper, totim, delt
726  class(swfmodeltype) :: this
727  integer(I4B), intent(in) :: ibudfl
728  integer(I4B), intent(inout) :: ipflag
729  class(bndtype), pointer :: packobj
730  integer(I4B) :: ip
731 
732  ! Package budget summary
733  do ip = 1, this%bndlist%Count()
734  packobj => getbndfromlist(this%bndlist, ip)
735  call packobj%bnd_ot_bdsummary(kstp, kper, this%iout, ibudfl)
736  end do
737 
738  ! mover budget summary
739  ! if (this%inmvr > 0) then
740  ! call this%mvr%mvr_ot_bdsummary(ibudfl)
741  ! end if
742 
743  ! model budget summary
744  call this%budget%finalize_step(delt)
745  if (ibudfl /= 0) then
746  ipflag = 1
747  call this%budget%budget_ot(kstp, kper, this%iout)
748  end if
749 
750  ! Write to budget csv every time step
751  call this%budget%writecsv(totim)
752 
753  end subroutine swf_ot_bdsummary
754 
755  !> @brief Deallocate
756  !<
757  subroutine swf_da(this)
758  ! modules
762  ! dummy
763  class(swfmodeltype) :: this
764  ! local
765  integer(I4B) :: ip
766  class(bndtype), pointer :: packobj
767 
768  ! Deallocate idm memory
769  call memorystore_remove(this%name, 'NAM', idm_context)
770  call memorystore_remove(component=this%name, context=idm_context)
771 
772  ! Internal flow packages deallocate
773  call this%dis%dis_da()
774  if (this%insto > 0) call this%sto%sto_da()
775  if (this%inic > 0) call this%ic%ic_da()
776  if (this%indfw > 0) call this%dfw%dfw_da()
777  call this%cxs%cxs_da()
778  call this%obs%obs_da()
779  call this%oc%oc_da()
780  call this%budget%budget_da()
781 
782  ! Internal package objects
783  deallocate (this%dis)
784  deallocate (this%budget)
785  deallocate (this%obs)
786  deallocate (this%oc)
787 
788  ! Boundary packages
789  do ip = 1, this%bndlist%Count()
790  packobj => getbndfromlist(this%bndlist, ip)
791  call packobj%bnd_da()
792  deallocate (packobj)
793  end do
794 
795  ! Scalars
796  call mem_deallocate(this%inic)
797  call mem_deallocate(this%indfw)
798  call mem_deallocate(this%incxs)
799  call mem_deallocate(this%insto)
800  call mem_deallocate(this%inobs)
801  call mem_deallocate(this%inoc)
802  call mem_deallocate(this%iss)
803  call mem_deallocate(this%inewtonur)
804 
805  ! Arrays
806 
807  ! NumericalModelType
808  call this%NumericalModelType%model_da()
809 
810  end subroutine swf_da
811 
812  !> @brief Surface Flow Model Budget Entry
813  !!
814  !! This subroutine adds a budget entry to the flow budget. It was added as
815  !! a method for the swf model object so that the exchange object could add its
816  !< contributions.
817  subroutine swf_bdentry(this, budterm, budtxt, rowlabel)
818  ! modules
819  use constantsmodule, only: lenbudtxt
820  use tdismodule, only: delt
821  ! dummy
822  class(swfmodeltype) :: this
823  real(DP), dimension(:, :), intent(in) :: budterm
824  character(len=LENBUDTXT), dimension(:), intent(in) :: budtxt
825  character(len=*), intent(in) :: rowlabel
826 
827  call this%budget%addentry(budterm, delt, budtxt, rowlabel=rowlabel)
828 
829  end subroutine swf_bdentry
830 
831  !> @brief Create boundary condition packages for this model
832  !<
833  subroutine package_create(this, filtyp, ipakid, ipaknum, pakname, mempath, &
834  inunit, iout)
835  ! modules
836  use constantsmodule, only: linelength
838  use swfflwmodule, only: flw_create
839  use chdmodule, only: chd_create
840  use swfcdbmodule, only: cdb_create
841  use swfzdgmodule, only: zdg_create
842  ! dummy
843  class(swfmodeltype) :: this
844  character(len=*), intent(in) :: filtyp
845  integer(I4B), intent(in) :: ipakid
846  integer(I4B), intent(in) :: ipaknum
847  character(len=*), intent(in) :: pakname
848  character(len=*), intent(in) :: mempath
849  integer(I4B), intent(in) :: inunit
850  integer(I4B), intent(in) :: iout
851  ! local
852  class(bndtype), pointer :: packobj
853  class(bndtype), pointer :: packobj2
854  integer(I4B) :: ip
855 
856  ! This part creates the package object
857  select case (filtyp)
858  case ('FLW6')
859  call flw_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
860  pakname, mempath)
861  packobj%ictMemPath = ''
862  case ('CHD6')
863  call chd_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
864  pakname, mempath)
865  packobj%ictMemPath = create_mem_path(this%name, 'DFW')
866  case ('CDB6')
867  call cdb_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
868  pakname, mempath, this%dis, this%cxs, &
869  this%dfw%lengthconv, this%dfw%timeconv)
870  case ('ZDG6')
871  call zdg_create(packobj, ipakid, ipaknum, inunit, iout, this%name, &
872  pakname, mempath, this%dis, this%cxs, this%dfw%unitconv)
873  case default
874  write (errmsg, *) 'Invalid package type: ', filtyp
875  call store_error(errmsg)
876  call store_error_filename(this%filename)
877  end select
878 
879  ! Check to make sure that the package name is unique, then store a
880  ! pointer to the package in the model bndlist
881  do ip = 1, this%bndlist%Count()
882  packobj2 => getbndfromlist(this%bndlist, ip)
883  if (packobj2%packName == pakname) then
884  write (errmsg, '(a,a)') 'Cannot create package. Package name '// &
885  'already exists: ', trim(pakname)
886  call store_error(errmsg, terminate=.true.)
887  end if
888  end do
889  call addbndtolist(this%bndlist, packobj)
890 
891  end subroutine package_create
892 
893  !> @brief Check to make sure required input files have been specified
894  !<
895  subroutine ftype_check(this, indis)
896  ! modules
897  ! dummy
898  class(swfmodeltype) :: this
899  integer(I4B), intent(in) :: indis
900  ! local
901 
902  ! Check for required packages. Stop if not present.
903  if (indis == 0) then
904  write (errmsg, '(a)') &
905  'Discretization Package (DISV1D6 or DIS2D6) not specified.'
906  call store_error(errmsg)
907  end if
908  if (this%inic == 0 .and. this%indfw /= 0) then
909  write (errmsg, '(a)') &
910  'Initial Conditions (IC6) must be specified if the Diffusive &
911  &Wave (DFW) package is used.'
912  call store_error(errmsg)
913  end if
914  if (this%indfw == 0) then
915  write (errmsg, '(1x,a)') &
916  'DFW6 Package must be specified.'
917  call store_error(errmsg)
918  end if
919  if (this%incxs > 0) then
920  if (this%dis%ndim /= 1) then
921  write (errmsg, '(1x,a)') &
922  'CXS6 Package can only be used for one-dimensional discretization &
923  &package (DISV1D). Remove CXS6 Package from model or convert &
924  &discretization package to DISV1D.'
925  call store_error(errmsg)
926  end if
927  end if
928  if (count_errors() > 0) then
929  write (errmsg, '(a)') 'One or more required package(s) not specified &
930  &and/or there are package incompatibilities.'
931  call store_error(errmsg)
932  call store_error_filename(this%filename)
933  end if
934 
935  end subroutine ftype_check
936 
937  !> @brief Source package info and begin to process
938  !<
939  subroutine create_bndpkgs(this, bndpkgs, pkgtypes, pkgnames, &
940  mempaths, inunits)
941  ! modules
944  ! dummy
945  class(swfmodeltype) :: this
946  integer(I4B), dimension(:), allocatable, intent(inout) :: bndpkgs
947  type(characterstringtype), dimension(:), contiguous, &
948  pointer, intent(inout) :: pkgtypes
949  type(characterstringtype), dimension(:), contiguous, &
950  pointer, intent(inout) :: pkgnames
951  type(characterstringtype), dimension(:), contiguous, &
952  pointer, intent(inout) :: mempaths
953  integer(I4B), dimension(:), contiguous, &
954  pointer, intent(inout) :: inunits
955  ! local
956  integer(I4B) :: ipakid, ipaknum
957  character(len=LENFTYPE) :: pkgtype, bndptype
958  character(len=LENPACKAGENAME) :: pkgname
959  character(len=LENMEMPATH) :: mempath
960  integer(I4B), pointer :: inunit
961  integer(I4B) :: n
962 
963  if (allocated(bndpkgs)) then
964 
965  ! create stress packages
966  ipakid = 1
967  bndptype = ''
968  do n = 1, size(bndpkgs)
969  !
970  pkgtype = pkgtypes(bndpkgs(n))
971  pkgname = pkgnames(bndpkgs(n))
972  mempath = mempaths(bndpkgs(n))
973  inunit => inunits(bndpkgs(n))
974  !
975  if (bndptype /= pkgtype) then
976  ipaknum = 1
977  bndptype = pkgtype
978  end if
979  !
980  call this%package_create(pkgtype, ipakid, ipaknum, pkgname, mempath, &
981  inunit, this%iout)
982  ipakid = ipakid + 1
983  ipaknum = ipaknum + 1
984  end do
985 
986  ! cleanup
987  deallocate (bndpkgs)
988  end if
989 
990  end subroutine create_bndpkgs
991 
992  !> @brief Source package info and begin to process
993  !<
994  subroutine create_packages(this)
995  ! modules
1001  use simvariablesmodule, only: idm_context
1002  use disv1dmodule, only: disv1d_cr
1003  use dis2dmodule, only: dis2d_cr
1004  use disv2dmodule, only: disv2d_cr
1005  use swfdfwmodule, only: dfw_cr
1006  use swfcxsmodule, only: cxs_cr
1007  use swfstomodule, only: sto_cr
1008  use swficmodule, only: ic_cr
1009  use swfocmodule, only: oc_cr
1010  ! dummy
1011  class(swfmodeltype) :: this
1012  ! local
1013  type(characterstringtype), dimension(:), contiguous, &
1014  pointer :: pkgtypes => null()
1015  type(characterstringtype), dimension(:), contiguous, &
1016  pointer :: pkgnames => null()
1017  type(characterstringtype), dimension(:), contiguous, &
1018  pointer :: mempaths => null()
1019  integer(I4B), dimension(:), contiguous, &
1020  pointer :: inunits => null()
1021  character(len=LENMEMPATH) :: model_mempath
1022  character(len=LENPACKAGETYPE) :: pkgtype
1023  character(len=LENPACKAGENAME) :: pkgname
1024  character(len=LENMEMPATH) :: mempath
1025  integer(I4B), pointer :: inunit
1026  integer(I4B), dimension(:), allocatable :: bndpkgs
1027  integer(I4B) :: n
1028  integer(I4B) :: indis = 0 ! DIS enabled flag
1029  character(len=LENMEMPATH) :: mempathic = ''
1030  character(len=LENMEMPATH) :: mempathdfw = ''
1031  character(len=LENMEMPATH) :: mempathcxs = ''
1032  character(len=LENMEMPATH) :: mempathsto = ''
1033 
1034  ! set input model memory path
1035  model_mempath = create_mem_path(component=this%name, context=idm_context)
1036 
1037  ! set pointers to model path package info
1038  call mem_setptr(pkgtypes, 'PKGTYPES', model_mempath)
1039  call mem_setptr(pkgnames, 'PKGNAMES', model_mempath)
1040  call mem_setptr(mempaths, 'MEMPATHS', model_mempath)
1041  call mem_setptr(inunits, 'INUNITS', model_mempath)
1042 
1043  do n = 1, size(pkgtypes)
1044 
1045  ! attributes for this input package
1046  pkgtype = pkgtypes(n)
1047  pkgname = pkgnames(n)
1048  mempath = mempaths(n)
1049  inunit => inunits(n)
1050 
1051  ! create dis package as it is a prerequisite for other packages
1052  select case (pkgtype)
1053  case ('DISV1D6')
1054  indis = 1
1055  call disv1d_cr(this%dis, this%name, mempath, indis, this%iout)
1056  case ('DIS2D6')
1057  indis = 1
1058  call dis2d_cr(this%dis, this%name, mempath, indis, this%iout)
1059  case ('DISV2D6')
1060  indis = 1
1061  call disv2d_cr(this%dis, this%name, mempath, indis, this%iout)
1062  case ('DFW6')
1063  this%indfw = 1
1064  mempathdfw = mempath
1065  case ('CXS6')
1066  this%incxs = 1
1067  mempathcxs = mempath
1068  case ('STO6')
1069  this%insto = 1
1070  mempathsto = mempath
1071  case ('IC6')
1072  this%inic = 1
1073  mempathic = mempath
1074  case ('OC6')
1075  this%inoc = inunit
1076  case ('OBS6')
1077  this%inobs = inunit
1078  case ('CHD6', 'FLW6', 'CDB6', 'ZDG6')
1079  call expandarray(bndpkgs)
1080  bndpkgs(size(bndpkgs)) = n
1081  case default
1082  ! TODO
1083  end select
1084  end do
1085 
1086  ! Create packages that are tied directly to model
1087  if (this%inic > 0) then
1088  call ic_cr(this%ic, this%name, mempathic, this%inic, this%iout, &
1089  this%dis)
1090  end if
1091  call cxs_cr(this%cxs, this%name, mempathcxs, this%incxs, this%iout, &
1092  this%dis)
1093  if (this%indfw > 0) then
1094  call dfw_cr(this%dfw, this%name, mempathdfw, this%indfw, this%iout, &
1095  this%cxs)
1096  end if
1097  if (this%insto > 0) then
1098  call sto_cr(this%sto, this%name, mempathsto, this%insto, this%iout, &
1099  this%cxs)
1100  end if
1101  call oc_cr(this%oc, this%name, this%inoc, this%iout)
1102  call swf_obs_cr(this%obs, this%inobs)
1103 
1104  ! Check to make sure that required ftype's have been specified
1105  call this%ftype_check(indis)
1106 
1107  call this%create_bndpkgs(bndpkgs, pkgtypes, pkgnames, mempaths, inunits)
1108 
1109  end subroutine create_packages
1110 
1111  !> @brief Check for steady state period
1112  !!
1113  !! Write warning message if steady state
1114  !! period and adaptive time stepping is
1115  !< active for the period
1116  subroutine steady_period_check(this)
1117  ! modules
1118  use tdismodule, only: kper
1120  use simvariablesmodule, only: warnmsg
1121  use simmodule, only: store_warning
1122  ! dummy
1123  class(swfmodeltype) :: this
1124 
1125  if (this%iss == 1) then
1126  if (isadaptiveperiod(kper)) then
1127  write (warnmsg, '(a,a,a,i0,a)') &
1128  'SWF Model (', trim(this%name), ') is steady state for period ', &
1129  kper, ' and adaptive time stepping is active. Adaptive time &
1130  &stepping may not work properly for steady-state conditions.'
1131  call store_warning(warnmsg)
1132  end if
1133  end if
1134 
1135  end subroutine steady_period_check
1136 
1137  !> @brief return 1 if any package causes the matrix to be asymmetric.
1138  !< Otherwise return 0.
1139  function swf_get_iasym(this) result(iasym)
1140  class(swfmodeltype) :: this
1141  ! local
1142  integer(I4B) :: iasym
1143  integer(I4B) :: ip
1144  class(bndtype), pointer :: packobj
1145 
1146  ! Start by setting iasym to zero
1147  iasym = 0
1148 
1149  ! DFW
1150  if (this%indfw > 0) then
1151  iasym = 1
1152  end if
1153 
1154  ! Check for any packages that introduce matrix asymmetry
1155  do ip = 1, this%bndlist%Count()
1156  packobj => getbndfromlist(this%bndlist, ip)
1157  if (packobj%iasym /= 0) iasym = 1
1158  end do
1159 
1160  end function swf_get_iasym
1161 
1162 end module swfmodule
logical(lgp) function, public isadaptiveperiod(kper)
@ brief Determine if period is adaptive
Definition: ats.f90:45
This module contains the base boundary package.
subroutine, public addbndtolist(list, bnd)
Add boundary to package list.
class(bndtype) function, pointer, public getbndfromlist(list, idx)
Get boundary from package list.
This module contains the BudgetModule.
Definition: Budget.f90:20
subroutine, public chd_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
Create a new constant head package.
Definition: gwf-chd.f90:56
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
real(dp), parameter dp9
real constant 9/10
Definition: Constants.f90:72
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:95
integer(i4b), parameter lenpackagetype
maximum length of a package type (DIS6, SFR6, CSUB6, etc.)
Definition: Constants.f90:38
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:39
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:37
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
subroutine, public dis2d_cr(dis, name_model, input_mempath, inunit, iout)
Create a new structured discretization object.
Definition: Dis2d.f90:92
subroutine, public disv1d_cr(dis, name_model, input_mempath, inunit, iout)
Definition: Disv1d.f90:89
subroutine, public disv2d_cr(dis, name_model, input_mempath, inunit, iout)
Create a new discretization by vertices object.
Definition: Disv2d.f90:94
This module defines variable data types.
Definition: kind.f90:8
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine, public memorystore_remove(component, subcomponent, context)
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_warning(msg, substring)
Store warning message.
Definition: Sim.f90:236
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
character(len=linelength) idm_context
integer(i4b) isimcheck
simulation input check flag (1) to check input, (0) to ignore checks
integer(i4b) ifailedstepretry
current retry for this time step
character(len=maxcharlen) warnmsg
warning message string
subroutine csr_diagsum(ia, flowja)
Definition: Sparse.f90:263
This module contains the CDB package methods.
Definition: swf-cdb.f90:7
subroutine, public cdb_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath, dis, cxs, lengthconv, timeconv)
@ brief Create a new package object
Definition: swf-cdb.f90:75
subroutine, public cxs_cr(pobj, name_model, input_mempath, inunit, iout, dis)
create package
Definition: swf-cxs.f90:62
This module contains the FLW package methods.
Definition: swf-flw.f90:7
subroutine, public flw_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
@ brief Create a new package object
Definition: swf-flw.f90:65
subroutine, public ic_cr(ic, name_model, input_mempath, inunit, iout, dis)
Create a new initial conditions object.
Definition: swf-ic.f90:33
Surface Water Flow (SWF) Module.
Definition: swf.f90:3
subroutine swf_ad(this)
Surface Water Flow Model Time Step Advance.
Definition: swf.f90:328
subroutine swf_ar(this)
SWF Allocate and Read.
Definition: swf.f90:257
subroutine create_packages(this)
Source package info and begin to process.
Definition: swf.f90:995
subroutine swf_bdentry(this, budterm, budtxt, rowlabel)
Surface Flow Model Budget Entry.
Definition: swf.f90:818
subroutine swf_cf(this, kiter)
Calculate coefficients.
Definition: swf.f90:374
subroutine package_create(this, filtyp, ipakid, ipaknum, pakname, mempath, inunit, iout)
Create boundary condition packages for this model.
Definition: swf.f90:835
subroutine swf_df(this)
Define packages of the model.
Definition: swf.f90:170
integer(i4b), parameter niunit_swf
Definition: swf.f90:78
subroutine create_bndpkgs(this, bndpkgs, pkgtypes, pkgnames, mempaths, inunits)
Source package info and begin to process.
Definition: swf.f90:941
subroutine swf_ot_obs(this)
Surface Water Flow Model output observations.
Definition: swf.f90:627
subroutine initialize(this, modelftype, filename, id, modelname)
Initialize common swf members.
Definition: swf.f90:85
subroutine allocate_scalars(this, modelname)
Allocate memory for scalar members.
Definition: swf.f90:112
subroutine steady_period_check(this)
Check for steady state period.
Definition: swf.f90:1117
subroutine swf_ot_dv(this, idvsave, idvprint, ipflag)
Surface Water Flow Model output dependent variable.
Definition: swf.f90:704
subroutine swf_mc(this, matrix_sln)
Map the positions of this models connections in the.
Definition: swf.f90:232
subroutine swf_ac(this, sparse)
Add the internal connections of this model to the sparse matrix.
Definition: swf.f90:206
subroutine swf_ot_bdsummary(this, ibudfl, ipflag)
Surface Water Flow Model output budget summary.
Definition: swf.f90:725
integer(i4b) function swf_get_iasym(this)
return 1 if any package causes the matrix to be asymmetric.
Definition: swf.f90:1140
subroutine swf_nur(this, neqmod, x, xtemp, dx, inewtonur, dxmax, locmax)
under-relaxation
Definition: swf.f90:459
subroutine swf_cq(this, icnvg, isuppress_output)
Calculate flow.
Definition: swf.f90:502
subroutine swf_da(this)
Deallocate.
Definition: swf.f90:758
subroutine swf_ot_flow(this, icbcfl, ibudfl, icbcun)
Surface Water Flow Model output flows.
Definition: swf.f90:653
subroutine swf_ot(this)
Surface Water Flow Model Output.
Definition: swf.f90:577
subroutine swf_bd(this, icnvg, isuppress_output)
Model Budget.
Definition: swf.f90:537
subroutine swf_fc(this, kiter, matrix_sln, inwtflag)
Fill coefficients.
Definition: swf.f90:393
subroutine allocate_arrays(this)
Allocate memory for scalar members.
Definition: swf.f90:145
integer(i4b), parameter swf_nmultipkg
Definition: swf.f90:77
subroutine swf_rp(this)
Surface Water Flow Model Read and Prepare.
Definition: swf.f90:298
subroutine ftype_check(this, indis)
Check to make sure required input files have been specified.
Definition: swf.f90:896
integer(i4b), parameter swf_nbasepkg
Definition: swf.f90:76
subroutine, public swf_obs_cr(obs, inobs)
Create a new obs object.
Definition: swf-obs.f90:39
subroutine, public oc_cr(ocobj, name_model, inunit, iout)
@ brief Create SwfOcType
Definition: swf-oc.f90:31
This module contains the storage package methods.
Definition: swf-sto.f90:7
subroutine, public sto_cr(stoobj, name_model, mempath, inunit, iout, cxs)
@ brief Create a new package object
Definition: swf-sto.f90:73
This module contains the ZDG package methods.
Definition: swf-zdg.f90:7
subroutine, public zdg_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath, dis, cxs, unitconv)
@ brief Create a new package object
Definition: swf-zdg.f90:79
logical(lgp), pointer, public endofperiod
flag indicating end of stress period
Definition: tdis.f90:27
subroutine, public tdis_ot(iout)
Print simulation time.
Definition: tdis.f90:274
real(dp), pointer, public totim
time relative to start of simulation
Definition: tdis.f90:32
logical(lgp), pointer, public readnewdata
flag indicating time to read new data
Definition: tdis.f90:26
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
real(dp), pointer, public delt
length of the current time step
Definition: tdis.f90:29
Highest level model type. All models extend this parent type.
Definition: BaseModel.f90:13
@ brief BndType
Derived type for the Budget object.
Definition: Budget.f90:39
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
@ brief Output control
Definition: swf-oc.f90:17