MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
numericalmodelmodule Module Reference

Data Types

type  numericalmodeltype
 

Functions/Subroutines

subroutine model_df (this)
 
subroutine model_ac (this, sparse)
 
subroutine model_mc (this, matrix_sln)
 
subroutine model_ar (this)
 
subroutine model_rp (this)
 
subroutine model_ad (this)
 
subroutine model_reset (this)
 
subroutine model_solve (this)
 
subroutine model_cf (this, kiter)
 
subroutine model_fc (this, kiter, matrix_sln, inwtflag)
 
subroutine model_ptcchk (this, iptc)
 
subroutine model_ptc (this, vec_residual, iptc, ptcf)
 
subroutine model_nr (this, kiter, matrix, inwtflag)
 
subroutine model_cc (this, innertot, kiter, iend, icnvgmod, cpak, ipak, dpak)
 
subroutine model_nur (this, neqmod, x, xtemp, dx, inewtonur, dxmax, locmax)
 
subroutine model_cq (this, icnvg, isuppress_output)
 
subroutine model_bd (this, icnvg, isuppress_output)
 
subroutine model_bdcalc (this, icnvg)
 
subroutine model_bdsave (this, icnvg)
 
subroutine model_ot (this)
 
subroutine model_bdentry (this, budterm, budtxt, rowlabel)
 
subroutine model_fp (this)
 
subroutine model_da (this)
 
subroutine set_moffset (this, moffset)
 
subroutine get_mrange (this, mstart, mend)
 
subroutine set_idsoln (this, id)
 
subroutine allocate_scalars (this, modelname)
 
subroutine allocate_arrays (this)
 
subroutine set_xptr (this, xsln, sln_offset, varNameTgt, memPathTgt)
 
subroutine set_rhsptr (this, rhssln, sln_offset, varNameTgt, memPathTgt)
 
subroutine set_iboundptr (this, iboundsln, sln_offset, varNameTgt, memPathTgt)
 
subroutine get_mcellid (this, node, mcellid)
 
subroutine get_mnodeu (this, node, nodeu)
 
integer(i4b) function get_iasym (this)
 
class(numericalmodeltype) function, pointer castasnumericalmodelclass (obj)
 
subroutine, public addnumericalmodeltolist (list, model)
 
class(numericalmodeltype) function, pointer, public getnumericalmodelfromlist (list, idx)
 
subroutine create_lstfile (this, lst_fname, model_fname, defined, headertxt)
 

Function/Subroutine Documentation

◆ addnumericalmodeltolist()

subroutine, public numericalmodelmodule::addnumericalmodeltolist ( type(listtype), intent(inout)  list,
class(numericalmodeltype), intent(inout), pointer  model 
)

Definition at line 429 of file NumericalModel.f90.

430  implicit none
431  ! -- dummy
432  type(ListType), intent(inout) :: list
433  class(NumericalModelType), pointer, intent(inout) :: model
434  ! -- local
435  class(*), pointer :: obj
436  !
437  obj => model
438  call list%Add(obj)
Here is the caller graph for this function:

◆ allocate_arrays()

subroutine numericalmodelmodule::allocate_arrays ( class(numericalmodeltype this)

Definition at line 296 of file NumericalModel.f90.

297  use constantsmodule, only: dzero
299  class(NumericalModelType) :: this
300  integer(I4B) :: i
301  !
302  call mem_allocate(this%xold, this%neq, 'XOLD', this%memoryPath)
303  call mem_allocate(this%flowja, this%nja, 'FLOWJA', this%memoryPath)
304  call mem_allocate(this%idxglo, this%nja, 'IDXGLO', this%memoryPath)
305  !
306  ! -- initialize
307  do i = 1, size(this%flowja)
308  this%flowja(i) = dzero
309  end do
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65

◆ allocate_scalars()

subroutine numericalmodelmodule::allocate_scalars ( class(numericalmodeltype this,
character(len=*), intent(in)  modelname 
)
private

Definition at line 273 of file NumericalModel.f90.

275  class(NumericalModelType) :: this
276  character(len=*), intent(in) :: modelname
277  !
278  ! -- allocate basetype members
279  call this%BaseModelType%allocate_scalars(modelname)
280  !
281  ! -- allocate members from this type
282  call mem_allocate(this%neq, 'NEQ', this%memoryPath)
283  call mem_allocate(this%nja, 'NJA', this%memoryPath)
284  call mem_allocate(this%icnvg, 'ICNVG', this%memoryPath)
285  call mem_allocate(this%moffset, 'MOFFSET', this%memoryPath)
286  allocate (this%filename)
287  allocate (this%bndlist)
288  !
289  this%filename = ''
290  this%neq = 0
291  this%nja = 0
292  this%icnvg = 0
293  this%moffset = 0

◆ castasnumericalmodelclass()

class(numericalmodeltype) function, pointer numericalmodelmodule::castasnumericalmodelclass ( class(*), intent(inout), pointer  obj)
private

Definition at line 415 of file NumericalModel.f90.

416  implicit none
417  class(*), pointer, intent(inout) :: obj
418  class(NumericalModelType), pointer :: res
419  !
420  res => null()
421  if (.not. associated(obj)) return
422  !
423  select type (obj)
424  class is (numericalmodeltype)
425  res => obj
426  end select
Here is the caller graph for this function:

◆ create_lstfile()

subroutine numericalmodelmodule::create_lstfile ( class(numericalmodeltype this,
character(len=*), intent(inout)  lst_fname,
character(len=*), intent(in)  model_fname,
logical(lgp), intent(in)  defined,
character(len=*), intent(in)  headertxt 
)
private

Definition at line 454 of file NumericalModel.f90.

455  ! -- modules
456  use kindmodule, only: lgp
458  ! -- dummy
459  class(NumericalModelType) :: this
460  character(len=*), intent(inout) :: lst_fname
461  character(len=*), intent(in) :: model_fname
462  logical(LGP), intent(in) :: defined
463  character(len=*), intent(in) :: headertxt
464  ! -- local
465  integer(I4B) :: i, istart, istop
466  !
467  ! -- set list file name if not provided
468  if (.not. defined) then
469  !
470  ! -- initialize
471  lst_fname = ' '
472  istart = 0
473  istop = len_trim(model_fname)
474  !
475  ! -- identify '.' character position from back of string
476  do i = istop, 1, -1
477  if (model_fname(i:i) == '.') then
478  istart = i
479  exit
480  end if
481  end do
482  !
483  ! -- if not found start from string end
484  if (istart == 0) istart = istop + 1
485  !
486  ! -- set list file name
487  lst_fname = model_fname(1:istart)
488  istop = istart + 3
489  lst_fname(istart:istop) = '.lst'
490  end if
491  !
492  ! -- create the list file
493  this%iout = getunit()
494  call openfile(this%iout, 0, lst_fname, 'LIST', filstat_opt='REPLACE')
495  !
496  ! -- write list file header
497  call write_listfile_header(this%iout, headertxt)
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
This module defines variable data types.
Definition: kind.f90:8
Here is the call graph for this function:

◆ get_iasym()

integer(i4b) function numericalmodelmodule::get_iasym ( class(numericalmodeltype this)

Definition at line 409 of file NumericalModel.f90.

410  class(NumericalModelType) :: this
411  integer(I4B) :: iasym
412  iasym = 0

◆ get_mcellid()

subroutine numericalmodelmodule::get_mcellid ( class(numericalmodeltype this,
integer(i4b), intent(in)  node,
character(len=*), intent(inout)  mcellid 
)

Definition at line 361 of file NumericalModel.f90.

362  use bndmodule, only: bndtype, getbndfromlist
363  class(NumericalModelType) :: this
364  integer(I4B), intent(in) :: node
365  character(len=*), intent(inout) :: mcellid
366  ! -- local
367  character(len=20) :: cellid
368  integer(I4B) :: ip, ipaknode, istart, istop
369  class(BndType), pointer :: packobj
370 
371  if (node < 1) then
372  cellid = ''
373  else if (node <= this%dis%nodes) then
374  call this%dis%noder_to_string(node, cellid)
375  else
376  cellid = '***ERROR***'
377  ipaknode = node - this%dis%nodes
378  istart = 1
379  do ip = 1, this%bndlist%Count()
380  packobj => getbndfromlist(this%bndlist, ip)
381  if (packobj%npakeq == 0) cycle
382  istop = istart + packobj%npakeq - 1
383  if (istart <= ipaknode .and. ipaknode <= istop) then
384  write (cellid, '(a, a, a, i0, a, i0, a)') '(', &
385  trim(packobj%filtyp), '_', &
386  packobj%ibcnum, '-', ipaknode - packobj%ioffset, ')'
387  exit
388  end if
389  istart = istop + 1
390  end do
391  end if
392  write (mcellid, '(i0, a, a, a, a)') this%id, '_', this%macronym, '-', &
393  trim(adjustl(cellid))
This module contains the base boundary package.
class(bndtype) function, pointer, public getbndfromlist(list, idx)
Get boundary from package list.
@ brief BndType
Here is the call graph for this function:

◆ get_mnodeu()

subroutine numericalmodelmodule::get_mnodeu ( class(numericalmodeltype this,
integer(i4b), intent(in)  node,
integer(i4b), intent(inout)  nodeu 
)

Definition at line 396 of file NumericalModel.f90.

397  use bndmodule, only: bndtype, getbndfromlist
398  class(NumericalModelType) :: this
399  integer(I4B), intent(in) :: node
400  integer(I4B), intent(inout) :: nodeu
401  ! -- local
402  if (node <= this%dis%nodes) then
403  nodeu = this%dis%get_nodeuser(node)
404  else
405  nodeu = -(node - this%dis%nodes)
406  end if
Here is the call graph for this function:

◆ get_mrange()

subroutine numericalmodelmodule::get_mrange ( class(numericalmodeltype this,
integer(i4b), intent(inout)  mstart,
integer(i4b), intent(inout)  mend 
)
private

Definition at line 259 of file NumericalModel.f90.

260  class(NumericalModelType) :: this
261  integer(I4B), intent(inout) :: mstart
262  integer(I4B), intent(inout) :: mend
263  mstart = this%moffset + 1
264  mend = mstart + this%neq - 1

◆ getnumericalmodelfromlist()

class(numericalmodeltype) function, pointer, public numericalmodelmodule::getnumericalmodelfromlist ( type(listtype), intent(inout)  list,
integer(i4b), intent(in)  idx 
)

Definition at line 441 of file NumericalModel.f90.

442  implicit none
443  ! -- dummy
444  type(ListType), intent(inout) :: list
445  integer(I4B), intent(in) :: idx
446  class(NumericalModelType), pointer :: res
447  ! -- local
448  class(*), pointer :: obj
449  !
450  obj => list%GetItem(idx)
451  res => castasnumericalmodelclass(obj)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ model_ac()

subroutine numericalmodelmodule::model_ac ( class(numericalmodeltype this,
type(sparsematrix), intent(inout)  sparse 
)
private

Definition at line 91 of file NumericalModel.f90.

92  class(NumericalModelType) :: this
93  type(sparsematrix), intent(inout) :: sparse

◆ model_ad()

subroutine numericalmodelmodule::model_ad ( class(numericalmodeltype this)
private

Definition at line 109 of file NumericalModel.f90.

110  class(NumericalModelType) :: this

◆ model_ar()

subroutine numericalmodelmodule::model_ar ( class(numericalmodeltype this)
private

Definition at line 101 of file NumericalModel.f90.

102  class(NumericalModelType) :: this

◆ model_bd()

subroutine numericalmodelmodule::model_bd ( class(numericalmodeltype this,
integer(i4b), intent(in)  icnvg,
integer(i4b), intent(in)  isuppress_output 
)
private

Definition at line 191 of file NumericalModel.f90.

192  class(NumericalModelType) :: this
193  integer(I4B), intent(in) :: icnvg
194  integer(I4B), intent(in) :: isuppress_output

◆ model_bdcalc()

subroutine numericalmodelmodule::model_bdcalc ( class(numericalmodeltype this,
integer(i4b), intent(in)  icnvg 
)
private

Definition at line 197 of file NumericalModel.f90.

198  class(NumericalModelType) :: this
199  integer(I4B), intent(in) :: icnvg

◆ model_bdentry()

subroutine numericalmodelmodule::model_bdentry ( class(numericalmodeltype this,
real(dp), dimension(:, :), intent(in)  budterm,
character(len=lenbudtxt), dimension(:), intent(in)  budtxt,
character(len=*), intent(in)  rowlabel 
)
private

Definition at line 211 of file NumericalModel.f90.

212  class(NumericalModelType) :: this
213  real(DP), dimension(:, :), intent(in) :: budterm
214  character(len=LENBUDTXT), dimension(:), intent(in) :: budtxt
215  character(len=*), intent(in) :: rowlabel

◆ model_bdsave()

subroutine numericalmodelmodule::model_bdsave ( class(numericalmodeltype this,
integer(i4b), intent(in)  icnvg 
)
private

Definition at line 202 of file NumericalModel.f90.

203  class(NumericalModelType) :: this
204  integer(I4B), intent(in) :: icnvg

◆ model_cc()

subroutine numericalmodelmodule::model_cc ( class(numericalmodeltype this,
integer(i4b), intent(in)  innertot,
integer(i4b), intent(in)  kiter,
integer(i4b), intent(in)  iend,
integer(i4b), intent(in)  icnvgmod,
character(len=lenpakloc), intent(inout)  cpak,
integer(i4b), intent(inout)  ipak,
real(dp), intent(inout)  dpak 
)
private

Definition at line 163 of file NumericalModel.f90.

164  class(NumericalModelType) :: this
165  integer(I4B), intent(in) :: innertot
166  integer(I4B), intent(in) :: kiter
167  integer(I4B), intent(in) :: iend
168  integer(I4B), intent(in) :: icnvgmod
169  character(len=LENPAKLOC), intent(inout) :: cpak
170  integer(I4B), intent(inout) :: ipak
171  real(DP), intent(inout) :: dpak

◆ model_cf()

subroutine numericalmodelmodule::model_cf ( class(numericalmodeltype this,
integer(i4b), intent(in)  kiter 
)
private

Definition at line 131 of file NumericalModel.f90.

132  class(NumericalModelType) :: this
133  integer(I4B), intent(in) :: kiter

◆ model_cq()

subroutine numericalmodelmodule::model_cq ( class(numericalmodeltype this,
integer(i4b), intent(in)  icnvg,
integer(i4b), intent(in)  isuppress_output 
)
private

Definition at line 185 of file NumericalModel.f90.

186  class(NumericalModelType) :: this
187  integer(I4B), intent(in) :: icnvg
188  integer(I4B), intent(in) :: isuppress_output

◆ model_da()

subroutine numericalmodelmodule::model_da ( class(numericalmodeltype this)
private

Definition at line 222 of file NumericalModel.f90.

223  ! -- modules
225  class(NumericalModelType) :: this
226 
227  ! -- Scalars
228  call mem_deallocate(this%neq)
229  call mem_deallocate(this%nja)
230  call mem_deallocate(this%icnvg)
231  call mem_deallocate(this%moffset)
232  deallocate (this%filename)
233  !
234  ! -- Arrays
235  call mem_deallocate(this%xold)
236  call mem_deallocate(this%flowja, 'FLOWJA', this%memoryPath)
237  call mem_deallocate(this%idxglo)
238  !
239  ! -- derived types
240  call this%bndlist%Clear()
241  deallocate (this%bndlist)
242  !
243  ! -- nullify pointers
244  call mem_deallocate(this%x, 'X', this%memoryPath)
245  call mem_deallocate(this%rhs, 'RHS', this%memoryPath)
246  call mem_deallocate(this%ibound, 'IBOUND', this%memoryPath)
247  !
248  ! -- BaseModelType
249  call this%BaseModelType%model_da()
250  !

◆ model_df()

subroutine numericalmodelmodule::model_df ( class(numericalmodeltype this)
private

Definition at line 87 of file NumericalModel.f90.

88  class(NumericalModelType) :: this

◆ model_fc()

subroutine numericalmodelmodule::model_fc ( class(numericalmodeltype this,
integer(i4b), intent(in)  kiter,
class(matrixbasetype), pointer  matrix_sln,
integer(i4b), intent(in)  inwtflag 
)
private

Definition at line 136 of file NumericalModel.f90.

137  class(NumericalModelType) :: this
138  integer(I4B), intent(in) :: kiter
139  class(MatrixBaseType), pointer :: matrix_sln
140  integer(I4B), intent(in) :: inwtflag

◆ model_fp()

subroutine numericalmodelmodule::model_fp ( class(numericalmodeltype this)
private

Definition at line 218 of file NumericalModel.f90.

219  class(NumericalModelType) :: this

◆ model_mc()

subroutine numericalmodelmodule::model_mc ( class(numericalmodeltype this,
class(matrixbasetype), pointer  matrix_sln 
)
private

Definition at line 96 of file NumericalModel.f90.

97  class(NumericalModelType) :: this
98  class(MatrixBaseType), pointer :: matrix_sln

◆ model_nr()

subroutine numericalmodelmodule::model_nr ( class(numericalmodeltype this,
integer(i4b), intent(in)  kiter,
class(matrixbasetype), pointer  matrix,
integer(i4b), intent(in)  inwtflag 
)
private

Definition at line 156 of file NumericalModel.f90.

157  class(NumericalModelType) :: this
158  integer(I4B), intent(in) :: kiter
159  class(MatrixBaseType), pointer :: matrix
160  integer(I4B), intent(in) :: inwtflag

◆ model_nur()

subroutine numericalmodelmodule::model_nur ( class(numericalmodeltype this,
integer(i4b), intent(in)  neqmod,
real(dp), dimension(neqmod), intent(inout)  x,
real(dp), dimension(neqmod), intent(in)  xtemp,
real(dp), dimension(neqmod), intent(inout)  dx,
integer(i4b), intent(inout)  inewtonur,
real(dp), intent(inout)  dxmax,
integer(i4b), intent(inout)  locmax 
)
private

Definition at line 174 of file NumericalModel.f90.

175  class(NumericalModelType) :: this
176  integer(I4B), intent(in) :: neqmod
177  real(DP), dimension(neqmod), intent(inout) :: x
178  real(DP), dimension(neqmod), intent(in) :: xtemp
179  real(DP), dimension(neqmod), intent(inout) :: dx
180  integer(I4B), intent(inout) :: inewtonur
181  real(DP), intent(inout) :: dxmax
182  integer(I4B), intent(inout) :: locmax

◆ model_ot()

subroutine numericalmodelmodule::model_ot ( class(numericalmodeltype this)
private

Definition at line 207 of file NumericalModel.f90.

208  class(NumericalModelType) :: this

◆ model_ptc()

subroutine numericalmodelmodule::model_ptc ( class(numericalmodeltype this,
class(vectorbasetype), pointer  vec_residual,
integer(i4b), intent(inout)  iptc,
real(dp), intent(inout)  ptcf 
)
private

Definition at line 149 of file NumericalModel.f90.

150  class(NumericalModelType) :: this
151  class(VectorBaseType), pointer :: vec_residual
152  integer(I4B), intent(inout) :: iptc
153  real(DP), intent(inout) :: ptcf

◆ model_ptcchk()

subroutine numericalmodelmodule::model_ptcchk ( class(numericalmodeltype this,
integer(i4b), intent(inout)  iptc 
)
private

Definition at line 143 of file NumericalModel.f90.

144  class(NumericalModelType) :: this
145  integer(I4B), intent(inout) :: iptc
146  iptc = 0

◆ model_reset()

subroutine numericalmodelmodule::model_reset ( class(numericalmodeltype this)
private

Definition at line 113 of file NumericalModel.f90.

114  use bndmodule, only: bndtype, getbndfromlist
115  class(NumericalModelType) :: this
116  ! local
117  class(BndType), pointer :: packobj
118  integer(I4B) :: ip
119 
120  do ip = 1, this%bndlist%Count()
121  packobj => getbndfromlist(this%bndlist, ip)
122  call packobj%bnd_reset()
123  end do
124 
Here is the call graph for this function:

◆ model_rp()

subroutine numericalmodelmodule::model_rp ( class(numericalmodeltype this)
private

Definition at line 105 of file NumericalModel.f90.

106  class(NumericalModelType) :: this

◆ model_solve()

subroutine numericalmodelmodule::model_solve ( class(numericalmodeltype this)

Definition at line 127 of file NumericalModel.f90.

128  class(NumericalModelType) :: this

◆ set_iboundptr()

subroutine numericalmodelmodule::set_iboundptr ( class(numericalmodeltype this,
integer(i4b), dimension(:), intent(in), pointer, contiguous  iboundsln,
integer(i4b)  sln_offset,
character(len=*), intent(in)  varNameTgt,
character(len=*), intent(in)  memPathTgt 
)

Definition at line 344 of file NumericalModel.f90.

346  ! -- dummy
347  class(NumericalModelType) :: this
348  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: iboundsln
349  integer(I4B) :: sln_offset
350  character(len=*), intent(in) :: varNameTgt
351  character(len=*), intent(in) :: memPathTgt
352  ! -- local
353  integer(I4B) :: offset
354  ! -- code
355  offset = this%moffset - sln_offset
356  this%ibound => iboundsln(offset + 1:offset + this%neq)
357  call mem_checkin(this%ibound, 'IBOUND', this%memoryPath, varnametgt, &
358  mempathtgt)

◆ set_idsoln()

subroutine numericalmodelmodule::set_idsoln ( class(numericalmodeltype this,
integer(i4b), intent(in)  id 
)
private

Definition at line 267 of file NumericalModel.f90.

268  class(NumericalModelType) :: this
269  integer(I4B), intent(in) :: id
270  this%idsoln = id

◆ set_moffset()

subroutine numericalmodelmodule::set_moffset ( class(numericalmodeltype this,
integer(i4b), intent(in)  moffset 
)

Definition at line 253 of file NumericalModel.f90.

254  class(NumericalModelType) :: this
255  integer(I4B), intent(in) :: moffset
256  this%moffset = moffset

◆ set_rhsptr()

subroutine numericalmodelmodule::set_rhsptr ( class(numericalmodeltype this,
real(dp), dimension(:), intent(in), pointer, contiguous  rhssln,
integer(i4b)  sln_offset,
character(len=*), intent(in)  varNameTgt,
character(len=*), intent(in)  memPathTgt 
)

Definition at line 328 of file NumericalModel.f90.

330  ! -- dummy
331  class(NumericalModelType) :: this
332  real(DP), dimension(:), pointer, contiguous, intent(in) :: rhssln
333  integer(I4B) :: sln_offset
334  character(len=*), intent(in) :: varNameTgt
335  character(len=*), intent(in) :: memPathTgt
336  ! -- local
337  integer(I4B) :: offset
338  ! -- code
339  offset = this%moffset - sln_offset
340  this%rhs => rhssln(offset + 1:offset + this%neq)
341  call mem_checkin(this%rhs, 'RHS', this%memoryPath, varnametgt, mempathtgt)

◆ set_xptr()

subroutine numericalmodelmodule::set_xptr ( class(numericalmodeltype this,
real(dp), dimension(:), intent(in), pointer, contiguous  xsln,
integer(i4b)  sln_offset,
character(len=*), intent(in)  varNameTgt,
character(len=*), intent(in)  memPathTgt 
)

Definition at line 312 of file NumericalModel.f90.

314  ! -- dummy
315  class(NumericalModelType) :: this
316  real(DP), dimension(:), pointer, contiguous, intent(in) :: xsln
317  integer(I4B) :: sln_offset
318  character(len=*), intent(in) :: varNameTgt
319  character(len=*), intent(in) :: memPathTgt
320  ! -- local
321  integer(I4B) :: offset
322  ! -- code
323  offset = this%moffset - sln_offset
324  this%x => xsln(offset + 1:offset + this%neq)
325  call mem_checkin(this%x, 'X', this%memoryPath, varnametgt, mempathtgt)