MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
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...
 

Function/Subroutine Documentation

◆ allocate_arrays()

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

Definition at line 445 of file DiscretizationBase.f90.

446  class(DisBaseType) :: this
447  integer :: isize
448  !
449  ! -- Allocate
450  call mem_allocate(this%mshape, this%ndim, 'MSHAPE', this%memoryPath)
451  call mem_allocate(this%xc, this%nodes, 'XC', this%memoryPath)
452  call mem_allocate(this%yc, this%nodes, 'YC', this%memoryPath)
453  call mem_allocate(this%top, this%nodes, 'TOP', this%memoryPath)
454  call mem_allocate(this%bot, this%nodes, 'BOT', this%memoryPath)
455  call mem_allocate(this%area, this%nodes, 'AREA', this%memoryPath)
456  !
457  ! -- Initialize
458  this%mshape(1) = this%nodes
459  !
460  ! -- Determine size of buff memory
461  if (this%nodes < this%nodesuser) then
462  isize = this%nodesuser
463  else
464  isize = this%nodes
465  end if
466  !
467  ! -- Allocate the arrays
468  call mem_allocate(this%dbuff, isize, 'DBUFF', this%name_model)
469  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 393 of file DiscretizationBase.f90.

394  ! -- dummy
395  class(DisBaseType) :: this
396  character(len=*), intent(in) :: name_model
397  character(len=*), intent(in) :: input_mempath
398  logical(LGP) :: found
399  !
400  ! -- Create memory path
401  this%memoryPath = create_mem_path(name_model, 'DIS')
402  !
403  ! -- Allocate
404  allocate (this%name_model)
405  allocate (this%input_fname)
406  !
407  call mem_allocate(this%inunit, 'INUNIT', this%memoryPath)
408  call mem_allocate(this%iout, 'IOUT', this%memoryPath)
409  call mem_allocate(this%nodes, 'NODES', this%memoryPath)
410  call mem_allocate(this%nodesuser, 'NODESUSER', this%memoryPath)
411  call mem_allocate(this%ndim, 'NDIM', this%memoryPath)
412  call mem_allocate(this%icondir, 'ICONDIR', this%memoryPath)
413  call mem_allocate(this%nogrb, 'NOGRB', this%memoryPath)
414  call mem_allocate(this%xorigin, 'XORIGIN', this%memoryPath)
415  call mem_allocate(this%yorigin, 'YORIGIN', this%memoryPath)
416  call mem_allocate(this%angrot, 'ANGROT', this%memoryPath)
417  call mem_allocate(this%nja, 'NJA', this%memoryPath)
418  call mem_allocate(this%njas, 'NJAS', this%memoryPath)
419  call mem_allocate(this%lenuni, 'LENUNI', this%memoryPath)
420  !
421  ! -- Initialize
422  this%name_model = name_model
423  this%input_mempath = input_mempath
424  this%input_fname = ''
425  this%inunit = 0
426  this%iout = 0
427  this%nodes = 0
428  this%nodesuser = 0
429  this%ndim = 1
430  this%icondir = 1
431  this%nogrb = 0
432  this%xorigin = dzero
433  this%yorigin = dzero
434  this%angrot = dzero
435  this%nja = 0
436  this%njas = 0
437  this%lenuni = 0
438  !
439  ! -- update input filename
440  call mem_set_value(this%input_fname, 'INPUT_FNAME', &
441  this%input_mempath, found)
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 308 of file DiscretizationBase.f90.

