MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
basedismodule Module Reference

Data Types

type  disbasetype
 

Functions/Subroutines

subroutine dis_df (this)
 Define the discretization. More...
 
subroutine dis_ac (this, moffset, sparse)
 Add connections to sparse cell connectivity matrix. More...
 
subroutine dis_mc (this, moffset, idxglo, matrix_sln)
 Map cell connections in the numerical solution coefficient matrix. More...
 
subroutine dis_ar (this, icelltype)
 Allocate and setup variables, and write binary grid file. More...
 
subroutine write_grb (this, icelltype)
 Write a binary grid file. More...
 
subroutine dis_da (this)
 @brier Deallocate variables More...
 
subroutine nodeu_to_string (this, nodeu, str)
 Convert a user nodenumber to a string (nodenumber), (k,j), or (k,i,j) More...
 
subroutine nodeu_to_array (this, nodeu, arr)
 Convert a user nodenumber to an array (nodenumber), (k,j), or (k,i,j) More...
 
integer(i4b) function get_nodeuser (this, noder)
 Convert a reduced nodenumber to a user node number. More...
 
integer(i4b) function get_nodenumber_idx1 (this, nodeu, icheck)
 
integer(i4b) function get_nodenumber_idx2 (this, k, j, icheck)
 
integer(i4b) function get_nodenumber_idx3 (this, k, i, j, icheck)
 
subroutine connection_normal (this, noden, nodem, ihc, xcomp, ycomp, zcomp, ipos)
 Get normal vector components between the cell and a given neighbor. The normal points outward from the shared face between noden and nodem. More...
 
subroutine connection_vector (this, noden, nodem, nozee, satn, satm, ihc, xcomp, ycomp, zcomp, conlen)
 Get unit vector components between the cell and a given neighbor. Saturation must be provided to compute cell center vertical coordinates. Also return the straight-line connection length. More...
 
subroutine, public dis_transform_xy (x, y, xorigin, yorigin, angrot, xglo, yglo)
 Get global (x, y) coordinates from cell-local coordinates. More...
 
subroutine get_dis_type (this, dis_type)
 Get the discretization type (DIS, DISV, or DISU) More...
 
integer(i4b) function get_dis_enum (this)
 Get the discretization type enumeration. More...
 
subroutine allocate_scalars (this, name_model, input_mempath)
 Allocate and initialize scalar variables. More...
 
subroutine allocate_arrays (this)
 Allocate and initialize arrays. More...
 
integer(i4b) function nodeu_from_string (this, lloc, istart, istop, in, iout, line, flag_string, allow_zero)
 Convert a string to a user nodenumber. More...
 
integer(i4b) function nodeu_from_cellid (this, cellid, inunit, iout, flag_string, allow_zero)
 Convert a cellid string to a user nodenumber. More...
 
integer(i4b) function noder_from_string (this, lloc, istart, istop, in, iout, line, flag_string)
 Convert a string to a reduced nodenumber. More...
 
integer(i4b) function noder_from_cellid (this, cellid, inunit, iout, flag_string, allow_zero)
 Convert cellid string to reduced nodenumber. More...
 
logical function supports_layers (this)
 Indicates whether the grid discretization supports layers. More...
 
integer(i4b) function get_ncpl (this)
 Return number of cells per layer. This is nodes for a DISU grid, as there are no layers. More...
 
real(dp) function get_cell_volume (this, n, x)
 Return volume of cell n based on x value passed. More...
 
subroutine get_polyverts (this, ic, polyverts, closed)
 Get a 2D array of cell polygon vertices, in clockwise order starting with the lower left corner. More...
 
integer(i4b) function get_npolyverts (this, ic, closed)
 Get the number of cell polygon vertices. More...
 
integer(i4b) function get_max_npolyverts (this, closed)
 Get the maximum number of cell polygon vertices. More...
 
subroutine read_int_array (this, line, lloc, istart, istop, iout, in, iarray, aname)
 Read an integer array. More...
 
subroutine read_dbl_array (this, line, lloc, istart, istop, iout, in, darray, aname)
 Read a double precision array. More...
 
subroutine fill_int_array (this, ibuff1, ibuff2)
 Fill an integer array. More...
 
subroutine fill_dbl_array (this, buff1, buff2)
 Fill a double precision array. More...
 
subroutine read_list (this, line_reader, in, iout, iprpak, nlist, inamedbound, iauxmultcol, nodelist, rlist, auxvar, auxname, boundname, label, pkgname, tsManager, iscloc, indxconvertflux)
 Read a list using the list reader. More...
 
subroutine read_layer_array (this, nodelist, darray, ncolbnd, maxbnd, icolbnd, aname, inunit, iout)
 Read a 2d double array into col icolbnd of darray. More...
 
subroutine record_array (this, darray, iout, iprint, idataun, aname, cdatafmp, nvaluesp, nwidthp, editdesc, dinact)
 Record a double precision array. More...
 
subroutine record_connection_array (this, flowja, ibinun, iout)
 Record a connection-based double precision array. More...
 
subroutine noder_to_string (this, noder, str)
 Convert reduced node number to string (nodenumber), (k,j) or (k,i,j) More...
 
subroutine noder_to_array (this, noder, arr)
 Convert reduced node number to array (nodenumber), (k,j) or (k,i,j) More...
 
subroutine record_srcdst_list_header (this, text, textmodel, textpackage, dstmodel, dstpackage, naux, auxtxt, ibdchn, nlist, iout)
 Record list header for imeth=6. More...
 
subroutine record_srcdst_list_entry (this, ibdchn, noder, noder2, q, naux, aux, olconv, olconv2)
 Record list header. More...
 
subroutine nlarray_to_nodelist (this, darray, nodelist, maxbnd, nbound, aname)
 Convert an integer array to nodelist. More...
 
subroutine highest_active (this, n, ibound)
 Find the first highest active cell beneath cell n. More...
 
subroutine highest_saturated (this, n, sat)
 Find the first saturated cell beneath cell n. More...
 
real(dp) function get_area (this, node)
 Return the cell area for the given node. More...
 
real(dp) function get_area_factor (this, node, idx_conn)
 @ brief Calculate the area factor for the cell connection More...
 
subroutine get_flow_width (this, n, m, idx_conn, width_n, width_m)
 @ brief Calculate the flow width between two cells More...
 
logical(lgp) function is_3d (this)
 @Brief return true if grid is three dimensional More...
 
logical(lgp) function is_2d (this)
 @Brief return true if grid is two dimensional More...
 
logical(lgp) function is_1d (this)
 @Brief return true if grid is one dimensional More...
 

Function/Subroutine Documentation

◆ allocate_arrays()

