MODFLOW 6  version 6.7.0.dev1
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 polygon vertices, listed in clockwise order beginning with the lower left corner. 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...
 
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 460 of file DiscretizationBase.f90.

461  class(DisBaseType) :: this
462  integer :: isize
463  !
464  ! -- Allocate
465  call mem_allocate(this%mshape, this%ndim, 'MSHAPE', this%memoryPath)
466  call mem_allocate(this%xc, this%nodes, 'XC', this%memoryPath)
467  call mem_allocate(this%yc, this%nodes, 'YC', this%memoryPath)
468  call mem_allocate(this%top, this%nodes, 'TOP', this%memoryPath)
469  call mem_allocate(this%bot, this%nodes, 'BOT', this%memoryPath)
470  call mem_allocate(this%area, this%nodes, 'AREA', this%memoryPath)
471  !
472  ! -- Initialize
473  this%mshape(1) = this%nodes
474  !
475  ! -- Determine size of buff memory
476  if (this%nodes < this%nodesuser) then
477  isize = this%nodesuser
478  else
479  isize = this%nodes
480  end if
481  !
482  ! -- Allocate the arrays
483  call mem_allocate(this%dbuff, isize, 'DBUFF', this%name_model)
484  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 401 of file DiscretizationBase.f90.

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

318  class(DisBaseType) :: this
319  integer(I4B), intent(in) :: noden !< cell (reduced nn)
320  integer(I4B), intent(in) :: nodem !< neighbor (reduced nn)
321  integer(I4B), intent(in) :: ihc !< horizontal connection flag
322  real(DP), intent(inout) :: xcomp
323  real(DP), intent(inout) :: ycomp
324  real(DP), intent(inout) :: zcomp
325  integer(I4B), intent(in) :: ipos
326 
327  call store_error('Programmer error: connection_normal must be overridden', &
328  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 334 of file DiscretizationBase.f90.

336  class(DisBaseType) :: this
337  integer(I4B), intent(in) :: noden !< cell (reduced nn)
338  integer(I4B), intent(in) :: nodem !< neighbor (reduced nn)
339  logical, intent(in) :: nozee
340  real(DP), intent(in) :: satn
341  real(DP), intent(in) :: satm
342  integer(I4B), intent(in) :: ihc !< horizontal connection flag
343  real(DP), intent(inout) :: xcomp
344  real(DP), intent(inout) :: ycomp
345  real(DP), intent(inout) :: zcomp
346  real(DP), intent(inout) :: conlen
347 
348  call store_error('Programmer error: connection_vector must be overridden', &
349  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 135 of file DiscretizationBase.f90.

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

◆ dis_ar()

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

Definition at line 176 of file DiscretizationBase.f90.

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

◆ dis_da()

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

Definition at line 207 of file DiscretizationBase.f90.

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

◆ dis_df()

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

Definition at line 128 of file DiscretizationBase.f90.

129  class(DisBaseType) :: this
130  call store_error('Programmer error: dis_df must be overridden', &
131  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 156 of file DiscretizationBase.f90.

157  ! -- dummy
158  class(DisBaseType) :: this
159  integer(I4B), intent(in) :: moffset
160  integer(I4B), dimension(:), intent(inout) :: idxglo
161  class(MatrixBaseType), pointer :: matrix_sln
162  ! -- local
163  integer(I4B) :: i, j, ipos, iglo, jglo
164  !
165  do i = 1, this%nodes
166  iglo = i + moffset
167  do ipos = this%con%ia(i), this%con%ia(i + 1) - 1
168  j = this%con%ja(ipos)
169  jglo = j + moffset
170  idxglo(ipos) = matrix_sln%get_position(iglo, jglo)
171  end do
172  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 353 of file DiscretizationBase.f90.

354  real(DP), intent(in) :: x !< the cell-x coordinate to transform
355  real(DP), intent(in) :: y !< the cell-y coordinate to transform
356  real(DP), intent(in) :: xorigin !< the cell-y coordinate to transform
357  real(DP), intent(in) :: yorigin !< the cell-y coordinate to transform
358  real(DP), intent(in) :: angrot !< the cell-y coordinate to transform
359  real(DP), intent(out) :: xglo !< the global cell-x coordinate
360  real(DP), intent(out) :: yglo !< the global cell-y coordinate
361  ! local
362  real(DP) :: ang
363 
364  xglo = x
365  yglo = y
366 
367  ! first _rotate_ to 'real world'
368  ang = angrot * dpio180
369  if (ang /= dzero) then
370  xglo = x * cos(ang) - y * sin(ang)
371  yglo = x * sin(ang) + y * cos(ang)
372  end if
373 
374  ! then _translate_
375  xglo = xglo + xorigin
376  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 743 of file DiscretizationBase.f90.

744  ! -- dummy
745  class(DisBaseType), intent(inout) :: this
746  real(DP), dimension(:), pointer, contiguous, intent(in) :: buff1
747  real(DP), dimension(:), pointer, contiguous, intent(inout) :: buff2
748  ! -- local
749  integer(I4B) :: nodeu
750  integer(I4B) :: noder
751 
752  do nodeu = 1, this%nodesuser
753  noder = this%get_nodenumber(nodeu, 0)
754  if (noder <= 0) cycle
755  buff2(noder) = buff1(nodeu)
756  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 726 of file DiscretizationBase.f90.

727  ! -- dummy
728  class(DisBaseType), intent(inout) :: this
729  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: ibuff1
730  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: ibuff2
731  ! -- local
732  integer(I4B) :: nodeu
733  integer(I4B) :: noder
734 
735  do nodeu = 1, this%nodesuser
736  noder = this%get_nodenumber(nodeu, 0)
737  if (noder <= 0) cycle
738  ibuff2(noder) = ibuff1(nodeu)
739  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 1115 of file DiscretizationBase.f90.

1116  class(DisBaseType) :: this
1117  integer(I4B), intent(in) :: node !< reduced node number
1118  real(DP) :: area
1119 
1120  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 1132 of file DiscretizationBase.f90.

1133  ! -- return
1134  real(DP) :: area_factor !< connection cell area factor
1135  ! -- dummy
1136  class(DisBaseType) :: this
1137  integer(I4B), intent(in) :: node !< cell node number
1138  integer(I4B), intent(in) :: idx_conn !< connection index
1139  ! -- local
1140  real(DP) :: area_node
1141  real(DP) :: area_conn
1142  !
1143  ! -- calculate the cell area fraction
1144  area_node = this%area(node)
1145  area_conn = this%con%hwva(idx_conn)
1146  !
1147  ! -- return the cell area factor
1148  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 656 of file DiscretizationBase.f90.

657  ! -- return
658  real(DP) :: get_cell_volume
659  ! -- dummy
660  class(DisBaseType) :: this
661  integer(I4B), intent(in) :: n
662  real(DP), intent(in) :: x
663  ! -- local
664  real(DP) :: tp
665  real(DP) :: bt
666  real(DP) :: sat
667  real(DP) :: thick
668 
669  get_cell_volume = dzero
670  tp = this%top(n)
671  bt = this%bot(n)
672  sat = squadraticsaturation(tp, bt, x)
673  thick = (tp - bt) * sat
674  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 390 of file DiscretizationBase.f90.

391  use constantsmodule, only: disundef
392  class(DisBaseType), intent(in) :: this
393  integer(I4B) :: dis_enum
394 
395  dis_enum = disundef
396  call store_error('Programmer error: get_dis_enum must be overridden', &
397  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 380 of file DiscretizationBase.f90.

381  class(DisBaseType), intent(in) :: this
382  character(len=*), intent(out) :: dis_type
383 
384  dis_type = "Not implemented"
385  call store_error('Programmer error: get_dis_type must be overridden', &
386  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 1158 of file DiscretizationBase.f90.

1159  ! dummy
1160  class(DisBaseType) :: this
1161  integer(I4B), intent(in) :: n !< cell node number
1162  integer(I4B), intent(in) :: m !< cell node number
1163  integer(I4B), intent(in) :: idx_conn !< connection index
1164  real(DP), intent(out) :: width_n !< flow width for cell n
1165  real(DP), intent(out) :: width_m !< flow width for cell m
1166  ! local
1167  integer(I4B) :: isympos
1168 
1169  ! For general case, width_n = width_m
1170  isympos = this%con%jas(idx_conn)
1171  width_n = this%con%hwva(isympos)
1172  width_m = width_n
1173 

◆ get_ncpl()

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

Definition at line 647 of file DiscretizationBase.f90.

648  integer(I4B) :: get_ncpl
649  class(DisBaseType) :: this
650  get_ncpl = 0
651  call store_error('Programmer error: get_ncpl must be overridden', &
652  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 281 of file DiscretizationBase.f90.

282  class(DisBaseType), intent(in) :: this
283  integer(I4B), intent(in) :: nodeu
284  integer(I4B), intent(in) :: icheck
285  integer(I4B) :: nodenumber
286 
287  nodenumber = 0
288  call store_error('Programmer error: get_nodenumber_idx1 must be overridden', &
289  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 292 of file DiscretizationBase.f90.

293  class(DisBaseType), intent(in) :: this
294  integer(I4B), intent(in) :: k, j
295  integer(I4B), intent(in) :: icheck
296  integer(I4B) :: nodenumber
297 
298  nodenumber = 0
299  call store_error('Programmer error: get_nodenumber_idx2 must be overridden', &
300  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 303 of file DiscretizationBase.f90.

304  class(DisBaseType), intent(in) :: this
305  integer(I4B), intent(in) :: k, i, j
306  integer(I4B), intent(in) :: icheck
307  integer(I4B) :: nodenumber
308 
309  nodenumber = 0
310  call store_error('Programmer error: get_nodenumber_idx3 must be overridden', &
311  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 269 of file DiscretizationBase.f90.

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

◆ 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 679 of file DiscretizationBase.f90.

680  class(DisBaseType), intent(inout) :: this
681  integer(I4B), intent(in) :: ic !< cell number (reduced)
682  real(DP), allocatable, intent(out) :: polyverts(:, :) !< polygon vertices (column-major indexing)
683  logical(LGP), intent(in), optional :: closed !< whether to close the polygon, duplicating a vertex
684 
685  errmsg = 'Programmer error: get_polyverts must be overridden'
686  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 1077 of file DiscretizationBase.f90.

1078  ! -- dummy
1079  class(DisBaseType) :: this
1080  integer(I4B), intent(inout) :: n
1081  integer(I4B), dimension(:), intent(in) :: ibound
1082  ! -- locals
1083  integer(I4B) :: m, ii, iis
1084  logical done, bottomcell
1085  !
1086  ! -- Loop through connected cells until the highest active one (including a
1087  ! constant head cell) is found. Return that cell as n.
1088  done = .false.
1089  do while (.not. done)
1090  bottomcell = .true.
1091  cloop: do ii = this%con%ia(n) + 1, this%con%ia(n + 1) - 1
1092  m = this%con%ja(ii)
1093  iis = this%con%jas(ii)
1094  if (this%con%ihc(iis) == 0 .and. m > n) then
1095  !
1096  ! -- this cannot be a bottom cell
1097  bottomcell = .false.
1098  !
1099  ! -- vertical down
1100  if (ibound(m) /= 0) then
1101  n = m
1102  done = .true.
1103  exit cloop
1104  else
1105  n = m
1106  exit cloop
1107  end if
1108  end if
1109  end do cloop
1110  if (bottomcell) done = .true.
1111  end do

◆ is_1d()

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

Definition at line 1203 of file DiscretizationBase.f90.

1204  ! dummy
1205  class(DisBaseType) :: this
1206  ! return
1207  logical(LGP) :: r
1208  r = .false.
1209  select case (this%get_dis_enum())
1210  case (dis1d, disv1d, disu1d)
1211  r = .true.
1212  end select

◆ is_2d()

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

Definition at line 1190 of file DiscretizationBase.f90.

1191  ! dummy
1192  class(DisBaseType) :: this
1193  ! return
1194  logical(LGP) :: r
1195  r = .false.
1196  select case (this%get_dis_enum())
1197  case (dis2d, disv2d, disu2d)
1198  r = .true.
1199  end select

◆ is_3d()

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

Definition at line 1177 of file DiscretizationBase.f90.

1178  ! dummy
1179  class(DisBaseType) :: this
1180  ! return
1181  logical(LGP) :: r
1182  r = .false.
1183  select case (this%get_dis_enum())
1184  case (dis, disv, disu)
1185  r = .true.
1186  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 1064 of file DiscretizationBase.f90.

1065  class(DisBaseType) :: this
1066  integer(I4B), intent(in) :: maxbnd
1067  integer(I4B), dimension(:), pointer, contiguous :: darray
1068  integer(I4B), dimension(maxbnd), intent(inout) :: nodelist
1069  integer(I4B), intent(inout) :: nbound
1070  character(len=*), intent(in) :: aname
1071 
1072  errmsg = 'Programmer error: nlarray_to_nodelist must be overridden'
1073  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 591 of file DiscretizationBase.f90.

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

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

986  ! -- dummy
987  class(DisBaseType) :: this
988  integer(I4B), intent(in) :: noder
989  integer(I4B), dimension(:), intent(inout) :: arr
990  ! -- local
991  integer(I4B) :: nodeu
992 
993  nodeu = this%get_nodeuser(noder)
994  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 972 of file DiscretizationBase.f90.

973  ! -- dummy
974  class(DisBaseType) :: this
975  integer(I4B), intent(in) :: noder
976  character(len=*), intent(inout) :: str
977  ! -- local
978  integer(I4B) :: nodeu
979 
980  nodeu = this%get_nodeuser(noder)
981  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 520 of file DiscretizationBase.f90.

522  ! -- dummy
523  class(DisBaseType) :: this
524  character(len=*), intent(inout) :: cellid
525  integer(I4B), intent(in) :: inunit
526  integer(I4B), intent(in) :: iout
527  logical, optional, intent(in) :: flag_string
528  logical, optional, intent(in) :: allow_zero
529  integer(I4B) :: nodeu
530 
531  nodeu = 0
532  call store_error('Programmer error: nodeu_from_cellid must be overridden', &
533  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 493 of file DiscretizationBase.f90.

495  ! -- dummy
496  class(DisBaseType) :: this
497  integer(I4B), intent(inout) :: lloc
498  integer(I4B), intent(inout) :: istart
499  integer(I4B), intent(inout) :: istop
500  integer(I4B), intent(in) :: in
501  integer(I4B), intent(in) :: iout
502  character(len=*), intent(inout) :: line
503  logical, optional, intent(in) :: flag_string
504  logical, optional, intent(in) :: allow_zero
505  integer(I4B) :: nodeu
506 
507  nodeu = 0
508  call store_error('Programmer error: nodeu_from_string must be overridden', &
509  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 259 of file DiscretizationBase.f90.

260  class(DisBaseType) :: this
261  integer(I4B), intent(in) :: nodeu
262  integer(I4B), dimension(:), intent(inout) :: arr
263 
264  call store_error('Programmer error: nodeu_to_array must be overridden', &
265  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 249 of file DiscretizationBase.f90.

250  class(DisBaseType) :: this
251  integer(I4B), intent(in) :: nodeu
252  character(len=*), intent(inout) :: str
253 
254  call store_error('Programmer error: nodeu_to_string must be overridden', &
255  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 708 of file DiscretizationBase.f90.

710  ! -- dummy
711  class(DisBaseType), intent(inout) :: this
712  character(len=*), intent(inout) :: line
713  integer(I4B), intent(inout) :: lloc
714  integer(I4B), intent(inout) :: istart
715  integer(I4B), intent(inout) :: istop
716  integer(I4B), intent(in) :: in
717  integer(I4B), intent(in) :: iout
718  real(DP), dimension(:), pointer, contiguous, intent(inout) :: darray
719  character(len=*), intent(in) :: aname
720 
721  errmsg = 'Programmer error: read_dbl_array must be overridden'
722  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 690 of file DiscretizationBase.f90.

692  ! -- dummy
693  class(DisBaseType), intent(inout) :: this
694  character(len=*), intent(inout) :: line
695  integer(I4B), intent(inout) :: lloc
696  integer(I4B), intent(inout) :: istart
697  integer(I4B), intent(inout) :: istop
698  integer(I4B), intent(in) :: in
699  integer(I4B), intent(in) :: iout
700  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: iarray
701  character(len=*), intent(in) :: aname
702 
703  errmsg = 'Programmer error: read_int_array must be overridden'
704  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 914 of file DiscretizationBase.f90.

916  ! -- dummy
917  class(DisBaseType) :: this
918  integer(I4B), intent(in) :: ncolbnd
919  integer(I4B), intent(in) :: maxbnd
920  integer(I4B), dimension(maxbnd) :: nodelist
921  real(DP), dimension(ncolbnd, maxbnd), intent(inout) :: darray
922  integer(I4B), intent(in) :: icolbnd
923  character(len=*), intent(in) :: aname
924  integer(I4B), intent(in) :: inunit
925  integer(I4B), intent(in) :: iout
926 
927  errmsg = 'Programmer error: read_layer_array must be overridden'
928  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 766 of file DiscretizationBase.f90.

770  ! -- modules
775  use inputoutputmodule, only: urword
778  ! -- dummy
779  class(DisBaseType) :: this
780  type(LongLineReaderType), intent(inout) :: line_reader
781  integer(I4B), intent(in) :: in
782  integer(I4B), intent(in) :: iout
783  integer(I4B), intent(in) :: iprpak
784  integer(I4B), intent(inout) :: nlist
785  integer(I4B), intent(in) :: inamedbound
786  integer(I4B), intent(in) :: iauxmultcol
787  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: nodelist
788  real(DP), dimension(:, :), pointer, contiguous, intent(inout) :: rlist
789  real(DP), dimension(:, :), pointer, contiguous, intent(inout) :: auxvar
790  character(len=LENAUXNAME), dimension(:), intent(inout) :: auxname
791  character(len=LENBOUNDNAME), dimension(:), pointer, contiguous, &
792  intent(inout) :: boundname
793  character(len=*), intent(in) :: label
794  character(len=*), intent(in) :: pkgName
795  type(TimeSeriesManagerType) :: tsManager
796  integer(I4B), intent(in) :: iscloc
797  integer(I4B), intent(in), optional :: indxconvertflux
798  ! -- local
799  integer(I4B) :: l
800  integer(I4B) :: nodeu, noder
801  character(len=LINELENGTH) :: nodestr
802  integer(I4B) :: ii, jj
803  real(DP), pointer :: bndElem => null()
804  type(ListReaderType) :: lstrdobj
805  type(TimeSeriesLinkType), pointer :: tsLinkBnd => null()
806  type(TimeSeriesLinkType), pointer :: tsLinkAux => null()
807  !
808  ! -- Read the list
809  call lstrdobj%read_list(line_reader, in, iout, nlist, inamedbound, &
810  this%mshape, nodelist, rlist, auxvar, auxname, &
811  boundname, label)
812  !
813  ! -- Go through all locations where a text string was found instead of
814  ! a double precision value and make time-series links to rlist
815  if (lstrdobj%ntxtrlist > 0) then
816  do l = 1, lstrdobj%ntxtrlist
817  ii = lstrdobj%idxtxtrow(l)
818  jj = lstrdobj%idxtxtcol(l)
819  tslinkbnd => null()
820  bndelem => rlist(jj, ii)
821  call read_value_or_time_series(lstrdobj%txtrlist(l), ii, jj, bndelem, &
822  pkgname, 'BND', tsmanager, iprpak, &
823  tslinkbnd)
824  if (associated(tslinkbnd)) then
825  !
826  ! -- If iauxmultcol is active and this column is the column
827  ! to be scaled, then assign tsLinkBnd%RMultiplier to auxvar
828  ! multiplier
829  if (iauxmultcol > 0 .and. jj == iscloc) then
830  tslinkbnd%RMultiplier => auxvar(iauxmultcol, ii)
831  end if
832  !
833  ! -- If boundaries are named, save the name in the link
834  if (lstrdobj%inamedbound == 1) then
835  tslinkbnd%BndName = lstrdobj%boundname(tslinkbnd%IRow)
836  end if
837  !
838  ! -- if the value is a flux and needs to be converted to a flow
839  ! then set the tsLinkBnd appropriately
840  if (present(indxconvertflux)) then
841  if (indxconvertflux == jj) then
842  tslinkbnd%convertflux = .true.
843  nodeu = nodelist(ii)
844  noder = this%get_nodenumber(nodeu, 0)
845  tslinkbnd%CellArea = this%get_area(noder)
846  end if
847  end if
848  !
849  end if
850  end do
851  end if
852  !
853  ! -- Make time-series substitutions for auxvar
854  if (lstrdobj%ntxtauxvar > 0) then
855  do l = 1, lstrdobj%ntxtauxvar
856  ii = lstrdobj%idxtxtauxrow(l)
857  jj = lstrdobj%idxtxtauxcol(l)
858  tslinkaux => null()
859  bndelem => auxvar(jj, ii)
860  call read_value_or_time_series(lstrdobj%txtauxvar(l), ii, jj, bndelem, &
861  pkgname, 'AUX', tsmanager, iprpak, &
862  tslinkaux)
863  if (lstrdobj%inamedbound == 1) then
864  if (associated(tslinkaux)) then
865  tslinkaux%BndName = lstrdobj%boundname(tslinkaux%IRow)
866  end if
867  end if
868  end do
869  end if
870  !
871  ! -- Multiply rlist by the multiplier column in auxvar
872  if (iauxmultcol > 0) then
873  do l = 1, nlist
874  rlist(iscloc, l) = rlist(iscloc, l) * auxvar(iauxmultcol, l)
875  end do
876  end if
877  !
878  ! -- Write the list to iout if requested
879  if (iprpak /= 0) then
880  call lstrdobj%write_list()
881  end if
882  !
883  ! -- Convert user nodenumbers to reduced nodenumbers, if necessary.
884  ! Conversion to reduced nodenumbers must be done last, after the
885  ! list is written so that correct indices are written to the list.
886  if (this%nodes < this%nodesuser) then
887  do l = 1, nlist
888  nodeu = nodelist(l)
889  noder = this%get_nodenumber(nodeu, 0)
890  if (noder <= 0) then
891  call this%nodeu_to_string(nodeu, nodestr)
892  write (errmsg, *) &
893  ' Cell is outside active grid domain: '// &
894  trim(adjustl(nodestr))
895  call store_error(errmsg)
896  end if
897  nodelist(l) = noder
898  end do
899  !
900  ! -- Check for errors and terminate if encountered
901  if (count_errors() > 0) then
902  write (errmsg, *) count_errors(), ' errors encountered.'
903  call store_error(errmsg)
904  call store_error_unit(in)
905  end if
906  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 935 of file DiscretizationBase.f90.

937  ! -- dummy
938  class(DisBaseType), intent(inout) :: this
939  real(DP), dimension(:), pointer, contiguous, intent(inout) :: darray !< double precision array to record
940  integer(I4B), intent(in) :: iout !< ascii output unit number
941  integer(I4B), intent(in) :: iprint !< whether to print the array
942  integer(I4B), intent(in) :: idataun !< binary output unit number
943  character(len=*), intent(in) :: aname !< text descriptor
944  character(len=*), intent(in) :: cdatafmp !< write format
945  integer(I4B), intent(in) :: nvaluesp !< values per line
946  integer(I4B), intent(in) :: nwidthp !< number width
947  character(len=*), intent(in) :: editdesc !< format type (I, G, F, S, E)
948  real(DP), intent(in) :: dinact !< double precision value for cells excluded from model domain
949 
950  errmsg = 'Programmer error: record_array must be overridden'
951  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 955 of file DiscretizationBase.f90.

956  ! -- dummy
957  class(DisBaseType) :: this
958  real(DP), dimension(:), intent(in) :: flowja
959  integer(I4B), intent(in) :: ibinun
960  integer(I4B), intent(in) :: iout
961  ! -- local
962  character(len=16), dimension(1) :: text
963  ! -- data
964  data text(1)/' FLOW-JA-FACE'/
965 
966  ! -- write full ja array
967  call ubdsv1(kstp, kper, text(1), ibinun, flowja, size(flowja), 1, 1, &
968  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 1018 of file DiscretizationBase.f90.

1020  ! -- dummy
1021  class(DisBaseType) :: this
1022  integer(I4B), intent(in) :: ibdchn
1023  integer(I4B), intent(in) :: noder
1024  integer(I4B), intent(in) :: noder2
1025  real(DP), intent(in) :: q
1026  integer(I4B), intent(in) :: naux
1027  real(DP), dimension(naux), intent(in) :: aux
1028  logical, optional, intent(in) :: olconv
1029  logical, optional, intent(in) :: olconv2
1030  ! -- local
1031  logical :: lconv
1032  logical :: lconv2
1033  integer(I4B) :: nodeu
1034  integer(I4B) :: nodeu2
1035  !
1036  ! -- Use ubdsvb to write list header
1037  if (present(olconv)) then
1038  lconv = olconv
1039  else
1040  lconv = .true.
1041  end if
1042  if (lconv) then
1043  nodeu = this%get_nodeuser(noder)
1044  else
1045  nodeu = noder
1046  end if
1047  if (present(olconv2)) then
1048  lconv2 = olconv2
1049  else
1050  lconv2 = .true.
1051  end if
1052  if (lconv2) then
1053  nodeu2 = this%get_nodeuser(noder2)
1054  else
1055  nodeu2 = noder2
1056  end if
1057  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 998 of file DiscretizationBase.f90.

1001  class(DisBaseType) :: this
1002  character(len=16), intent(in) :: text
1003  character(len=16), intent(in) :: textmodel
1004  character(len=16), intent(in) :: textpackage
1005  character(len=16), intent(in) :: dstmodel
1006  character(len=16), intent(in) :: dstpackage
1007  integer(I4B), intent(in) :: naux
1008  character(len=16), dimension(:), intent(in) :: auxtxt
1009  integer(I4B), intent(in) :: ibdchn
1010  integer(I4B), intent(in) :: nlist
1011  integer(I4B), intent(in) :: iout
1012 
1013  errmsg = 'Programmer error: record_srcdst_list_header must be overridden'
1014  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 638 of file DiscretizationBase.f90.

639  class(DisBaseType) :: this
640  supports_layers = .false.
641  call store_error('Programmer error: supports_layers must be overridden', &
642  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 199 of file DiscretizationBase.f90.

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