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

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

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

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

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

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

◆ dis_ar()

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

Definition at line 177 of file DiscretizationBase.f90.

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

◆ dis_da()

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

Definition at line 208 of file DiscretizationBase.f90.

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

◆ dis_df()

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

Definition at line 129 of file DiscretizationBase.f90.

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

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

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

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

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

1155  class(DisBaseType) :: this
1156  integer(I4B), intent(in) :: node !< reduced node number
1157  real(DP) :: area
1158 
1159  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 1171 of file DiscretizationBase.f90.

1172  ! -- return
1173  real(DP) :: area_factor !< connection cell area factor
1174  ! -- dummy
1175  class(DisBaseType) :: this
1176  integer(I4B), intent(in) :: node !< cell node number
1177  integer(I4B), intent(in) :: idx_conn !< connection index
1178  ! -- local
1179  real(DP) :: area_node
1180  real(DP) :: area_conn
1181  !
1182  ! -- calculate the cell area fraction
1183  area_node = this%area(node)
1184  area_conn = this%con%hwva(idx_conn)
1185  !
1186  ! -- return the cell area factor
1187  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 657 of file DiscretizationBase.f90.

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

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

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

1198  ! dummy
1199  class(DisBaseType) :: this
1200  integer(I4B), intent(in) :: n !< cell node number
1201  integer(I4B), intent(in) :: m !< cell node number
1202  integer(I4B), intent(in) :: idx_conn !< connection index
1203  real(DP), intent(out) :: width_n !< flow width for cell n
1204  real(DP), intent(out) :: width_m !< flow width for cell m
1205  ! local
1206  integer(I4B) :: isympos
1207 
1208  ! For general case, width_n = width_m
1209  isympos = this%con%jas(idx_conn)
1210  width_n = this%con%hwva(isympos)
1211  width_m = width_n
1212 

◆ get_ncpl()

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

Definition at line 648 of file DiscretizationBase.f90.

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

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

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

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

271  class(DisBaseType) :: this
272  integer(I4B), intent(in) :: noder
273  integer(I4B) :: nodenumber
274 
275  if (this%nodes < this%nodesuser) then
276  nodenumber = this%nodeuser(noder)
277  else
278  nodenumber = noder
279  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 680 of file DiscretizationBase.f90.

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

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

1117  ! -- dummy
1118  class(DisBaseType) :: this
1119  integer(I4B), intent(inout) :: n
1120  real(DP), dimension(:), intent(in) :: sat
1121  ! -- locals
1122  integer(I4B) :: m, ii, iis
1123  logical(LGP) :: is_done, bottomcell
1124  !
1125  ! -- Loop through connected cells until the highest saturated one (including a
1126  ! constant head cell) is found. Return that cell as n.
1127  is_done = .false.
1128  do while (.not. is_done)
1129  bottomcell = .true.
1130  cloop: do ii = this%con%ia(n) + 1, this%con%ia(n + 1) - 1
1131  m = this%con%ja(ii)
1132  iis = this%con%jas(ii)
1133  if (this%con%ihc(iis) == 0 .and. m > n) then
1134  !
1135  ! -- this cannot be a bottom cell
1136  bottomcell = .false.
1137  !
1138  ! -- vertical down
1139  if (sat(m) > dzero) then
1140  n = m
1141  is_done = .true.
1142  exit cloop
1143  else
1144  n = m
1145  exit cloop
1146  end if
1147  end if
1148  end do cloop
1149  if (bottomcell) is_done = .true.
1150  end do

◆ is_1d()

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

Definition at line 1242 of file DiscretizationBase.f90.

1243  ! dummy
1244  class(DisBaseType) :: this
1245  ! return
1246  logical(LGP) :: r
1247  r = .false.
1248  select case (this%get_dis_enum())
1249  case (dis1d, disv1d, disu1d)
1250  r = .true.
1251  end select

◆ is_2d()

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

Definition at line 1229 of file DiscretizationBase.f90.

1230  ! dummy
1231  class(DisBaseType) :: this
1232  ! return
1233  logical(LGP) :: r
1234  r = .false.
1235  select case (this%get_dis_enum())
1236  case (dis2d, disv2d, disu2d)
1237  r = .true.
1238  end select

◆ is_3d()

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

Definition at line 1216 of file DiscretizationBase.f90.

1217  ! dummy
1218  class(DisBaseType) :: this
1219  ! return
1220  logical(LGP) :: r
1221  r = .false.
1222  select case (this%get_dis_enum())
1223  case (dis, disv, disu)
1224  r = .true.
1225  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 1065 of file DiscretizationBase.f90.

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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