subroutine basedismodule::allocate_arrays ( class(disbasetype this)
private

Definition at line 463 of file DiscretizationBase.f90.

464  class(DisBaseType) :: this
465  integer :: isize
466  !
467  ! -- Allocate
468  call mem_allocate(this%mshape, this%ndim, 'MSHAPE', this%memoryPath)
469  call mem_allocate(this%xc, this%nodes, 'XC', this%memoryPath)
470  call mem_allocate(this%yc, this%nodes, 'YC', this%memoryPath)
471  call mem_allocate(this%top, this%nodes, 'TOP', this%memoryPath)
472  call mem_allocate(this%bot, this%nodes, 'BOT', this%memoryPath)
473  call mem_allocate(this%area, this%nodes, 'AREA', this%memoryPath)
474  !
475  ! -- Initialize
476  this%mshape(1) = this%nodes
477  !
478  ! -- Determine size of buff memory
479  if (this%nodes < this%nodesuser) then
480  isize = this%nodesuser
481  else
482  isize = this%nodes
483  end if
484  !
485  ! -- Allocate the arrays
486  call mem_allocate(this%dbuff, isize, 'DBUFF', this%name_model)
487  call mem_allocate(this%ibuff, isize, 'IBUFF', this%name_model)

◆ allocate_scalars()

subroutine basedismodule::allocate_scalars ( class(disbasetype this,
character(len=*), intent(in)  name_model,
character(len=*), intent(in)  input_mempath 
)

Definition at line 404 of file DiscretizationBase.f90.

405  ! -- dummy
406  class(DisBaseType) :: this
407  character(len=*), intent(in) :: name_model
408  character(len=*), intent(in) :: input_mempath
409  logical(LGP) :: found
410  !
411  ! -- Create memory path
412  this%memoryPath = create_mem_path(name_model, 'DIS')
413  !
414  ! -- Allocate
415  allocate (this%name_model)
416  allocate (this%input_fname)
417  allocate (this%output_fname)
418  !
419  call mem_allocate(this%inunit, 'INUNIT', this%memoryPath)
420  call mem_allocate(this%iout, 'IOUT', this%memoryPath)
421  call mem_allocate(this%nodes, 'NODES', this%memoryPath)
422  call mem_allocate(this%nodesuser, 'NODESUSER', this%memoryPath)
423  call mem_allocate(this%ndim, 'NDIM', this%memoryPath)
424  call mem_allocate(this%icondir, 'ICONDIR', this%memoryPath)
425  call mem_allocate(this%nogrb, 'NOGRB', this%memoryPath)
426  call mem_allocate(this%xorigin, 'XORIGIN', this%memoryPath)
427  call mem_allocate(this%yorigin, 'YORIGIN', this%memoryPath)
428  call mem_allocate(this%angrot, 'ANGROT', this%memoryPath)
429  call mem_allocate(this%nja, 'NJA', this%memoryPath)
430  call mem_allocate(this%njas, 'NJAS', this%memoryPath)
431  call mem_allocate(this%lenuni, 'LENUNI', this%memoryPath)
432  !
433  ! -- Initialize
434  this%name_model = name_model
435  this%input_mempath = input_mempath
436  this%input_fname = ''
437  this%output_fname = ''
438  this%inunit = 0
439  this%iout = 0
440  this%nodes = 0
441  this%nodesuser = 0
442  this%ndim = 1
443  this%icondir = 1
444  this%nogrb = 0
445  this%xorigin = dzero
446  this%yorigin = dzero
447  this%angrot = dzero
448  this%nja = 0
449  this%njas = 0
450  this%lenuni = 0
451  !
452  ! -- update input and output filenames
453  call mem_set_value(this%input_fname, 'INPUT_FNAME', &
454  this%input_mempath, found)
455  call mem_set_value(this%output_fname, 'GRB6_FILENAME', &
456  this%input_mempath, found)
457  if (.not. found) then
458  this%output_fname = trim(this%input_fname)//'.grb'
459  end if
Here is the call graph for this function:

◆ connection_normal()

subroutine basedismodule::connection_normal ( class(disbasetype this,
integer(i4b), intent(in)  noden,
integer(i4b), intent(in)  nodem,
integer(i4b), intent(in)  ihc,
real(dp), intent(inout)  xcomp,
real(dp), intent(inout)  ycomp,
real(dp), intent(inout)  zcomp,
integer(i4b), intent(in)  ipos 
)
private
Parameters
[in]nodencell (reduced nn)
[in]nodemneighbor (reduced nn)
[in]ihchorizontal connection flag

Definition at line 319 of file DiscretizationBase.f90.

321  class(DisBaseType) :: this
322  integer(I4B), intent(in) :: noden !< cell (reduced nn)
323  integer(I4B), intent(in) :: nodem !< neighbor (reduced nn)
324  integer(I4B), intent(in) :: ihc !< horizontal connection flag
325  real(DP), intent(inout) :: xcomp
326  real(DP), intent(inout) :: ycomp
327  real(DP), intent(inout) :: zcomp
328  integer(I4B), intent(in) :: ipos
329 
330  call store_error('Programmer error: connection_normal must be overridden', &
331  terminate=.true.)
Here is the call graph for this function:

◆ connection_vector()

subroutine basedismodule::connection_vector ( class(disbasetype this,
integer(i4b), intent(in)  noden,
integer(i4b), intent(in)  nodem,
logical, intent(in)  nozee,
real(dp), intent(in)  satn,
real(dp), intent(in)  satm,
integer(i4b), intent(in)  ihc,
real(dp), intent(inout)  xcomp,
real(dp), intent(inout)  ycomp,
real(dp), intent(inout)  zcomp,
real(dp), intent(inout)  conlen 
)
private
Parameters
[in]nodencell (reduced nn)
[in]nodemneighbor (reduced nn)
[in]ihchorizontal connection flag

Definition at line 337 of file DiscretizationBase.f90.

339  class(DisBaseType) :: this
340  integer(I4B), intent(in) :: noden !< cell (reduced nn)
341  integer(I4B), intent(in) :: nodem !< neighbor (reduced nn)
342  logical, intent(in) :: nozee
343  real(DP), intent(in) :: satn
344  real(DP), intent(in) :: satm
345  integer(I4B), intent(in) :: ihc !< horizontal connection flag
346  real(DP), intent(inout) :: xcomp
347  real(DP), intent(inout) :: ycomp
348  real(DP), intent(inout) :: zcomp
349  real(DP), intent(inout) :: conlen
350 
351  call store_error('Programmer error: connection_vector must be overridden', &
352  terminate=.true.)
Here is the call graph for this function:

◆ dis_ac()

subroutine basedismodule::dis_ac ( class(disbasetype this,
integer(i4b), intent(in)  moffset,
type(sparsematrix), intent(inout)  sparse 
)
private

Definition at line 138 of file DiscretizationBase.f90.

139  ! -- modules
140  use sparsemodule, only: sparsematrix
141  ! -- dummy
142  class(DisBaseType) :: this
143  integer(I4B), intent(in) :: moffset
144  type(sparsematrix), intent(inout) :: sparse
145  ! -- local
146  integer(I4B) :: i, j, ipos, iglo, jglo
147  !
148  do i = 1, this%nodes
149  do ipos = this%con%ia(i), this%con%ia(i + 1) - 1
150  j = this%con%ja(ipos)
151  iglo = i + moffset
152  jglo = j + moffset
153  call sparse%addconnection(iglo, jglo, 1)
154  end do
155  end do

◆ dis_ar()

subroutine basedismodule::dis_ar ( class(disbasetype this,
integer(i4b), dimension(:), intent(in)  icelltype 
)
private

Definition at line 179 of file DiscretizationBase.f90.

180  ! -- dummy
181  class(DisBaseType) :: this
182  integer(I4B), dimension(:), intent(in) :: icelltype
183  ! -- local
184  integer(I4B), dimension(:), allocatable :: ict
185  integer(I4B) :: nu, nr
186  !
187  ! -- Expand icelltype to full grid; fill with 0 if cell is excluded
188  allocate (ict(this%nodesuser))
189  do nu = 1, this%nodesuser
190  nr = this%get_nodenumber(nu, 0)
191  if (nr > 0) then
192  ict(nu) = icelltype(nr)
193  else
194  ict(nu) = 0
195  end if
196  end do
197  !
198  if (this%nogrb == 0) call this%write_grb(ict)

◆ dis_da()

subroutine basedismodule::dis_da ( class(disbasetype this)
private

Definition at line 210 of file DiscretizationBase.f90.

211  ! -- modules
213  ! -- dummy
214  class(DisBaseType) :: this
215  !
216  ! -- Strings
217  deallocate (this%name_model)
218  deallocate (this%input_fname)
219  deallocate (this%output_fname)
220  !
221  ! -- Scalars
222  call mem_deallocate(this%inunit)
223  call mem_deallocate(this%iout)
224  call mem_deallocate(this%nodes)
225  call mem_deallocate(this%nodesuser)
226  call mem_deallocate(this%ndim)
227  call mem_deallocate(this%icondir)
228  call mem_deallocate(this%nogrb)
229  call mem_deallocate(this%xorigin)
230  call mem_deallocate(this%yorigin)
231  call mem_deallocate(this%angrot)
232  call mem_deallocate(this%nja)
233  call mem_deallocate(this%njas)
234  call mem_deallocate(this%lenuni)
235  !
236  ! -- Arrays
237  call mem_deallocate(this%mshape)
238  call mem_deallocate(this%xc)
239  call mem_deallocate(this%yc)
240  call mem_deallocate(this%top)
241  call mem_deallocate(this%bot)
242  call mem_deallocate(this%area)
243  call mem_deallocate(this%dbuff)
244  call mem_deallocate(this%ibuff)
245  !
246  ! -- Connections
247  call this%con%con_da()
248  deallocate (this%con)

◆ dis_df()

subroutine basedismodule::dis_df ( class(disbasetype this)
private

Definition at line 131 of file DiscretizationBase.f90.

132  class(DisBaseType) :: this
133  call store_error('Programmer error: dis_df must be overridden', &
134  terminate=.true.)
Here is the call graph for this function:

◆ dis_mc()

subroutine basedismodule::dis_mc ( class(disbasetype this,
integer(i4b), intent(in)  moffset,
integer(i4b), dimension(:), intent(inout)  idxglo,
class(matrixbasetype), pointer  matrix_sln 
)

Definition at line 159 of file DiscretizationBase.f90.

160  ! -- dummy
161  class(DisBaseType) :: this
162  integer(I4B), intent(in) :: moffset
163  integer(I4B), dimension(:), intent(inout) :: idxglo
164  class(MatrixBaseType), pointer :: matrix_sln
165  ! -- local
166  integer(I4B) :: i, j, ipos, iglo, jglo
167  !
168  do i = 1, this%nodes
169  iglo = i + moffset
170  do ipos = this%con%ia(i), this%con%ia(i + 1) - 1
171  j = this%con%ja(ipos)
172  jglo = j + moffset
173  idxglo(ipos) = matrix_sln%get_position(iglo, jglo)
174  end do
175  end do

◆ dis_transform_xy()

subroutine, public basedismodule::dis_transform_xy ( real(dp), intent(in)  x,
real(dp), intent(in)  y,
real(dp), intent(in)  xorigin,
real(dp), intent(in)  yorigin,
real(dp), intent(in)  angrot,
real(dp), intent(out)  xglo,
real(dp), intent(out)  yglo 
)
Parameters
[in]xthe cell-x coordinate to transform
[in]ythe cell-y coordinate to transform
[in]xoriginthe cell-y coordinate to transform
[in]yoriginthe cell-y coordinate to transform
[in]angrotthe cell-y coordinate to transform
[out]xglothe global cell-x coordinate
[out]yglothe global cell-y coordinate

Definition at line 356 of file DiscretizationBase.f90.

357  real(DP), intent(in) :: x !< the cell-x coordinate to transform
358  real(DP), intent(in) :: y !< the cell-y coordinate to transform
359  real(DP), intent(in) :: xorigin !< the cell-y coordinate to transform
360  real(DP), intent(in) :: yorigin !< the cell-y coordinate to transform
361  real(DP), intent(in) :: angrot !< the cell-y coordinate to transform
362  real(DP), intent(out) :: xglo !< the global cell-x coordinate
363  real(DP), intent(out) :: yglo !< the global cell-y coordinate
364  ! local
365  real(DP) :: ang
366 
367  xglo = x
368  yglo = y
369 
370  ! first _rotate_ to 'real world'
371  ang = angrot * dpio180
372  if (ang /= dzero) then
373  xglo = x * cos(ang) - y * sin(ang)
374  yglo = x * sin(ang) + y * cos(ang)
375  end if
376 
377  ! then _translate_
378  xglo = xglo + xorigin
379  yglo = yglo + yorigin
Here is the caller graph for this function:

◆ fill_dbl_array()

subroutine basedismodule::fill_dbl_array ( class(disbasetype), intent(inout)  this,
real(dp), dimension(:), intent(in), pointer, contiguous  buff1,
real(dp), dimension(:), intent(inout), pointer, contiguous  buff2 
)
private

Definition at line 767 of file DiscretizationBase.f90.

768  ! -- dummy
769  class(DisBaseType), intent(inout) :: this
770  real(DP), dimension(:), pointer, contiguous, intent(in) :: buff1
771  real(DP), dimension(:), pointer, contiguous, intent(inout) :: buff2
772  ! -- local
773  integer(I4B) :: nodeu
774  integer(I4B) :: noder
775 
776  do nodeu = 1, this%nodesuser
777  noder = this%get_nodenumber(nodeu, 0)
778  if (noder <= 0) cycle
779  buff2(noder) = buff1(nodeu)
780  end do
Here is the caller graph for this function:

◆ fill_int_array()

subroutine basedismodule::fill_int_array ( class(disbasetype), intent(inout)  this,
integer(i4b), dimension(:), intent(in), pointer, contiguous  ibuff1,
integer(i4b), dimension(:), intent(inout), pointer, contiguous  ibuff2 
)
private

Definition at line 750 of file DiscretizationBase.f90.

751  ! -- dummy
752  class(DisBaseType), intent(inout) :: this
753  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: ibuff1
754  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: ibuff2
755  ! -- local
756  integer(I4B) :: nodeu
757  integer(I4B) :: noder
758 
759  do nodeu = 1, this%nodesuser
760  noder = this%get_nodenumber(nodeu, 0)
761  if (noder <= 0) cycle
762  ibuff2(noder) = ibuff1(nodeu)
763  end do
Here is the caller graph for this function:

◆ get_area()

real(dp) function basedismodule::get_area ( class(disbasetype this,
integer(i4b), intent(in)  node 
)
private
Parameters
[in]nodereduced node number

Definition at line 1177 of file DiscretizationBase.f90.

1178  class(DisBaseType) :: this
1179  integer(I4B), intent(in) :: node !< reduced node number
1180  real(DP) :: area
1181 
1182  area = this%area(node)

◆ get_area_factor()

real(dp) function basedismodule::get_area_factor ( class(disbasetype this,
integer(i4b), intent(in)  node,
integer(i4b), intent(in)  idx_conn 
)
private

Function calculates the area factor for the cell connection. The sum of all area factors for all cell connections to overlying or underlying cells cells will be 1.

TODO: confirm that this works for cells that are only partially covered by overlying or underlying cells.

Returns
connection cell area factor
Parameters
[in]nodecell node number
[in]idx_connconnection index

Definition at line 1194 of file DiscretizationBase.f90.

1195  ! -- return
1196  real(DP) :: area_factor !< connection cell area factor
1197  ! -- dummy
1198  class(DisBaseType) :: this
1199  integer(I4B), intent(in) :: node !< cell node number
1200  integer(I4B), intent(in) :: idx_conn !< connection index
1201  ! -- local
1202  real(DP) :: area_node
1203  real(DP) :: area_conn
1204  !
1205  ! -- calculate the cell area fraction
1206  area_node = this%area(node)
1207  area_conn = this%con%hwva(idx_conn)
1208  !
1209  ! -- return the cell area factor
1210  area_factor = area_conn / area_node

◆ get_cell_volume()

real(dp) function basedismodule::get_cell_volume ( class(disbasetype this,
integer(i4b), intent(in)  n,
real(dp), intent(in)  x 
)
private

Definition at line 659 of file DiscretizationBase.f90.

660  ! -- return
661  real(DP) :: get_cell_volume
662  ! -- dummy
663  class(DisBaseType) :: this
664  integer(I4B), intent(in) :: n
665  real(DP), intent(in) :: x
666  ! -- local
667  real(DP) :: tp
668  real(DP) :: bt
669  real(DP) :: sat
670  real(DP) :: thick
671 
672  get_cell_volume = dzero
673  tp = this%top(n)
674  bt = this%bot(n)
675  sat = squadraticsaturation(tp, bt, x)
676  thick = (tp - bt) * sat
677  get_cell_volume = this%area(n) * thick
Here is the call graph for this function:

◆ get_dis_enum()

integer(i4b) function basedismodule::get_dis_enum ( class(disbasetype), intent(in)  this)
private

Definition at line 393 of file DiscretizationBase.f90.

394  use constantsmodule, only: disundef
395  class(DisBaseType), intent(in) :: this
396  integer(I4B) :: dis_enum
397 
398  dis_enum = disundef
399  call store_error('Programmer error: get_dis_enum must be overridden', &
400  terminate=.true.)
This module contains simulation constants.
Definition: Constants.f90:9
@ disundef
undefined discretization
Definition: Constants.f90:153
Here is the call graph for this function:

◆ get_dis_type()

subroutine basedismodule::get_dis_type ( class(disbasetype), intent(in)  this,
character(len=*), intent(out)  dis_type 
)
private

Definition at line 383 of file DiscretizationBase.f90.

384  class(DisBaseType), intent(in) :: this
385  character(len=*), intent(out) :: dis_type
386 
387  dis_type = "Not implemented"
388  call store_error('Programmer error: get_dis_type must be overridden', &
389  terminate=.true.)
Here is the call graph for this function:

◆ get_flow_width()

subroutine basedismodule::get_flow_width ( class(disbasetype this,
integer(i4b), intent(in)  n,
integer(i4b), intent(in)  m,
integer(i4b), intent(in)  idx_conn,
real(dp), intent(out)  width_n,
real(dp), intent(out)  width_m 
)
private

This should only be called for connections with IHC > 0. Routine is needed, so it can be overridden by the linear network discretization, which allows for a separate flow

Parameters
[in]ncell node number
[in]mcell node number
[in]idx_connconnection index
[out]width_nflow width for cell n
[out]width_mflow width for cell m

Definition at line 1220 of file DiscretizationBase.f90.

1221  ! dummy
1222  class(DisBaseType) :: this
1223  integer(I4B), intent(in) :: n !< cell node number
1224  integer(I4B), intent(in) :: m !< cell node number
1225  integer(I4B), intent(in) :: idx_conn !< connection index
1226  real(DP), intent(out) :: width_n !< flow width for cell n
1227  real(DP), intent(out) :: width_m !< flow width for cell m
1228  ! local
1229  integer(I4B) :: isympos
1230 
1231  ! For general case, width_n = width_m
1232  isympos = this%con%jas(idx_conn)
1233  width_n = this%con%hwva(isympos)
1234  width_m = width_n
1235 

◆ get_max_npolyverts()

integer(i4b) function basedismodule::get_max_npolyverts ( class(disbasetype), intent(inout)  this,
logical(lgp), intent(in), optional  closed 
)
private
Parameters
[in]closedwhether to close the polygon, duplicating a vertex

Definition at line 704 of file DiscretizationBase.f90.

705  class(DisBaseType), intent(inout) :: this
706  logical(LGP), intent(in), optional :: closed !< whether to close the polygon, duplicating a vertex
707  integer(I4B) :: max_npolyverts
708  max_npolyverts = 0 ! suppress compiler warning
709  errmsg = 'Programmer error: get_max_npolyverts must be overridden'
710  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:

◆ get_ncpl()

integer(i4b) function basedismodule::get_ncpl ( class(disbasetype this)
private

Definition at line 650 of file DiscretizationBase.f90.

651  integer(I4B) :: get_ncpl
652  class(DisBaseType) :: this
653  get_ncpl = 0
654  call store_error('Programmer error: get_ncpl must be overridden', &
655  terminate=.true.)
Here is the call graph for this function:

◆ get_nodenumber_idx1()

integer(i4b) function basedismodule::get_nodenumber_idx1 ( class(disbasetype), intent(in)  this,
integer(i4b), intent(in)  nodeu,
integer(i4b), intent(in)  icheck 
)
private

Definition at line 284 of file DiscretizationBase.f90.

285  class(DisBaseType), intent(in) :: this
286  integer(I4B), intent(in) :: nodeu
287  integer(I4B), intent(in) :: icheck
288  integer(I4B) :: nodenumber
289 
290  nodenumber = 0
291  call store_error('Programmer error: get_nodenumber_idx1 must be overridden', &
292  terminate=.true.)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_nodenumber_idx2()

integer(i4b) function basedismodule::get_nodenumber_idx2 ( class(disbasetype), intent(in)  this,
integer(i4b), intent(in)  k,
integer(i4b), intent(in)  j,
integer(i4b), intent(in)  icheck 
)
private

Definition at line 295 of file DiscretizationBase.f90.

296  class(DisBaseType), intent(in) :: this
297  integer(I4B), intent(in) :: k, j
298  integer(I4B), intent(in) :: icheck
299  integer(I4B) :: nodenumber
300 
301  nodenumber = 0
302  call store_error('Programmer error: get_nodenumber_idx2 must be overridden', &
303  terminate=.true.)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_nodenumber_idx3()

integer(i4b) function basedismodule::get_nodenumber_idx3 ( class(disbasetype), intent(in)  this,
integer(i4b), intent(in)  k,
integer(i4b), intent(in)  i,
integer(i4b), intent(in)  j,
integer(i4b), intent(in)  icheck 
)
private

Definition at line 306 of file DiscretizationBase.f90.

307  class(DisBaseType), intent(in) :: this
308  integer(I4B), intent(in) :: k, i, j
309  integer(I4B), intent(in) :: icheck
310  integer(I4B) :: nodenumber
311 
312  nodenumber = 0
313  call store_error('Programmer error: get_nodenumber_idx3 must be overridden', &
314  terminate=.true.)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_nodeuser()

integer(i4b) function basedismodule::get_nodeuser ( class(disbasetype this,
integer(i4b), intent(in)  noder 
)
private

Definition at line 272 of file DiscretizationBase.f90.

273  class(DisBaseType) :: this
274  integer(I4B), intent(in) :: noder
275  integer(I4B) :: nodenumber
276 
277  if (this%nodes < this%nodesuser) then
278  nodenumber = this%nodeuser(noder)
279  else
280  nodenumber = noder
281  end if

◆ get_npolyverts()

integer(i4b) function basedismodule::get_npolyverts ( class(disbasetype), intent(inout)  this,
integer(i4b), intent(in)  ic,
logical(lgp), intent(in), optional  closed 
)
private
Parameters
[in]iccell number (reduced)
[in]closedwhether to close the polygon, duplicating a vertex

Definition at line 693 of file DiscretizationBase.f90.

694  class(DisBaseType), intent(inout) :: this
695  integer(I4B), intent(in) :: ic !< cell number (reduced)
696  logical(LGP), intent(in), optional :: closed !< whether to close the polygon, duplicating a vertex
697  integer(I4B) :: npolyverts
698  npolyverts = 0 ! suppress compiler warning
699  errmsg = 'Programmer error: get_npolyverts must be overridden'
700  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:

◆ get_polyverts()

subroutine basedismodule::get_polyverts ( class(disbasetype), intent(inout)  this,
integer(i4b), intent(in)  ic,
real(dp), dimension(:, :), intent(out), allocatable  polyverts,
logical(lgp), intent(in), optional  closed 
)
private
Parameters
[in]iccell number (reduced)
[out]polyvertspolygon vertices (column-major indexing)
[in]closedwhether to close the polygon, duplicating a vertex

Definition at line 682 of file DiscretizationBase.f90.

683  class(DisBaseType), intent(inout) :: this
684  integer(I4B), intent(in) :: ic !< cell number (reduced)
685  real(DP), allocatable, intent(out) :: polyverts(:, :) !< polygon vertices (column-major indexing)
686  logical(LGP), intent(in), optional :: closed !< whether to close the polygon, duplicating a vertex
687 
688  errmsg = 'Programmer error: get_polyverts must be overridden'
689  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:

◆ highest_active()

subroutine basedismodule::highest_active ( class(disbasetype this,
integer(i4b), intent(inout)  n,
integer(i4b), dimension(:), intent(in)  ibound 
)
private

Definition at line 1101 of file DiscretizationBase.f90.

1102  ! -- dummy
1103  class(DisBaseType) :: this
1104  integer(I4B), intent(inout) :: n
1105  integer(I4B), dimension(:), intent(in) :: ibound
1106  ! -- locals
1107  integer(I4B) :: m, ii, iis
1108  logical done, bottomcell
1109  !
1110  ! -- Loop through connected cells until the highest active one (including a
1111  ! constant head cell) is found. Return that cell as n.
1112  done = .false.
1113  do while (.not. done)
1114  bottomcell = .true.
1115  cloop: do ii = this%con%ia(n) + 1, this%con%ia(n + 1) - 1
1116  m = this%con%ja(ii)
1117  iis = this%con%jas(ii)
1118  if (this%con%ihc(iis) == 0 .and. m > n) then
1119  !
1120  ! -- this cannot be a bottom cell
1121  bottomcell = .false.
1122  !
1123  ! -- vertical down
1124  if (ibound(m) /= 0) then
1125  n = m
1126  done = .true.
1127  exit cloop
1128  else
1129  n = m
1130  exit cloop
1131  end if
1132  end if
1133  end do cloop
1134  if (bottomcell) done = .true.
1135  end do

◆ highest_saturated()

subroutine basedismodule::highest_saturated ( class(disbasetype this,
integer(i4b), intent(inout)  n,
real(dp), dimension(:), intent(in)  sat 
)
private

Definition at line 1139 of file DiscretizationBase.f90.

1140  ! -- dummy
1141  class(DisBaseType) :: this
1142  integer(I4B), intent(inout) :: n
1143  real(DP), dimension(:), intent(in) :: sat
1144  ! -- locals
1145  integer(I4B) :: m, ii, iis
1146  logical(LGP) :: is_done, bottomcell
1147  !
1148  ! -- Loop through connected cells until the highest saturated one (including a
1149  ! constant head cell) is found. Return that cell as n.
1150  is_done = .false.
1151  do while (.not. is_done)
1152  bottomcell = .true.
1153  cloop: do ii = this%con%ia(n) + 1, this%con%ia(n + 1) - 1
1154  m = this%con%ja(ii)
1155  iis = this%con%jas(ii)
1156  if (this%con%ihc(iis) == 0 .and. m > n) then
1157  !
1158  ! -- this cannot be a bottom cell
1159  bottomcell = .false.
1160  !
1161  ! -- vertical down
1162  if (sat(m) > dzero) then
1163  n = m
1164  is_done = .true.
1165  exit cloop
1166  else
1167  n = m
1168  exit cloop
1169  end if
1170  end if
1171  end do cloop
1172  if (bottomcell) is_done = .true.
1173  end do

◆ is_1d()

logical(lgp) function basedismodule::is_1d ( class(disbasetype this)
private

Definition at line 1265 of file DiscretizationBase.f90.

1266  ! dummy
1267  class(DisBaseType) :: this
1268  ! return
1269  logical(LGP) :: r
1270  r = .false.
1271  select case (this%get_dis_enum())
1272  case (dis1d, disv1d, disu1d)
1273  r = .true.
1274  end select

◆ is_2d()

logical(lgp) function basedismodule::is_2d ( class(disbasetype this)
private

Definition at line 1252 of file DiscretizationBase.f90.

1253  ! dummy
1254  class(DisBaseType) :: this
1255  ! return
1256  logical(LGP) :: r
1257  r = .false.
1258  select case (this%get_dis_enum())
1259  case (dis2d, disv2d, disu2d)
1260  r = .true.
1261  end select

◆ is_3d()

logical(lgp) function basedismodule::is_3d ( class(disbasetype this)
private

Definition at line 1239 of file DiscretizationBase.f90.

1240  ! dummy
1241  class(DisBaseType) :: this
1242  ! return
1243  logical(LGP) :: r
1244  r = .false.
1245  select case (this%get_dis_enum())
1246  case (dis, disv, disu)
1247  r = .true.
1248  end select

◆ nlarray_to_nodelist()

subroutine basedismodule::nlarray_to_nodelist ( class(disbasetype this,
integer(i4b), dimension(:), pointer, contiguous  darray,
integer(i4b), dimension(maxbnd), intent(inout)  nodelist,
integer(i4b), intent(in)  maxbnd,
integer(i4b), intent(inout)  nbound,
character(len=*), intent(in)  aname 
)
private

For DIS/DISV, the array is layer number, for DISU it's node number.

Definition at line 1088 of file DiscretizationBase.f90.

1089  class(DisBaseType) :: this
1090  integer(I4B), intent(in) :: maxbnd
1091  integer(I4B), dimension(:), pointer, contiguous :: darray
1092  integer(I4B), dimension(maxbnd), intent(inout) :: nodelist
1093  integer(I4B), intent(inout) :: nbound
1094  character(len=*), intent(in) :: aname
1095 
1096  errmsg = 'Programmer error: nlarray_to_nodelist must be overridden'
1097  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:

◆ noder_from_cellid()

integer(i4b) function basedismodule::noder_from_cellid ( class(disbasetype this,
character(len=*), intent(inout)  cellid,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout,
logical, intent(in), optional  flag_string,
logical, intent(in), optional  allow_zero 
)
private

If flag_string argument is present and true, the first token in string is allowed to be a string (e.g. boundary name). In this case, if a string is encountered, return value as -2. If allow_zero argument is present and true, if all indices equal zero, the result can be zero. If allow_zero is false, a zero in any index is an error.

Definition at line 594 of file DiscretizationBase.f90.

596  ! -- return
597  integer(I4B) :: noder
598  ! -- dummy
599  class(DisBaseType) :: this
600  character(len=*), intent(inout) :: cellid
601  integer(I4B), intent(in) :: inunit
602  integer(I4B), intent(in) :: iout
603  logical, optional, intent(in) :: flag_string
604  logical, optional, intent(in) :: allow_zero
605  ! -- local
606  integer(I4B) :: nodeu
607  logical :: allowzerolocal
608  character(len=LINELENGTH) :: nodestr
609  logical :: flag_string_local
610  !
611  if (present(flag_string)) then
612  flag_string_local = flag_string
613  else
614  flag_string_local = .false.
615  end if
616  if (present(allow_zero)) then
617  allowzerolocal = allow_zero
618  else
619  allowzerolocal = .false.
620  end if
621  !
622  nodeu = this%nodeu_from_cellid(cellid, inunit, iout, flag_string_local, &
623  allowzerolocal)
624  !
625  ! -- Convert user-based nodenumber to reduced node number
626  if (nodeu > 0) then
627  noder = this%get_nodenumber(nodeu, 0)
628  else
629  noder = nodeu
630  end if
631  if (noder <= 0 .and. .not. flag_string_local) then
632  call this%nodeu_to_string(nodeu, nodestr)
633  write (errmsg, *) &
634  ' Cell is outside active grid domain: '// &
635  trim(adjustl(nodestr))
636  call store_error(errmsg)
637  end if
Here is the call graph for this function:

◆ noder_from_string()

integer(i4b) function basedismodule::noder_from_string ( class(disbasetype this,
integer(i4b), intent(inout)  lloc,
integer(i4b), intent(inout)  istart,
integer(i4b), intent(inout)  istop,
integer(i4b), intent(in)  in,
integer(i4b), intent(in)  iout,
character(len=*), intent(inout)  line,
logical, intent(in), optional  flag_string 
)
private

If the model is unstructured; just read user nodenumber. If flag_string argument is present and true, the first token in string is allowed to be a string (e.g. boundary name). In this case, if a string is encountered, return value as -2.

Definition at line 546 of file DiscretizationBase.f90.

548  ! -- dummy
549  class(DisBaseType) :: this
550  integer(I4B), intent(inout) :: lloc
551  integer(I4B), intent(inout) :: istart
552  integer(I4B), intent(inout) :: istop
553  integer(I4B), intent(in) :: in
554  integer(I4B), intent(in) :: iout
555  character(len=*), intent(inout) :: line
556  logical, optional, intent(in) :: flag_string
557  integer(I4B) :: noder
558  ! -- local
559  integer(I4B) :: nodeu
560  character(len=LINELENGTH) :: nodestr
561  logical :: flag_string_local
562  !
563  if (present(flag_string)) then
564  flag_string_local = flag_string
565  else
566  flag_string_local = .false.
567  end if
568  nodeu = this%nodeu_from_string(lloc, istart, istop, in, iout, line, &
569  flag_string_local)
570  !
571  ! -- Convert user-based nodenumber to reduced node number
572  if (nodeu > 0) then
573  noder = this%get_nodenumber(nodeu, 0)
574  else
575  noder = nodeu
576  end if
577  if (noder <= 0 .and. .not. flag_string_local) then
578  call this%nodeu_to_string(nodeu, nodestr)
579  write (errmsg, *) &
580  ' Cell is outside active grid domain: '// &
581  trim(adjustl(nodestr))
582  call store_error(errmsg)
583  end if
Here is the call graph for this function:

◆ noder_to_array()

subroutine basedismodule::noder_to_array ( class(disbasetype this,
integer(i4b), intent(in)  noder,
integer(i4b), dimension(:), intent(inout)  arr 
)
private

Definition at line 1009 of file DiscretizationBase.f90.

1010  ! -- dummy
1011  class(DisBaseType) :: this
1012  integer(I4B), intent(in) :: noder
1013  integer(I4B), dimension(:), intent(inout) :: arr
1014  ! -- local
1015  integer(I4B) :: nodeu
1016 
1017  nodeu = this%get_nodeuser(noder)
1018  call this%nodeu_to_array(nodeu, arr)

◆ noder_to_string()

subroutine basedismodule::noder_to_string ( class(disbasetype this,
integer(i4b), intent(in)  noder,
character(len=*), intent(inout)  str 
)
private

Definition at line 996 of file DiscretizationBase.f90.

997  ! -- dummy
998  class(DisBaseType) :: this
999  integer(I4B), intent(in) :: noder
1000  character(len=*), intent(inout) :: str
1001  ! -- local
1002  integer(I4B) :: nodeu
1003 
1004  nodeu = this%get_nodeuser(noder)
1005  call this%nodeu_to_string(nodeu, str)

◆ nodeu_from_cellid()

integer(i4b) function basedismodule::nodeu_from_cellid ( class(disbasetype this,
character(len=*), intent(inout)  cellid,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout,
logical, intent(in), optional  flag_string,
logical, intent(in), optional  allow_zero 
)
private

If flag_string is present and true, the first token may be non-numeric (e.g. boundary name). In this case, return -2.

If allow_zero is present and true, and all indices are zero, the result can be zero. If allow_zero is false, a zero in any index is an error.

Definition at line 523 of file DiscretizationBase.f90.

525  ! -- dummy
526  class(DisBaseType) :: this
527  character(len=*), intent(inout) :: cellid
528  integer(I4B), intent(in) :: inunit
529  integer(I4B), intent(in) :: iout
530  logical, optional, intent(in) :: flag_string
531  logical, optional, intent(in) :: allow_zero
532  integer(I4B) :: nodeu
533 
534  nodeu = 0
535  call store_error('Programmer error: nodeu_from_cellid must be overridden', &
536  terminate=.true.)
Here is the call graph for this function:

◆ nodeu_from_string()

integer(i4b) function basedismodule::nodeu_from_string ( class(disbasetype this,
integer(i4b), intent(inout)  lloc,
integer(i4b), intent(inout)  istart,
integer(i4b), intent(inout)  istop,
integer(i4b), intent(in)  in,
integer(i4b), intent(in)  iout,
character(len=*), intent(inout)  line,
logical, intent(in), optional  flag_string,
logical, intent(in), optional  allow_zero 
)
private

If DIS or DISV, read indices. If DISU, read user node number directly. If flag_string is present and true, the first token may be non-numeric (e.g. boundary name). In this case, return -2.

Definition at line 496 of file DiscretizationBase.f90.

498  ! -- dummy
499  class(DisBaseType) :: this
500  integer(I4B), intent(inout) :: lloc
501  integer(I4B), intent(inout) :: istart
502  integer(I4B), intent(inout) :: istop
503  integer(I4B), intent(in) :: in
504  integer(I4B), intent(in) :: iout
505  character(len=*), intent(inout) :: line
506  logical, optional, intent(in) :: flag_string
507  logical, optional, intent(in) :: allow_zero
508  integer(I4B) :: nodeu
509 
510  nodeu = 0
511  call store_error('Programmer error: nodeu_from_string must be overridden', &
512  terminate=.true.)
Here is the call graph for this function:

◆ nodeu_to_array()

subroutine basedismodule::nodeu_to_array ( class(disbasetype this,
integer(i4b), intent(in)  nodeu,
integer(i4b), dimension(:), intent(inout)  arr 
)
private

Definition at line 262 of file DiscretizationBase.f90.

263  class(DisBaseType) :: this
264  integer(I4B), intent(in) :: nodeu
265  integer(I4B), dimension(:), intent(inout) :: arr
266 
267  call store_error('Programmer error: nodeu_to_array must be overridden', &
268  terminate=.true.)
Here is the call graph for this function:

◆ nodeu_to_string()

subroutine basedismodule::nodeu_to_string ( class(disbasetype this,
integer(i4b), intent(in)  nodeu,
character(len=*), intent(inout)  str 
)

Definition at line 252 of file DiscretizationBase.f90.

253  class(DisBaseType) :: this
254  integer(I4B), intent(in) :: nodeu
255  character(len=*), intent(inout) :: str
256 
257  call store_error('Programmer error: nodeu_to_string must be overridden', &
258  terminate=.true.)
Here is the call graph for this function:

◆ read_dbl_array()

subroutine basedismodule::read_dbl_array ( class(disbasetype), intent(inout)  this,
character(len=*), intent(inout)  line,
integer(i4b), intent(inout)  lloc,
integer(i4b), intent(inout)  istart,
integer(i4b), intent(inout)  istop,
integer(i4b), intent(in)  iout,
integer(i4b), intent(in)  in,
real(dp), dimension(:), intent(inout), pointer, contiguous  darray,
character(len=*), intent(in)  aname 
)
private

Definition at line 732 of file DiscretizationBase.f90.

734  ! -- dummy
735  class(DisBaseType), intent(inout) :: this
736  character(len=*), intent(inout) :: line
737  integer(I4B), intent(inout) :: lloc
738  integer(I4B), intent(inout) :: istart
739  integer(I4B), intent(inout) :: istop
740  integer(I4B), intent(in) :: in
741  integer(I4B), intent(in) :: iout
742  real(DP), dimension(:), pointer, contiguous, intent(inout) :: darray
743  character(len=*), intent(in) :: aname
744 
745  errmsg = 'Programmer error: read_dbl_array must be overridden'
746  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ read_int_array()

subroutine basedismodule::read_int_array ( class(disbasetype), intent(inout)  this,
character(len=*), intent(inout)  line,
integer(i4b), intent(inout)  lloc,
integer(i4b), intent(inout)  istart,
integer(i4b), intent(inout)  istop,
integer(i4b), intent(in)  iout,
integer(i4b), intent(in)  in,
integer(i4b), dimension(:), intent(inout), pointer, contiguous  iarray,
character(len=*), intent(in)  aname 
)
private

Definition at line 714 of file DiscretizationBase.f90.

716  ! -- dummy
717  class(DisBaseType), intent(inout) :: this
718  character(len=*), intent(inout) :: line
719  integer(I4B), intent(inout) :: lloc
720  integer(I4B), intent(inout) :: istart
721  integer(I4B), intent(inout) :: istop
722  integer(I4B), intent(in) :: in
723  integer(I4B), intent(in) :: iout
724  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: iarray
725  character(len=*), intent(in) :: aname
726 
727  errmsg = 'Programmer error: read_int_array must be overridden'
728  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ read_layer_array()

subroutine basedismodule::read_layer_array ( class(disbasetype this,
integer(i4b), dimension(maxbnd)  nodelist,
real(dp), dimension(ncolbnd, maxbnd), intent(inout)  darray,
integer(i4b), intent(in)  ncolbnd,
integer(i4b), intent(in)  maxbnd,
integer(i4b), intent(in)  icolbnd,
character(len=*), intent(in)  aname,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout 
)

For cells that are outside of the active domain, do not copy the array value into darray.

Definition at line 938 of file DiscretizationBase.f90.

940  ! -- dummy
941  class(DisBaseType) :: this
942  integer(I4B), intent(in) :: ncolbnd
943  integer(I4B), intent(in) :: maxbnd
944  integer(I4B), dimension(maxbnd) :: nodelist
945  real(DP), dimension(ncolbnd, maxbnd), intent(inout) :: darray
946  integer(I4B), intent(in) :: icolbnd
947  character(len=*), intent(in) :: aname
948  integer(I4B), intent(in) :: inunit
949  integer(I4B), intent(in) :: iout
950 
951  errmsg = 'Programmer error: read_layer_array must be overridden'
952  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:

◆ read_list()

subroutine basedismodule::read_list ( class(disbasetype this,
type(longlinereadertype), intent(inout)  line_reader,
integer(i4b), intent(in)  in,
integer(i4b), intent(in)  iout,
integer(i4b), intent(in)  iprpak,
integer(i4b), intent(inout)  nlist,
integer(i4b), intent(in)  inamedbound,
integer(i4b), intent(in)  iauxmultcol,
integer(i4b), dimension(:), intent(inout), pointer, contiguous  nodelist,
real(dp), dimension(:, :), intent(inout), pointer, contiguous  rlist,
real(dp), dimension(:, :), intent(inout), pointer, contiguous  auxvar,
character(len=lenauxname), dimension(:), intent(inout)  auxname,
character(len=lenboundname), dimension(:), intent(inout), pointer, contiguous  boundname,
character(len=*), intent(in)  label,
character(len=*), intent(in)  pkgname,
type(timeseriesmanagertype tsManager,
integer(i4b), intent(in)  iscloc,
integer(i4b), intent(in), optional  indxconvertflux 
)
private

Convert user node numbers to reduced numbers. Terminate if any nodenumbers are within an inactive domain. Set up time series and multiply by iauxmultcol if it exists. Write the list to iout if iprpak is set.

Definition at line 790 of file DiscretizationBase.f90.

794  ! -- modules
799  use inputoutputmodule, only: urword
802  ! -- dummy
803  class(DisBaseType) :: this
804  type(LongLineReaderType), intent(inout) :: line_reader
805  integer(I4B), intent(in) :: in
806  integer(I4B), intent(in) :: iout
807  integer(I4B), intent(in) :: iprpak
808  integer(I4B), intent(inout) :: nlist
809  integer(I4B), intent(in) :: inamedbound
810  integer(I4B), intent(in) :: iauxmultcol
811  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: nodelist
812  real(DP), dimension(:, :), pointer, contiguous, intent(inout) :: rlist
813  real(DP), dimension(:, :), pointer, contiguous, intent(inout) :: auxvar
814  character(len=LENAUXNAME), dimension(:), intent(inout) :: auxname
815  character(len=LENBOUNDNAME), dimension(:), pointer, contiguous, &
816  intent(inout) :: boundname
817  character(len=*), intent(in) :: label
818  character(len=*), intent(in) :: pkgName
819  type(TimeSeriesManagerType) :: tsManager
820  integer(I4B), intent(in) :: iscloc
821  integer(I4B), intent(in), optional :: indxconvertflux
822  ! -- local
823  integer(I4B) :: l
824  integer(I4B) :: nodeu, noder
825  character(len=LINELENGTH) :: nodestr
826  integer(I4B) :: ii, jj
827  real(DP), pointer :: bndElem => null()
828  type(ListReaderType) :: lstrdobj
829  type(TimeSeriesLinkType), pointer :: tsLinkBnd => null()
830  type(TimeSeriesLinkType), pointer :: tsLinkAux => null()
831  !
832  ! -- Read the list
833  call lstrdobj%read_list(line_reader, in, iout, nlist, inamedbound, &
834  this%mshape, nodelist, rlist, auxvar, auxname, &
835  boundname, label)
836  !
837  ! -- Go through all locations where a text string was found instead of
838  ! a double precision value and make time-series links to rlist
839  if (lstrdobj%ntxtrlist > 0) then
840  do l = 1, lstrdobj%ntxtrlist
841  ii = lstrdobj%idxtxtrow(l)
842  jj = lstrdobj%idxtxtcol(l)
843  tslinkbnd => null()
844  bndelem => rlist(jj, ii)
845  call read_value_or_time_series(lstrdobj%txtrlist(l), ii, jj, bndelem, &
846  pkgname, 'BND', tsmanager, iprpak, &
847  tslinkbnd)
848  if (associated(tslinkbnd)) then
849  !
850  ! -- If iauxmultcol is active and this column is the column
851  ! to be scaled, then assign tsLinkBnd%RMultiplier to auxvar
852  ! multiplier
853  if (iauxmultcol > 0 .and. jj == iscloc) then
854  tslinkbnd%RMultiplier => auxvar(iauxmultcol, ii)
855  end if
856  !
857  ! -- If boundaries are named, save the name in the link
858  if (lstrdobj%inamedbound == 1) then
859  tslinkbnd%BndName = lstrdobj%boundname(tslinkbnd%IRow)
860  end if
861  !
862  ! -- if the value is a flux and needs to be converted to a flow
863  ! then set the tsLinkBnd appropriately
864  if (present(indxconvertflux)) then
865  if (indxconvertflux == jj) then
866  tslinkbnd%convertflux = .true.
867  nodeu = nodelist(ii)
868  noder = this%get_nodenumber(nodeu, 0)
869  tslinkbnd%CellArea = this%get_area(noder)
870  end if
871  end if
872  !
873  end if
874  end do
875  end if
876  !
877  ! -- Make time-series substitutions for auxvar
878  if (lstrdobj%ntxtauxvar > 0) then
879  do l = 1, lstrdobj%ntxtauxvar
880  ii = lstrdobj%idxtxtauxrow(l)
881  jj = lstrdobj%idxtxtauxcol(l)
882  tslinkaux => null()
883  bndelem => auxvar(jj, ii)
884  call read_value_or_time_series(lstrdobj%txtauxvar(l), ii, jj, bndelem, &
885  pkgname, 'AUX', tsmanager, iprpak, &
886  tslinkaux)
887  if (lstrdobj%inamedbound == 1) then
888  if (associated(tslinkaux)) then
889  tslinkaux%BndName = lstrdobj%boundname(tslinkaux%IRow)
890  end if
891  end if
892  end do
893  end if
894  !
895  ! -- Multiply rlist by the multiplier column in auxvar
896  if (iauxmultcol > 0) then
897  do l = 1, nlist
898  rlist(iscloc, l) = rlist(iscloc, l) * auxvar(iauxmultcol, l)
899  end do
900  end if
901  !
902  ! -- Write the list to iout if requested
903  if (iprpak /= 0) then
904  call lstrdobj%write_list()
905  end if
906  !
907  ! -- Convert user nodenumbers to reduced nodenumbers, if necessary.
908  ! Conversion to reduced nodenumbers must be done last, after the
909  ! list is written so that correct indices are written to the list.
910  if (this%nodes < this%nodesuser) then
911  do l = 1, nlist
912  nodeu = nodelist(l)
913  noder = this%get_nodenumber(nodeu, 0)
914  if (noder <= 0) then
915  call this%nodeu_to_string(nodeu, nodestr)
916  write (errmsg, *) &
917  ' Cell is outside active grid domain: '// &
918  trim(adjustl(nodestr))
919  call store_error(errmsg)
920  end if
921  nodelist(l) = noder
922  end do
923  !
924  ! -- Check for errors and terminate if encountered
925  if (count_errors() > 0) then
926  write (errmsg, *) count_errors(), ' errors encountered.'
927  call store_error(errmsg)
928  call store_error_unit(in)
929  end if
930  end if
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:36
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
Generic List Reader Module.
Definition: ListReader.f90:3
This module contains the LongLineReaderType.
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
subroutine, public read_value_or_time_series(textInput, ii, jj, bndElem, pkgName, auxOrBnd, tsManager, iprpak, tsLink)
Call this subroutine if the time-series link is available or needed.
Here is the call graph for this function:

◆ record_array()

subroutine basedismodule::record_array ( class(disbasetype), intent(inout)  this,
real(dp), dimension(:), intent(inout), pointer, contiguous  darray,
integer(i4b), intent(in)  iout,
integer(i4b), intent(in)  iprint,
integer(i4b), intent(in)  idataun,
character(len=*), intent(in)  aname,
character(len=*), intent(in)  cdatafmp,
integer(i4b), intent(in)  nvaluesp,
integer(i4b), intent(in)  nwidthp,
character(len=*), intent(in)  editdesc,
real(dp), intent(in)  dinact 
)
private

The array is written to a formatted or unformatted external file depending on the arguments.

Parameters
[in,out]darraydouble precision array to record
[in]ioutascii output unit number
[in]iprintwhether to print the array
[in]idataunbinary output unit number
[in]anametext descriptor
[in]cdatafmpwrite format
[in]nvaluespvalues per line
[in]nwidthpnumber width
[in]editdescformat type (I, G, F, S, E)
[in]dinactdouble precision value for cells excluded from model domain

Definition at line 959 of file DiscretizationBase.f90.

961  ! -- dummy
962  class(DisBaseType), intent(inout) :: this
963  real(DP), dimension(:), pointer, contiguous, intent(inout) :: darray !< double precision array to record
964  integer(I4B), intent(in) :: iout !< ascii output unit number
965  integer(I4B), intent(in) :: iprint !< whether to print the array
966  integer(I4B), intent(in) :: idataun !< binary output unit number
967  character(len=*), intent(in) :: aname !< text descriptor
968  character(len=*), intent(in) :: cdatafmp !< write format
969  integer(I4B), intent(in) :: nvaluesp !< values per line
970  integer(I4B), intent(in) :: nwidthp !< number width
971  character(len=*), intent(in) :: editdesc !< format type (I, G, F, S, E)
972  real(DP), intent(in) :: dinact !< double precision value for cells excluded from model domain
973 
974  errmsg = 'Programmer error: record_array must be overridden'
975  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:

◆ record_connection_array()

subroutine basedismodule::record_connection_array ( class(disbasetype this,
real(dp), dimension(:), intent(in)  flowja,
integer(i4b), intent(in)  ibinun,
integer(i4b), intent(in)  iout 
)
private

Definition at line 979 of file DiscretizationBase.f90.

980  ! -- dummy
981  class(DisBaseType) :: this
982  real(DP), dimension(:), intent(in) :: flowja
983  integer(I4B), intent(in) :: ibinun
984  integer(I4B), intent(in) :: iout
985  ! -- local
986  character(len=16), dimension(1) :: text
987  ! -- data
988  data text(1)/' FLOW-JA-FACE'/
989 
990  ! -- write full ja array
991  call ubdsv1(kstp, kper, text(1), ibinun, flowja, size(flowja), 1, 1, &
992  iout, delt, pertim, totim)
Here is the call graph for this function:

◆ record_srcdst_list_entry()

subroutine basedismodule::record_srcdst_list_entry ( class(disbasetype this,
integer(i4b), intent(in)  ibdchn,
integer(i4b), intent(in)  noder,
integer(i4b), intent(in)  noder2,
real(dp), intent(in)  q,
integer(i4b), intent(in)  naux,
real(dp), dimension(naux), intent(in)  aux,
logical, intent(in), optional  olconv,
logical, intent(in), optional  olconv2 
)
private

Definition at line 1042 of file DiscretizationBase.f90.

1044  ! -- dummy
1045  class(DisBaseType) :: this
1046  integer(I4B), intent(in) :: ibdchn
1047  integer(I4B), intent(in) :: noder
1048  integer(I4B), intent(in) :: noder2
1049  real(DP), intent(in) :: q
1050  integer(I4B), intent(in) :: naux
1051  real(DP), dimension(naux), intent(in) :: aux
1052  logical, optional, intent(in) :: olconv
1053  logical, optional, intent(in) :: olconv2
1054  ! -- local
1055  logical :: lconv
1056  logical :: lconv2
1057  integer(I4B) :: nodeu
1058  integer(I4B) :: nodeu2
1059  !
1060  ! -- Use ubdsvb to write list header
1061  if (present(olconv)) then
1062  lconv = olconv
1063  else
1064  lconv = .true.
1065  end if
1066  if (lconv) then
1067  nodeu = this%get_nodeuser(noder)
1068  else
1069  nodeu = noder
1070  end if
1071  if (present(olconv2)) then
1072  lconv2 = olconv2
1073  else
1074  lconv2 = .true.
1075  end if
1076  if (lconv2) then
1077  nodeu2 = this%get_nodeuser(noder2)
1078  else
1079  nodeu2 = noder2
1080  end if
1081  call ubdsvd(ibdchn, nodeu, nodeu2, q, naux, aux)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ record_srcdst_list_header()

subroutine basedismodule::record_srcdst_list_header ( class(disbasetype this,
character(len=16), intent(in)  text,
character(len=16), intent(in)  textmodel,
character(len=16), intent(in)  textpackage,
character(len=16), intent(in)  dstmodel,
character(len=16), intent(in)  dstpackage,
integer(i4b), intent(in)  naux,
character(len=16), dimension(:), intent(in)  auxtxt,
integer(i4b), intent(in)  ibdchn,
integer(i4b), intent(in)  nlist,
integer(i4b), intent(in)  iout 
)
private

Definition at line 1022 of file DiscretizationBase.f90.

1025  class(DisBaseType) :: this
1026  character(len=16), intent(in) :: text
1027  character(len=16), intent(in) :: textmodel
1028  character(len=16), intent(in) :: textpackage
1029  character(len=16), intent(in) :: dstmodel
1030  character(len=16), intent(in) :: dstpackage
1031  integer(I4B), intent(in) :: naux
1032  character(len=16), dimension(:), intent(in) :: auxtxt
1033  integer(I4B), intent(in) :: ibdchn
1034  integer(I4B), intent(in) :: nlist
1035  integer(I4B), intent(in) :: iout
1036 
1037  errmsg = 'Programmer error: record_srcdst_list_header must be overridden'
1038  call store_error(errmsg, terminate=.true.)
Here is the call graph for this function:

◆ supports_layers()

logical function basedismodule::supports_layers ( class(disbasetype this)
private

Definition at line 641 of file DiscretizationBase.f90.

642  class(DisBaseType) :: this
643  supports_layers = .false.
644  call store_error('Programmer error: supports_layers must be overridden', &
645  terminate=.true.)
Here is the call graph for this function:

◆ write_grb()

subroutine basedismodule::write_grb ( class(disbasetype this,
integer(i4b), dimension(:), intent(in)  icelltype 
)
private

Definition at line 202 of file DiscretizationBase.f90.

203  class(DisBaseType) :: this
204  integer(I4B), dimension(:), intent(in) :: icelltype
205  call store_error('Programmer error: write_grb must be overridden', &
206  terminate=.true.)
Here is the call graph for this function: