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