310  class(DisBaseType) :: this
311  integer(I4B), intent(in) :: noden !< cell (reduced nn)
312  integer(I4B), intent(in) :: nodem !< neighbor (reduced nn)
313  integer(I4B), intent(in) :: ihc !< horizontal connection flag
314  real(DP), intent(inout) :: xcomp
315  real(DP), intent(inout) :: ycomp
316  real(DP), intent(inout) :: zcomp
317  integer(I4B), intent(in) :: ipos
318 
319  call store_error('Programmer error: connection_normal must be overridden', &
320  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 326 of file DiscretizationBase.f90.

328  class(DisBaseType) :: this
329  integer(I4B), intent(in) :: noden !< cell (reduced nn)
330  integer(I4B), intent(in) :: nodem !< neighbor (reduced nn)
331  logical, intent(in) :: nozee
332  real(DP), intent(in) :: satn
333  real(DP), intent(in) :: satm
334  integer(I4B), intent(in) :: ihc !< horizontal connection flag
335  real(DP), intent(inout) :: xcomp
336  real(DP), intent(inout) :: ycomp
337  real(DP), intent(inout) :: zcomp
338  real(DP), intent(inout) :: conlen
339 
340  call store_error('Programmer error: connection_vector must be overridden', &
341  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 128 of file DiscretizationBase.f90.

129  ! -- modules
130  use sparsemodule, only: sparsematrix
131  ! -- dummy
132  class(DisBaseType) :: this
133  integer(I4B), intent(in) :: moffset
134  type(sparsematrix), intent(inout) :: sparse
135  ! -- local
136  integer(I4B) :: i, j, ipos, iglo, jglo
137  !
138  do i = 1, this%nodes
139  do ipos = this%con%ia(i), this%con%ia(i + 1) - 1
140  j = this%con%ja(ipos)
141  iglo = i + moffset
142  jglo = j + moffset
143  call sparse%addconnection(iglo, jglo, 1)
144  end do
145  end do

◆ dis_ar()

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

Definition at line 169 of file DiscretizationBase.f90.

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

◆ dis_da()

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

Definition at line 200 of file DiscretizationBase.f90.

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

◆ dis_df()

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

Definition at line 121 of file DiscretizationBase.f90.

122  class(DisBaseType) :: this
123  call store_error('Programmer error: dis_df must be overridden', &
124  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 149 of file DiscretizationBase.f90.

150  ! -- dummy
151  class(DisBaseType) :: this
152  integer(I4B), intent(in) :: moffset
153  integer(I4B), dimension(:), intent(inout) :: idxglo
154  class(MatrixBaseType), pointer :: matrix_sln
155  ! -- local
156  integer(I4B) :: i, j, ipos, iglo, jglo
157  !
158  do i = 1, this%nodes
159  iglo = i + moffset
160  do ipos = this%con%ia(i), this%con%ia(i + 1) - 1
161  j = this%con%ja(ipos)
162  jglo = j + moffset
163  idxglo(ipos) = matrix_sln%get_position(iglo, jglo)
164  end do
165  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 345 of file DiscretizationBase.f90.

346  real(DP), intent(in) :: x !< the cell-x coordinate to transform
347  real(DP), intent(in) :: y !< the cell-y coordinate to transform
348  real(DP), intent(in) :: xorigin !< the cell-y coordinate to transform
349  real(DP), intent(in) :: yorigin !< the cell-y coordinate to transform
350  real(DP), intent(in) :: angrot !< the cell-y coordinate to transform
351  real(DP), intent(out) :: xglo !< the global cell-x coordinate
352  real(DP), intent(out) :: yglo !< the global cell-y coordinate
353  ! local
354  real(DP) :: ang
355 
356  xglo = x
357  yglo = y
358 
359  ! first _rotate_ to 'real world'
360  ang = angrot * dpio180
361  if (ang /= dzero) then
362  xglo = x * cos(ang) - y * sin(ang)
363  yglo = x * sin(ang) + y * cos(ang)
364  end if
365 
366  ! then _translate_
367  xglo = xglo + xorigin
368  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 728 of file DiscretizationBase.f90.

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

712  ! -- dummy
713  class(DisBaseType), intent(inout) :: this
714  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: ibuff1
715  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: ibuff2
716  ! -- local
717  integer(I4B) :: nodeu
718  integer(I4B) :: noder
719 
720  do nodeu = 1, this%nodesuser
721  noder = this%get_nodenumber(nodeu, 0)
722  if (noder <= 0) cycle
723  ibuff2(noder) = ibuff1(nodeu)
724  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 1100 of file DiscretizationBase.f90.

1101  class(DisBaseType) :: this
1102  integer(I4B), intent(in) :: node !< reduced node number
1103  real(DP) :: area
1104 
1105  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 1117 of file DiscretizationBase.f90.

1118  ! -- return
1119  real(DP) :: area_factor !< connection cell area factor
1120  ! -- dummy
1121  class(DisBaseType) :: this
1122  integer(I4B), intent(in) :: node !< cell node number
1123  integer(I4B), intent(in) :: idx_conn !< connection index
1124  ! -- local
1125  real(DP) :: area_node
1126  real(DP) :: area_conn
1127  !
1128  ! -- calculate the cell area fraction
1129  area_node = this%area(node)
1130  area_conn = this%con%hwva(idx_conn)
1131  !
1132  ! -- return the cell area factor
1133  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 641 of file DiscretizationBase.f90.

642  ! -- return
643  real(DP) :: get_cell_volume
644  ! -- dummy
645  class(DisBaseType) :: this
646  integer(I4B), intent(in) :: n
647  real(DP), intent(in) :: x
648  ! -- local
649  real(DP) :: tp
650  real(DP) :: bt
651  real(DP) :: sat
652  real(DP) :: thick
653 
654  get_cell_volume = dzero
655  tp = this%top(n)
656  bt = this%bot(n)
657  sat = squadraticsaturation(tp, bt, x)
658  thick = (tp - bt) * sat
659  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 382 of file DiscretizationBase.f90.

383  use constantsmodule, only: disundef
384  class(DisBaseType), intent(in) :: this
385  integer(I4B) :: dis_enum
386 
387  dis_enum = disundef
388  call store_error('Programmer error: get_dis_enum must be overridden', &
389  terminate=.true.)
This module contains simulation constants.
Definition: Constants.f90:9
@ disundef
undefined discretization
Definition: Constants.f90:152
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 372 of file DiscretizationBase.f90.

373  class(DisBaseType), intent(in) :: this
374  character(len=*), intent(out) :: dis_type
375 
376  dis_type = "Not implemented"
377  call store_error('Programmer error: get_dis_type must be overridden', &
378  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 1143 of file DiscretizationBase.f90.

1144  ! dummy
1145  class(DisBaseType) :: this
1146  integer(I4B), intent(in) :: n !< cell node number
1147  integer(I4B), intent(in) :: m !< cell node number
1148  integer(I4B), intent(in) :: idx_conn !< connection index
1149  real(DP), intent(out) :: width_n !< flow width for cell n
1150  real(DP), intent(out) :: width_m !< flow width for cell m
1151  ! local
1152  integer(I4B) :: isympos
1153 
1154  ! For general case, width_n = width_m
1155  isympos = this%con%jas(idx_conn)
1156  width_n = this%con%hwva(isympos)
1157  width_m = width_n
1158 

◆ get_ncpl()

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

Definition at line 632 of file DiscretizationBase.f90.

633  integer(I4B) :: get_ncpl
634  class(DisBaseType) :: this
635  get_ncpl = 0
636  call store_error('Programmer error: get_ncpl must be overridden', &
637  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 273 of file DiscretizationBase.f90.

274  class(DisBaseType), intent(in) :: this
275  integer(I4B), intent(in) :: nodeu
276  integer(I4B), intent(in) :: icheck
277  integer(I4B) :: nodenumber
278 
279  nodenumber = 0
280  call store_error('Programmer error: get_nodenumber_idx1 must be overridden', &
281  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 284 of file DiscretizationBase.f90.

285  class(DisBaseType), intent(in) :: this
286  integer(I4B), intent(in) :: k, j
287  integer(I4B), intent(in) :: icheck
288  integer(I4B) :: nodenumber
289 
290  nodenumber = 0
291  call store_error('Programmer error: get_nodenumber_idx2 must be overridden', &
292  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 295 of file DiscretizationBase.f90.

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

262  class(DisBaseType) :: this
263  integer(I4B), intent(in) :: noder
264  integer(I4B) :: nodenumber
265 
266  if (this%nodes < this%nodesuser) then
267  nodenumber = this%nodeuser(noder)
268  else
269  nodenumber = noder
270  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 664 of file DiscretizationBase.f90.

665  class(DisBaseType), intent(inout) :: this
666  integer(I4B), intent(in) :: ic !< cell number (reduced)
667  real(DP), allocatable, intent(out) :: polyverts(:, :) !< polygon vertices (column-major indexing)
668  logical(LGP), intent(in), optional :: closed !< whether to close the polygon, duplicating a vertex
669 
670  errmsg = 'Programmer error: get_polyverts must be overridden'
671  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 1062 of file DiscretizationBase.f90.

1063  ! -- dummy
1064  class(DisBaseType) :: this
1065  integer(I4B), intent(inout) :: n
1066  integer(I4B), dimension(:), intent(in) :: ibound
1067  ! -- locals
1068  integer(I4B) :: m, ii, iis
1069  logical done, bottomcell
1070  !
1071  ! -- Loop through connected cells until the highest active one (including a
1072  ! constant head cell) is found. Return that cell as n.
1073  done = .false.
1074  do while (.not. done)
1075  bottomcell = .true.
1076  cloop: do ii = this%con%ia(n) + 1, this%con%ia(n + 1) - 1
1077  m = this%con%ja(ii)
1078  iis = this%con%jas(ii)
1079  if (this%con%ihc(iis) == 0 .and. m > n) then
1080  !
1081  ! -- this cannot be a bottom cell
1082  bottomcell = .false.
1083  !
1084  ! -- vertical down
1085  if (ibound(m) /= 0) then
1086  n = m
1087  done = .true.
1088  exit cloop
1089  else
1090  n = m
1091  exit cloop
1092  end if
1093  end if
1094  end do cloop
1095  if (bottomcell) done = .true.
1096  end do

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

1050  class(DisBaseType) :: this
1051  integer(I4B), intent(in) :: maxbnd
1052  integer(I4B), dimension(:), pointer, contiguous :: darray
1053  integer(I4B), dimension(maxbnd), intent(inout) :: nodelist
1054  integer(I4B), intent(inout) :: nbound
1055  character(len=*), intent(in) :: aname
1056 
1057  errmsg = 'Programmer error: nlarray_to_nodelist must be overridden'
1058  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 576 of file DiscretizationBase.f90.

578  ! -- return
579  integer(I4B) :: noder
580  ! -- dummy
581  class(DisBaseType) :: this
582  character(len=*), intent(inout) :: cellid
583  integer(I4B), intent(in) :: inunit
584  integer(I4B), intent(in) :: iout
585  logical, optional, intent(in) :: flag_string
586  logical, optional, intent(in) :: allow_zero
587  ! -- local
588  integer(I4B) :: nodeu
589  logical :: allowzerolocal
590  character(len=LINELENGTH) :: nodestr
591  logical :: flag_string_local
592  !
593  if (present(flag_string)) then
594  flag_string_local = flag_string
595  else
596  flag_string_local = .false.
597  end if
598  if (present(allow_zero)) then
599  allowzerolocal = allow_zero
600  else
601  allowzerolocal = .false.
602  end if
603  !
604  nodeu = this%nodeu_from_cellid(cellid, inunit, iout, flag_string_local, &
605  allowzerolocal)
606  !
607  ! -- Convert user-based nodenumber to reduced node number
608  if (nodeu > 0) then
609  noder = this%get_nodenumber(nodeu, 0)
610  else
611  noder = nodeu
612  end if
613  if (noder <= 0 .and. .not. flag_string_local) then
614  call this%nodeu_to_string(nodeu, nodestr)
615  write (errmsg, *) &
616  ' Cell is outside active grid domain: '// &
617  trim(adjustl(nodestr))
618  call store_error(errmsg)
619  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 528 of file DiscretizationBase.f90.

530  ! -- dummy
531  class(DisBaseType) :: this
532  integer(I4B), intent(inout) :: lloc
533  integer(I4B), intent(inout) :: istart
534  integer(I4B), intent(inout) :: istop
535  integer(I4B), intent(in) :: in
536  integer(I4B), intent(in) :: iout
537  character(len=*), intent(inout) :: line
538  logical, optional, intent(in) :: flag_string
539  integer(I4B) :: noder
540  ! -- local
541  integer(I4B) :: nodeu
542  character(len=LINELENGTH) :: nodestr
543  logical :: flag_string_local
544  !
545  if (present(flag_string)) then
546  flag_string_local = flag_string
547  else
548  flag_string_local = .false.
549  end if
550  nodeu = this%nodeu_from_string(lloc, istart, istop, in, iout, line, &
551  flag_string_local)
552  !
553  ! -- Convert user-based nodenumber to reduced node number
554  if (nodeu > 0) then
555  noder = this%get_nodenumber(nodeu, 0)
556  else
557  noder = nodeu
558  end if
559  if (noder <= 0 .and. .not. flag_string_local) then
560  call this%nodeu_to_string(nodeu, nodestr)
561  write (errmsg, *) &
562  ' Cell is outside active grid domain: '// &
563  trim(adjustl(nodestr))
564  call store_error(errmsg)
565  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 970 of file DiscretizationBase.f90.

971  ! -- dummy
972  class(DisBaseType) :: this
973  integer(I4B), intent(in) :: noder
974  integer(I4B), dimension(:), intent(inout) :: arr
975  ! -- local
976  integer(I4B) :: nodeu
977 
978  nodeu = this%get_nodeuser(noder)
979  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 957 of file DiscretizationBase.f90.

958  ! -- dummy
959  class(DisBaseType) :: this
960  integer(I4B), intent(in) :: noder
961  character(len=*), intent(inout) :: str
962  ! -- local
963  integer(I4B) :: nodeu
964 
965  nodeu = this%get_nodeuser(noder)
966  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 505 of file DiscretizationBase.f90.

507  ! -- dummy
508  class(DisBaseType) :: this
509  character(len=*), intent(inout) :: cellid
510  integer(I4B), intent(in) :: inunit
511  integer(I4B), intent(in) :: iout
512  logical, optional, intent(in) :: flag_string
513  logical, optional, intent(in) :: allow_zero
514  integer(I4B) :: nodeu
515 
516  nodeu = 0
517  call store_error('Programmer error: nodeu_from_cellid must be overridden', &
518  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 478 of file DiscretizationBase.f90.

480  ! -- dummy
481  class(DisBaseType) :: this
482  integer(I4B), intent(inout) :: lloc
483  integer(I4B), intent(inout) :: istart
484  integer(I4B), intent(inout) :: istop
485  integer(I4B), intent(in) :: in
486  integer(I4B), intent(in) :: iout
487  character(len=*), intent(inout) :: line
488  logical, optional, intent(in) :: flag_string
489  logical, optional, intent(in) :: allow_zero
490  integer(I4B) :: nodeu
491 
492  nodeu = 0
493  call store_error('Programmer error: nodeu_from_string must be overridden', &
494  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 251 of file DiscretizationBase.f90.

252  class(DisBaseType) :: this
253  integer(I4B), intent(in) :: nodeu
254  integer(I4B), dimension(:), intent(inout) :: arr
255 
256  call store_error('Programmer error: nodeu_to_array must be overridden', &
257  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 241 of file DiscretizationBase.f90.

242  class(DisBaseType) :: this
243  integer(I4B), intent(in) :: nodeu
244  character(len=*), intent(inout) :: str
245 
246  call store_error('Programmer error: nodeu_to_string must be overridden', &
247  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 693 of file DiscretizationBase.f90.

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

677  ! -- dummy
678  class(DisBaseType), intent(inout) :: this
679  character(len=*), intent(inout) :: line
680  integer(I4B), intent(inout) :: lloc
681  integer(I4B), intent(inout) :: istart
682  integer(I4B), intent(inout) :: istop
683  integer(I4B), intent(in) :: in
684  integer(I4B), intent(in) :: iout
685  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: iarray
686  character(len=*), intent(in) :: aname
687 
688  errmsg = 'Programmer error: read_int_array must be overridden'
689  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 899 of file DiscretizationBase.f90.

901  ! -- dummy
902  class(DisBaseType) :: this
903  integer(I4B), intent(in) :: ncolbnd
904  integer(I4B), intent(in) :: maxbnd
905  integer(I4B), dimension(maxbnd) :: nodelist
906  real(DP), dimension(ncolbnd, maxbnd), intent(inout) :: darray
907  integer(I4B), intent(in) :: icolbnd
908  character(len=*), intent(in) :: aname
909  integer(I4B), intent(in) :: inunit
910  integer(I4B), intent(in) :: iout
911 
912  errmsg = 'Programmer error: read_layer_array must be overridden'
913  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 751 of file DiscretizationBase.f90.

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

922  ! -- dummy
923  class(DisBaseType), intent(inout) :: this
924  real(DP), dimension(:), pointer, contiguous, intent(inout) :: darray !< double precision array to record
925  integer(I4B), intent(in) :: iout !< ascii output unit number
926  integer(I4B), intent(in) :: iprint !< whether to print the array
927  integer(I4B), intent(in) :: idataun !< binary output unit number
928  character(len=*), intent(in) :: aname !< text descriptor
929  character(len=*), intent(in) :: cdatafmp !< write format
930  integer(I4B), intent(in) :: nvaluesp !< values per line
931  integer(I4B), intent(in) :: nwidthp !< number width
932  character(len=*), intent(in) :: editdesc !< format type (I, G, F, S, E)
933  real(DP), intent(in) :: dinact !< double precision value for cells excluded from model domain
934 
935  errmsg = 'Programmer error: record_array must be overridden'
936  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 940 of file DiscretizationBase.f90.

941  ! -- dummy
942  class(DisBaseType) :: this
943  real(DP), dimension(:), intent(in) :: flowja
944  integer(I4B), intent(in) :: ibinun
945  integer(I4B), intent(in) :: iout
946  ! -- local
947  character(len=16), dimension(1) :: text
948  ! -- data
949  data text(1)/' FLOW-JA-FACE'/
950 
951  ! -- write full ja array
952  call ubdsv1(kstp, kper, text(1), ibinun, flowja, size(flowja), 1, 1, &
953  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 1003 of file DiscretizationBase.f90.

1005  ! -- dummy
1006  class(DisBaseType) :: this
1007  integer(I4B), intent(in) :: ibdchn
1008  integer(I4B), intent(in) :: noder
1009  integer(I4B), intent(in) :: noder2
1010  real(DP), intent(in) :: q
1011  integer(I4B), intent(in) :: naux
1012  real(DP), dimension(naux), intent(in) :: aux
1013  logical, optional, intent(in) :: olconv
1014  logical, optional, intent(in) :: olconv2
1015  ! -- local
1016  logical :: lconv
1017  logical :: lconv2
1018  integer(I4B) :: nodeu
1019  integer(I4B) :: nodeu2
1020  !
1021  ! -- Use ubdsvb to write list header
1022  if (present(olconv)) then
1023  lconv = olconv
1024  else
1025  lconv = .true.
1026  end if
1027  if (lconv) then
1028  nodeu = this%get_nodeuser(noder)
1029  else
1030  nodeu = noder
1031  end if
1032  if (present(olconv2)) then
1033  lconv2 = olconv2
1034  else
1035  lconv2 = .true.
1036  end if
1037  if (lconv2) then
1038  nodeu2 = this%get_nodeuser(noder2)
1039  else
1040  nodeu2 = noder2
1041  end if
1042  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 983 of file DiscretizationBase.f90.

986  class(DisBaseType) :: this
987  character(len=16), intent(in) :: text
988  character(len=16), intent(in) :: textmodel
989  character(len=16), intent(in) :: textpackage
990  character(len=16), intent(in) :: dstmodel
991  character(len=16), intent(in) :: dstpackage
992  integer(I4B), intent(in) :: naux
993  character(len=16), dimension(:), intent(in) :: auxtxt
994  integer(I4B), intent(in) :: ibdchn
995  integer(I4B), intent(in) :: nlist
996  integer(I4B), intent(in) :: iout
997 
998  errmsg = 'Programmer error: record_srcdst_list_header must be overridden'
999  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 623 of file DiscretizationBase.f90.

624  class(DisBaseType) :: this
625  supports_layers = .false.
626  call store_error('Programmer error: supports_layers must be overridden', &
627  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 192 of file DiscretizationBase.f90.

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