MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
Disu.f90
Go to the documentation of this file.
1 module disumodule
2 
4  use kindmodule, only: dp, i4b, lgp
13  use basedismodule, only: disbasetype
17  use tdismodule, only: kstp, kper, pertim, totim, delt
18  use disvgeom, only: line_unit_vector
19 
20  implicit none
21 
22  private
23  public :: disutype
24  public :: disu_cr
25  public :: castasdisutype
26 
27  !> @brief Unstructured grid discretization
28  type, extends(disbasetype) :: disutype
29  integer(I4B), pointer :: njausr => null() ! user-specified nja size
30  integer(I4B), pointer :: nvert => null() ! number of x,y vertices
31  real(dp), pointer :: voffsettol => null() ! vertical offset tolerance
32  real(dp), dimension(:, :), pointer, contiguous :: vertices => null() ! cell vertices stored as 2d array of x and y
33  real(dp), dimension(:, :), pointer, contiguous :: cellxy => null() ! cell center stored as 2d array of x and y
34  real(dp), dimension(:), pointer, contiguous :: top1d => null() ! (size:nodesuser) cell top elevation
35  real(dp), dimension(:), pointer, contiguous :: bot1d => null() ! (size:nodesuser) cell bottom elevation
36  real(dp), dimension(:), pointer, contiguous :: area1d => null() ! (size:nodesuser) cell area, in plan view
37  integer(I4B), dimension(:), pointer, contiguous :: iainp => null() ! (size:nodesuser+1) user iac converted ia
38  integer(I4B), dimension(:), pointer, contiguous :: jainp => null() ! (size:njausr) user-input ja array
39  integer(I4B), dimension(:), pointer, contiguous :: ihcinp => null() ! (size:njausr) user-input ihc array
40  real(dp), dimension(:), pointer, contiguous :: cl12inp => null() ! (size:njausr) user-input cl12 array
41  real(dp), dimension(:), pointer, contiguous :: hwvainp => null() ! (size:njausr) user-input hwva array
42  real(dp), dimension(:), pointer, contiguous :: angldegxinp => null() ! (size:njausr) user-input angldegx array
43  integer(I4B), pointer :: iangledegx => null() ! =1 when angle information was present in input, 0 otherwise
44  integer(I4B), dimension(:), pointer, contiguous :: iavert => null() ! cell vertex pointer ia array
45  integer(I4B), dimension(:), pointer, contiguous :: javert => null() ! cell vertex pointer ja array
46  integer(I4B), dimension(:), pointer, contiguous :: idomain => null() ! idomain (nodes)
47  logical(LGP) :: readfromfile ! True, when DIS is read from file (almost always)
48 
49  contains
50 
51  procedure :: dis_df => disu_df
52  procedure :: disu_load
53  procedure :: dis_da => disu_da
54  procedure :: get_dis_type => get_dis_type
55  procedure :: get_dis_enum => get_dis_enum
56  procedure :: disu_ck
57  procedure :: grid_finalize
58  procedure :: get_nodenumber_idx1
59  procedure :: nodeu_to_string
60  procedure :: nodeu_to_array
61  procedure :: nodeu_from_string
62  procedure :: nodeu_from_cellid
63  procedure :: connection_normal
64  procedure :: connection_vector
65  procedure :: supports_layers
66  procedure :: get_ncpl
67  procedure, public :: record_array
68  procedure, public :: record_srcdst_list_header
69  ! -- private
70  procedure :: allocate_scalars
71  procedure :: allocate_arrays
72  procedure :: allocate_arrays_mem
73  procedure :: source_options
74  procedure :: source_dimensions
75  procedure :: source_griddata
76  procedure :: source_connectivity
77  procedure :: source_vertices
78  procedure :: source_cell2d
79  procedure :: log_options
80  procedure :: log_dimensions
81  procedure :: log_griddata
82  procedure :: log_connectivity
83  procedure :: define_cellverts
84  procedure :: write_grb
85  !
86  ! -- Read a node-sized model array (reduced or not)
87  procedure :: read_int_array
88  procedure :: read_dbl_array
89 
90  end type disutype
91 
93  logical :: length_units = .false.
94  logical :: nogrb = .false.
95  logical :: xorigin = .false.
96  logical :: yorigin = .false.
97  logical :: angrot = .false.
98  logical :: voffsettol = .false.
99  logical :: nodes = .false.
100  logical :: nja = .false.
101  logical :: nvert = .false.
102  logical :: top = .false.
103  logical :: bot = .false.
104  logical :: area = .false.
105  logical :: idomain = .false.
106  logical :: iac = .false.
107  logical :: ja = .false.
108  logical :: ihc = .false.
109  logical :: cl12 = .false.
110  logical :: hwva = .false.
111  logical :: angldegx = .false.
112  logical :: iv = .false.
113  logical :: xv = .false.
114  logical :: yv = .false.
115  logical :: icell2d = .false.
116  logical :: xc = .false.
117  logical :: yc = .false.
118  logical :: ncvert = .false.
119  logical :: icvert = .false.
120  end type disufoundtype
121 
122 contains
123 
124  !> @brief Create a new unstructured discretization object
125  !<
126  subroutine disu_cr(dis, name_model, input_mempath, inunit, iout)
127  ! -- dummy
128  class(disbasetype), pointer :: dis
129  character(len=*), intent(in) :: name_model
130  character(len=*), intent(in) :: input_mempath
131  integer(I4B), intent(in) :: inunit
132  integer(I4B), intent(in) :: iout
133  ! -- local
134  type(disutype), pointer :: disnew
135  character(len=*), parameter :: fmtheader = &
136  "(1X, /1X, 'DISU -- UNSTRUCTURED GRID DISCRETIZATION PACKAGE,', &
137  &' VERSION 2 : 3/27/2014 - INPUT READ FROM MEMPATH: ', A, //)"
138  !
139  ! -- Create a new discretization object
140  allocate (disnew)
141  dis => disnew
142  !
143  ! -- Allocate scalars and assign data
144  call dis%allocate_scalars(name_model, input_mempath)
145  dis%inunit = inunit
146  dis%iout = iout
147  !
148  ! -- If disu is enabled
149  if (inunit > 0) then
150  !
151  ! -- Identify package
152  if (iout > 0) then
153  write (iout, fmtheader) dis%input_mempath
154  end if
155  !
156  ! -- load disu
157  call disnew%disu_load()
158  end if
159  !
160  end subroutine disu_cr
161 
162  !> @brief Transfer IDM data into this discretization object
163  !<
164  subroutine disu_load(this)
165  ! -- dummy
166  class(disutype) :: this
167  !
168  ! -- source input data
169  call this%source_options()
170  call this%source_dimensions()
171  call this%source_griddata()
172  call this%source_connectivity()
173  !
174  ! -- If NVERT specified and greater than 0, then source VERTICES and CELL2D
175  if (this%nvert > 0) then
176  call this%source_vertices()
177  call this%source_cell2d()
178  else
179  ! -- connection direction information cannot be calculated
180  this%icondir = 0
181  end if
182  !
183  ! -- Make some final disu checks on the non-reduced user-provided
184  ! input
185  call this%disu_ck()
186  !
187  end subroutine disu_load
188 
189  !> @brief Define the discretization
190  !<
191  subroutine disu_df(this)
192  ! -- dummy
193  class(disutype) :: this
194  !
195  call this%grid_finalize()
196  !
197  end subroutine disu_df
198 
199  !> @brief Finalize the grid
200  !<
201  subroutine grid_finalize(this)
202  ! -- dummy
203  class(disutype) :: this
204  ! -- locals
205  integer(I4B) :: n
206  integer(I4B) :: node
207  integer(I4B) :: noder
208  integer(I4B) :: nrsize
209  ! -- formats
210  character(len=*), parameter :: fmtdz = &
211  "('CELL (',i0,',',i0,',',i0,') THICKNESS <= 0. ', &
212  &'TOP, BOT: ',2(1pg24.15))"
213  character(len=*), parameter :: fmtnr = &
214  "(/1x, 'The specified IDOMAIN results in a reduced number of cells.',&
215  &/1x, 'Number of user nodes: ',I0,&
216  &/1X, 'Number of nodes in solution: ', I0, //)"
217  !
218  ! -- count active cells
219  this%nodes = 0
220  do n = 1, this%nodesuser
221  if (this%idomain(n) > 0) this%nodes = this%nodes + 1
222  end do
223  !
224  ! -- Check to make sure nodes is a valid number
225  if (this%nodes == 0) then
226  call store_error('Model does not have any active nodes. &
227  &Ensure IDOMAIN array has some values greater &
228  &than zero.')
229  call store_error_filename(this%input_fname)
230  end if
231  !
232  ! -- Write message if reduced grid
233  if (this%nodes < this%nodesuser) then
234  write (this%iout, fmtnr) this%nodesuser, this%nodes
235  end if
236  !
237  ! -- Array size is now known, so allocate
238  call this%allocate_arrays()
239  !
240  ! -- Fill the nodereduced array with the reduced nodenumber, or
241  ! a negative number to indicate it is a pass-through cell, or
242  ! a zero to indicate that the cell is excluded from the
243  ! solution. (negative idomain not supported for disu)
244  if (this%nodes < this%nodesuser) then
245  noder = 1
246  do node = 1, this%nodesuser
247  if (this%idomain(node) > 0) then
248  this%nodereduced(node) = noder
249  noder = noder + 1
250  elseif (this%idomain(node) < 0) then
251  this%nodereduced(node) = -1
252  else
253  this%nodereduced(node) = 0
254  end if
255  end do
256  end if
257  !
258  ! -- Fill nodeuser if a reduced grid
259  if (this%nodes < this%nodesuser) then
260  noder = 1
261  do node = 1, this%nodesuser
262  if (this%idomain(node) > 0) then
263  this%nodeuser(noder) = node
264  noder = noder + 1
265  end if
266  end do
267  end if
268  !
269  ! -- Move top1d, bot1d, and area1d into top, bot, and area
270  do node = 1, this%nodesuser
271  noder = node
272  if (this%nodes < this%nodesuser) noder = this%nodereduced(node)
273  if (noder <= 0) cycle
274  this%top(noder) = this%top1d(node)
275  this%bot(noder) = this%bot1d(node)
276  this%area(noder) = this%area1d(node)
277  end do
278  !
279  ! -- fill cell center coordinates
280  if (this%nvert > 0) then
281  do node = 1, this%nodesuser
282  noder = node
283  if (this%nodes < this%nodesuser) noder = this%nodereduced(node)
284  if (noder <= 0) cycle
285  this%xc(noder) = this%cellxy(1, node)
286  this%yc(noder) = this%cellxy(2, node)
287  end do
288  else
289  call mem_reallocate(this%xc, 0, 'XC', this%memoryPath)
290  call mem_reallocate(this%yc, 0, 'YC', this%memoryPath)
291  end if
292  !
293  ! -- create and fill the connections object
294  nrsize = 0
295  if (this%nodes < this%nodesuser) nrsize = this%nodes
296  allocate (this%con)
297  call this%con%disuconnections(this%name_model, this%nodes, &
298  this%nodesuser, nrsize, &
299  this%nodereduced, this%nodeuser, &
300  this%iainp, this%jainp, &
301  this%ihcinp, this%cl12inp, &
302  this%hwvainp, this%angldegxinp, &
303  this%iangledegx)
304  this%nja = this%con%nja
305  this%njas = this%con%njas
306  !
307  end subroutine grid_finalize
308 
309  !> @brief Check discretization info
310  !<
311  subroutine disu_ck(this)
312  ! -- dummy
313  class(disutype) :: this
314  ! -- local
315  integer(I4B) :: n, m
316  integer(I4B) :: ipos
317  integer(I4B) :: ihc
318  real(DP) :: dz
319  ! -- formats
320  character(len=*), parameter :: fmtidm = &
321  &"('Invalid idomain value ', i0, ' specified for node ', i0)"
322  character(len=*), parameter :: fmtdz = &
323  &"('Cell ', i0, ' with thickness <= 0. Top, bot: ', 2(1pg24.15))"
324  character(len=*), parameter :: fmtarea = &
325  &"('Cell ', i0, ' with area <= 0. Area: ', 1(1pg24.15))"
326  character(len=*), parameter :: fmtjan = &
327  &"('Cell ', i0, ' must have its first connection be itself. Found: ', i0)"
328  character(len=*), parameter :: fmtjam = &
329  &"('Cell ', i0, ' has invalid connection in JA. Found: ', i0)"
330  character(len=*), parameter :: fmterrmsg = &
331  "('Top elevation (', 1pg15.6, ') for cell ', i0, ' is above bottom &
332  &elevation (', 1pg15.6, ') for cell ', i0, '. Based on node numbering &
333  &rules cell ', i0, ' must be below cell ', i0, '.')"
334  !
335  ! -- Check connectivity
336  do n = 1, this%nodesuser
337  !
338  ! -- Ensure first connection is to itself, and
339  ! that ja(ia(n)) is positive
340  ipos = this%iainp(n)
341  m = this%jainp(ipos)
342  if (m < 0) then
343  m = abs(m)
344  this%jainp(ipos) = m
345  end if
346  if (n /= m) then
347  write (errmsg, fmtjan) n, m
348  call store_error(errmsg)
349  end if
350  !
351  ! -- Check for valid node numbers in connected cells
352  do ipos = this%iainp(n) + 1, this%iainp(n + 1) - 1
353  m = this%jainp(ipos)
354  if (m < 0 .or. m > this%nodesuser) then
355  ! -- make sure first connection is to itself
356  write (errmsg, fmtjam) n, m
357  call store_error(errmsg)
358  end if
359  end do
360  end do
361  !
362  ! -- terminate if errors found
363  if (count_errors() > 0) then
364  if (this%inunit > 0) then
365  call store_error_filename(this%input_fname)
366  end if
367  end if
368  !
369  ! -- Ensure idomain values are valid
370  do n = 1, this%nodesuser
371  if (this%idomain(n) > 1 .or. this%idomain(n) < 0) then
372  write (errmsg, fmtidm) this%idomain(n), n
373  call store_error(errmsg)
374  end if
375  end do
376  !
377  ! -- Check for zero and negative thickness and zero or negative areas
378  ! for cells with idomain == 1
379  do n = 1, this%nodesuser
380  if (this%idomain(n) == 1) then
381  dz = this%top1d(n) - this%bot1d(n)
382  if (dz <= dzero) then
383  write (errmsg, fmt=fmtdz) n, this%top1d(n), this%bot1d(n)
384  call store_error(errmsg)
385  end if
386  if (this%area1d(n) <= dzero) then
387  write (errmsg, fmt=fmtarea) n, this%area1d(n)
388  call store_error(errmsg)
389  end if
390  end if
391  end do
392  !
393  ! -- check to make sure voffsettol is >= 0
394  if (this%voffsettol < dzero) then
395  write (errmsg, '(a, 1pg15.6)') &
396  'Vertical offset tolerance must be greater than zero. Found ', &
397  this%voffsettol
398  call store_error(errmsg)
399  if (this%inunit > 0) then
400  call store_error_filename(this%input_fname)
401  end if
402  end if
403  !
404  ! -- For cell n, ensure that underlying cells have tops less than
405  ! or equal to the bottom of cell n
406  do n = 1, this%nodesuser
407  do ipos = this%iainp(n) + 1, this%iainp(n + 1) - 1
408  m = this%jainp(ipos)
409  ihc = this%ihcinp(ipos)
410  if (ihc == 0 .and. m > n) then
411  dz = this%top1d(m) - this%bot1d(n)
412  if (dz > this%voffsettol) then
413  write (errmsg, fmterrmsg) this%top1d(m), m, this%bot1d(n), n, m, n
414  call store_error(errmsg)
415  end if
416  end if
417  end do
418  end do
419  !
420  ! -- terminate if errors found
421  if (count_errors() > 0) then
422  if (this%inunit > 0) then
423  call store_error_filename(this%input_fname)
424  end if
425  end if
426  !
427  end subroutine disu_ck
428 
429  !> @brief Deallocate variables
430  !<
431  subroutine disu_da(this)
432  ! -- dummy
433  class(disutype) :: this
434  !
435  ! -- Deallocate idm memory
436  call memorystore_remove(this%name_model, 'DISU', idm_context)
437  call memorystore_remove(component=this%name_model, &
438  context=idm_context)
439  !
440  ! -- scalars
441  call mem_deallocate(this%njausr)
442  call mem_deallocate(this%nvert)
443  call mem_deallocate(this%voffsettol)
444  call mem_deallocate(this%iangledegx)
445  !
446  ! -- arrays
447  if (this%readFromFile) then
448  call mem_deallocate(this%top1d)
449  call mem_deallocate(this%bot1d)
450  call mem_deallocate(this%area1d)
451  if (associated(this%iavert)) then
452  call mem_deallocate(this%iavert)
453  call mem_deallocate(this%javert)
454  end if
455  call mem_deallocate(this%vertices)
456  call mem_deallocate(this%iainp)
457  call mem_deallocate(this%jainp)
458  call mem_deallocate(this%ihcinp)
459  call mem_deallocate(this%cl12inp)
460  call mem_deallocate(this%hwvainp)
461  call mem_deallocate(this%angldegxinp)
462  end if
463  !
464  call mem_deallocate(this%idomain)
465  call mem_deallocate(this%cellxy)
466  !
467  call mem_deallocate(this%nodeuser)
468  call mem_deallocate(this%nodereduced)
469  !
470  ! -- DisBaseType deallocate
471  call this%DisBaseType%dis_da()
472  !
473  end subroutine disu_da
474 
475  !> @brief Convert a user nodenumber to a string (nodenumber)
476  !<
477  subroutine nodeu_to_string(this, nodeu, str)
478  ! -- dummy
479  class(disutype) :: this
480  integer(I4B), intent(in) :: nodeu
481  character(len=*), intent(inout) :: str
482  ! -- local
483  character(len=10) :: nstr
484  !
485  write (nstr, '(i0)') nodeu
486  str = '('//trim(adjustl(nstr))//')'
487  !
488  end subroutine nodeu_to_string
489 
490  !> @brief Convert a user nodenumber to an array (nodenumber)
491  !<
492  subroutine nodeu_to_array(this, nodeu, arr)
493  class(disutype) :: this
494  integer(I4B), intent(in) :: nodeu
495  integer(I4B), dimension(:), intent(inout) :: arr
496  ! -- local
497  integer(I4B) :: isize
498  !
499  ! -- check the size of arr
500  isize = size(arr)
501  if (isize /= this%ndim) then
502  write (errmsg, '(a,i0,a,i0,a)') &
503  'Program error: nodeu_to_array size of array (', isize, &
504  ') is not equal to the discretization dimension (', this%ndim, ')'
505  call store_error(errmsg, terminate=.true.)
506  end if
507  !
508  ! -- fill array
509  arr(1) = nodeu
510  !
511  end subroutine nodeu_to_array
512 
513  !> @brief Copy options from IDM into package
514  !<
515  subroutine source_options(this)
516  ! -- dummy
517  class(disutype) :: this
518  ! -- locals
519  character(len=LENVARNAME), dimension(3) :: lenunits = &
520  &[character(len=LENVARNAME) :: 'FEET', 'METERS', 'CENTIMETERS']
521  type(disufoundtype) :: found
522  !
523  ! -- update defaults with idm sourced values
524  call mem_set_value(this%lenuni, 'LENGTH_UNITS', this%input_mempath, &
525  lenunits, found%length_units)
526  call mem_set_value(this%nogrb, 'NOGRB', this%input_mempath, found%nogrb)
527  call mem_set_value(this%xorigin, 'XORIGIN', this%input_mempath, found%xorigin)
528  call mem_set_value(this%yorigin, 'YORIGIN', this%input_mempath, found%yorigin)
529  call mem_set_value(this%angrot, 'ANGROT', this%input_mempath, found%angrot)
530  call mem_set_value(this%voffsettol, 'VOFFSETTOL', this%input_mempath, &
531  found%voffsettol)
532  !
533  ! -- log values to list file
534  if (this%iout > 0) then
535  call this%log_options(found)
536  end if
537  !
538  end subroutine source_options
539 
540  !> @brief Write user options to list file
541  !<
542  subroutine log_options(this, found)
543  ! -- dummy
544  class(disutype) :: this
545  type(disufoundtype), intent(in) :: found
546  !
547  write (this%iout, '(1x,a)') 'Setting Discretization Options'
548  !
549  if (found%length_units) then
550  write (this%iout, '(4x,a,i0)') 'Model length unit [0=UND, 1=FEET, &
551  &2=METERS, 3=CENTIMETERS] set as ', this%lenuni
552  end if
553  !
554  if (found%nogrb) then
555  write (this%iout, '(4x,a,i0)') 'Binary grid file [0=GRB, 1=NOGRB] &
556  &set as ', this%nogrb
557  end if
558  !
559  if (found%xorigin) then
560  write (this%iout, '(4x,a,G0)') 'XORIGIN = ', this%xorigin
561  end if
562  !
563  if (found%yorigin) then
564  write (this%iout, '(4x,a,G0)') 'YORIGIN = ', this%yorigin
565  end if
566  !
567  if (found%angrot) then
568  write (this%iout, '(4x,a,G0)') 'ANGROT = ', this%angrot
569  end if
570  !
571  if (found%voffsettol) then
572  write (this%iout, '(4x,a,G0)') 'VERTICAL_OFFSET_TOLERANCE = ', &
573  this%voffsettol
574  end if
575  !
576  write (this%iout, '(1x,a,/)') 'End Setting Discretization Options'
577  !
578  end subroutine log_options
579 
580  !> @brief Copy dimensions from IDM into package
581  !<
582  subroutine source_dimensions(this)
583  ! -- dummy
584  class(disutype) :: this
585  ! -- locals
586  integer(I4B) :: n
587  type(disufoundtype) :: found
588  !
589  ! -- update defaults with idm sourced values
590  call mem_set_value(this%nodesuser, 'NODES', this%input_mempath, found%nodes)
591  call mem_set_value(this%njausr, 'NJA', this%input_mempath, found%nja)
592  call mem_set_value(this%nvert, 'NVERT', this%input_mempath, found%nvert)
593  !
594  ! -- log simulation values
595  if (this%iout > 0) then
596  call this%log_dimensions(found)
597  end if
598  !
599  ! -- verify dimensions were set
600  if (this%nodesuser < 1) then
601  call store_error( &
602  'NODES was not specified or was specified incorrectly.')
603  end if
604  if (this%njausr < 1) then
605  call store_error( &
606  'NJA was not specified or was specified incorrectly.')
607  end if
608  !
609  ! -- terminate if errors were detected
610  if (count_errors() > 0) then
611  call store_error_filename(this%input_fname)
612  end if
613  !
614  ! -- allocate vectors that are the size of nodesuser
615  this%readFromFile = .true.
616  call mem_allocate(this%top1d, this%nodesuser, 'TOP1D', this%memoryPath)
617  call mem_allocate(this%bot1d, this%nodesuser, 'BOT1D', this%memoryPath)
618  call mem_allocate(this%area1d, this%nodesuser, 'AREA1D', this%memoryPath)
619  call mem_allocate(this%idomain, this%nodesuser, 'IDOMAIN', this%memoryPath)
620  call mem_allocate(this%vertices, 2, this%nvert, 'VERTICES', this%memoryPath)
621  call mem_allocate(this%iainp, this%nodesuser + 1, 'IAINP', this%memoryPath)
622  call mem_allocate(this%jainp, this%njausr, 'JAINP', this%memoryPath)
623  call mem_allocate(this%ihcinp, this%njausr, 'IHCINP', this%memoryPath)
624  call mem_allocate(this%cl12inp, this%njausr, 'CL12INP', this%memoryPath)
625  call mem_allocate(this%hwvainp, this%njausr, 'HWVAINP', this%memoryPath)
626  call mem_allocate(this%angldegxinp, this%njausr, 'ANGLDEGXINP', &
627  this%memoryPath)
628  if (this%nvert > 0) then
629  call mem_allocate(this%cellxy, 2, this%nodesuser, 'CELLXY', this%memoryPath)
630  else
631  call mem_allocate(this%cellxy, 2, 0, 'CELLXY', this%memoryPath)
632  end if
633  !
634  ! -- initialize all cells to be active (idomain = 1)
635  do n = 1, this%nodesuser
636  this%idomain(n) = 1
637  end do
638  !
639  end subroutine source_dimensions
640 
641  !> @brief Write dimensions to list file
642  !<
643  subroutine log_dimensions(this, found)
644  class(disutype) :: this
645  type(disufoundtype), intent(in) :: found
646  !
647  write (this%iout, '(1x,a)') 'Setting Discretization Dimensions'
648  !
649  if (found%nodes) then
650  write (this%iout, '(4x,a,i0)') 'NODES = ', this%nodesuser
651  end if
652  !
653  if (found%nja) then
654  write (this%iout, '(4x,a,i0)') 'NJA = ', this%njausr
655  end if
656  !
657  if (found%nvert) then
658  write (this%iout, '(4x,a,i0)') 'NVERT = ', this%nvert
659  end if
660  !
661  write (this%iout, '(1x,a,/)') 'End Setting Discretization Dimensions'
662  !
663  end subroutine log_dimensions
664 
665  !> @brief Copy grid data from IDM into package
666  !<
667  subroutine source_griddata(this)
668  ! -- dummy
669  class(disutype) :: this
670  ! -- locals
671  type(disufoundtype) :: found
672  !
673  ! -- update defaults with idm sourced values
674  call mem_set_value(this%top1d, 'TOP', this%input_mempath, found%top)
675  call mem_set_value(this%bot1d, 'BOT', this%input_mempath, found%bot)
676  call mem_set_value(this%area1d, 'AREA', this%input_mempath, found%area)
677  call mem_set_value(this%idomain, 'IDOMAIN', this%input_mempath, found%idomain)
678  !
679  ! -- log simulation values
680  if (this%iout > 0) then
681  call this%log_griddata(found)
682  end if
683  !
684  end subroutine source_griddata
685 
686  !> @brief Write griddata found to list file
687  !<
688  subroutine log_griddata(this, found)
689  ! -- dummy
690  class(disutype) :: this
691  type(disufoundtype), intent(in) :: found
692  !
693  write (this%iout, '(1x,a)') 'Setting Discretization Griddata'
694  !
695  if (found%top) then
696  write (this%iout, '(4x,a)') 'TOP set from input file'
697  end if
698  !
699  if (found%bot) then
700  write (this%iout, '(4x,a)') 'BOT set from input file'
701  end if
702  !
703  if (found%area) then
704  write (this%iout, '(4x,a)') 'AREA set from input file'
705  end if
706  !
707  if (found%idomain) then
708  write (this%iout, '(4x,a)') 'IDOMAIN set from input file'
709  end if
710  !
711  write (this%iout, '(1x,a,/)') 'End Setting Discretization Griddata'
712  !
713  end subroutine log_griddata
714 
715  !> @brief Copy grid connectivity info from IDM into package
716  !<
717  subroutine source_connectivity(this)
718  ! -- dummy
719  class(disutype) :: this
720  ! -- locals
721  type(disufoundtype) :: found
722  integer(I4B), dimension(:), contiguous, pointer :: iac => null()
723  ! -- formats
724  !
725  ! -- update defaults with idm sourced values
726  call mem_set_value(this%jainp, 'JA', this%input_mempath, found%ja)
727  call mem_set_value(this%ihcinp, 'IHC', this%input_mempath, found%ihc)
728  call mem_set_value(this%cl12inp, 'CL12', this%input_mempath, found%cl12)
729  call mem_set_value(this%hwvainp, 'HWVA', this%input_mempath, found%hwva)
730  call mem_set_value(this%angldegxinp, 'ANGLDEGX', this%input_mempath, &
731  found%angldegx)
732  !
733  ! -- set pointer to iac input array
734  call mem_setptr(iac, 'IAC', this%input_mempath)
735  !
736  ! -- Convert iac to ia
737  if (associated(iac)) call iac_to_ia(iac, this%iainp)
738  !
739  ! -- Set angldegx flag if found
740  if (found%angldegx) this%iangledegx = 1
741  !
742  ! -- log simulation values
743  if (this%iout > 0) then
744  call this%log_connectivity(found, iac)
745  end if
746  !
747  end subroutine source_connectivity
748 
749  !> @brief Write griddata found to list file
750  !<
751  subroutine log_connectivity(this, found, iac)
752  class(disutype) :: this
753  type(disufoundtype), intent(in) :: found
754  integer(I4B), dimension(:), contiguous, pointer, intent(in) :: iac
755  !
756  write (this%iout, '(1x,a)') 'Setting Discretization Connectivity'
757  !
758  if (associated(iac)) then
759  write (this%iout, '(4x,a)') 'IAC set from input file'
760  end if
761  !
762  if (found%ja) then
763  write (this%iout, '(4x,a)') 'JA set from input file'
764  end if
765  !
766  if (found%ihc) then
767  write (this%iout, '(4x,a)') 'IHC set from input file'
768  end if
769  !
770  if (found%cl12) then
771  write (this%iout, '(4x,a)') 'CL12 set from input file'
772  end if
773  !
774  if (found%hwva) then
775  write (this%iout, '(4x,a)') 'HWVA set from input file'
776  end if
777  !
778  if (found%angldegx) then
779  write (this%iout, '(4x,a)') 'ANGLDEGX set from input file'
780  end if
781  !
782  write (this%iout, '(1x,a,/)') 'End Setting Discretization Connectivity'
783  !
784  end subroutine log_connectivity
785 
786  !> @brief Copy grid vertex data from IDM into package
787  !<
788  subroutine source_vertices(this)
789  ! -- dummy
790  class(disutype) :: this
791  ! -- local
792  integer(I4B) :: i
793  real(DP), dimension(:), contiguous, pointer :: vert_x => null()
794  real(DP), dimension(:), contiguous, pointer :: vert_y => null()
795  ! -- formats
796  !
797  ! -- set pointers to memory manager input arrays
798  call mem_setptr(vert_x, 'XV', this%input_mempath)
799  call mem_setptr(vert_y, 'YV', this%input_mempath)
800  !
801  ! -- set vertices 2d array
802  if (associated(vert_x) .and. associated(vert_y)) then
803  do i = 1, this%nvert
804  this%vertices(1, i) = vert_x(i)
805  this%vertices(2, i) = vert_y(i)
806  end do
807  else
808  call store_error('Required Vertex arrays not found.')
809  end if
810  !
811  ! -- log
812  if (this%iout > 0) then
813  write (this%iout, '(1x,a)') 'Discretization Vertex data loaded'
814  end if
815  !
816  end subroutine source_vertices
817 
818  !> @brief Build data structures to hold cell vertex info
819  !<
820  subroutine define_cellverts(this, icell2d, ncvert, icvert)
821  ! -- modules
822  use sparsemodule, only: sparsematrix
823  ! -- dummy
824  class(disutype) :: this
825  integer(I4B), dimension(:), contiguous, pointer, intent(in) :: icell2d
826  integer(I4B), dimension(:), contiguous, pointer, intent(in) :: ncvert
827  integer(I4B), dimension(:), contiguous, pointer, intent(in) :: icvert
828  ! -- locals
829  type(sparsematrix) :: vert_spm
830  integer(I4B) :: i, j, ierr
831  integer(I4B) :: icv_idx, startvert, maxnnz = 5
832  !
833  ! -- initialize sparse matrix
834  call vert_spm%init(this%nodesuser, this%nvert, maxnnz)
835  !
836  ! -- add sparse matrix connections from input memory paths
837  icv_idx = 1
838  do i = 1, this%nodesuser
839  if (icell2d(i) /= i) call store_error('ICELL2D input sequence violation.')
840  do j = 1, ncvert(i)
841  call vert_spm%addconnection(i, icvert(icv_idx), 0)
842  if (j == 1) then
843  startvert = icvert(icv_idx)
844  elseif (j == ncvert(i) .and. (icvert(icv_idx) /= startvert)) then
845  call vert_spm%addconnection(i, startvert, 0)
846  end if
847  icv_idx = icv_idx + 1
848  end do
849  end do
850  !
851  ! -- allocate and fill iavert and javert
852  call mem_allocate(this%iavert, this%nodesuser + 1, 'IAVERT', this%memoryPath)
853  call mem_allocate(this%javert, vert_spm%nnz, 'JAVERT', this%memoryPath)
854  call vert_spm%filliaja(this%iavert, this%javert, ierr)
855  call vert_spm%destroy()
856  !
857  end subroutine define_cellverts
858 
859  !> @brief Copy cell2d data from IDM into package
860  !<
861  subroutine source_cell2d(this)
862  ! -- dummy
863  class(disutype) :: this
864  ! -- locals
865  integer(I4B), dimension(:), contiguous, pointer :: icell2d => null()
866  integer(I4B), dimension(:), contiguous, pointer :: ncvert => null()
867  integer(I4B), dimension(:), contiguous, pointer :: icvert => null()
868  real(DP), dimension(:), contiguous, pointer :: cell_x => null()
869  real(DP), dimension(:), contiguous, pointer :: cell_y => null()
870  integer(I4B) :: i
871  !
872  ! -- set pointers to input path ncvert and icvert
873  call mem_setptr(icell2d, 'ICELL2D', this%input_mempath)
874  call mem_setptr(ncvert, 'NCVERT', this%input_mempath)
875  call mem_setptr(icvert, 'ICVERT', this%input_mempath)
876  !
877  ! --
878  if (associated(icell2d) .and. associated(ncvert) &
879  .and. associated(icvert)) then
880  call this%define_cellverts(icell2d, ncvert, icvert)
881  else
882  call store_error('Required cell vertex arrays not found.')
883  end if
884  !
885  ! -- set pointers to cell center arrays
886  call mem_setptr(cell_x, 'XC', this%input_mempath)
887  call mem_setptr(cell_y, 'YC', this%input_mempath)
888  !
889  ! -- set cell centers
890  if (associated(cell_x) .and. associated(cell_y)) then
891  do i = 1, this%nodesuser
892  this%cellxy(1, i) = cell_x(i)
893  this%cellxy(2, i) = cell_y(i)
894  end do
895  else
896  call store_error('Required cell center arrays not found.')
897  end if
898  !
899  ! -- log
900  if (this%iout > 0) then
901  write (this%iout, '(1x,a)') 'Discretization Cell2d data loaded'
902  end if
903  !
904  end subroutine source_cell2d
905 
906  !> @brief Write a binary grid file
907  !<
908  subroutine write_grb(this, icelltype)
909  ! -- modules
910  use openspecmodule, only: access, form
911  use constantsmodule, only: lenbigline
912  ! -- dummy
913  class(disutype) :: this
914  integer(I4B), dimension(:), intent(in) :: icelltype
915  ! -- local
916  integer(I4B) :: i, iunit, ntxt, version
917  integer(I4B), parameter :: lentxt = 100
918  character(len=50) :: txthdr
919  character(len=lentxt) :: txt
920  character(len=LINELENGTH) :: fname
921  character(len=LENBIGLINE) :: crs
922  logical(LGP) :: found_crs
923  ! -- formats
924  character(len=*), parameter :: fmtgrdsave = &
925  "(4X,'BINARY GRID INFORMATION WILL BE WRITTEN TO:', &
926  &/,6X,'UNIT NUMBER: ', I0,/,6X, 'FILE NAME: ', A)"
927  !
928  ! -- Initialize
929  version = 1
930  ntxt = 11
931  if (this%nvert > 0) ntxt = ntxt + 5
932  !
933  call mem_set_value(crs, 'CRS', this%input_mempath, found_crs)
934  !
935  ! -- set version
936  if (found_crs) then
937  ntxt = ntxt + 1
938  version = 2
939  end if
940  !
941  ! -- Open the file
942  fname = trim(this%output_fname)
943  iunit = getunit()
944  write (this%iout, fmtgrdsave) iunit, trim(adjustl(fname))
945  call openfile(iunit, this%iout, trim(adjustl(fname)), 'DATA(BINARY)', &
946  form, access, 'REPLACE')
947  !
948  ! -- write header information
949  write (txthdr, '(a)') 'GRID DISU'
950  txthdr(50:50) = new_line('a')
951  write (iunit) txthdr
952  write (txthdr, '(a)') 'VERSION 1'
953  txthdr(50:50) = new_line('a')
954  write (iunit) txthdr
955  write (txthdr, '(a, i0)') 'NTXT ', ntxt
956  txthdr(50:50) = new_line('a')
957  write (iunit) txthdr
958  write (txthdr, '(a, i0)') 'LENTXT ', lentxt
959  txthdr(50:50) = new_line('a')
960  write (iunit) txthdr
961  !
962  ! -- write variable definitions
963  write (txt, '(3a, i0)') 'NODES ', 'INTEGER ', 'NDIM 0 # ', this%nodesuser
964  txt(lentxt:lentxt) = new_line('a')
965  write (iunit) txt
966  write (txt, '(3a, i0)') 'NJA ', 'INTEGER ', 'NDIM 0 # ', this%con%nja
967  txt(lentxt:lentxt) = new_line('a')
968  write (iunit) txt
969  write (txt, '(3a, 1pg24.15)') 'XORIGIN ', 'DOUBLE ', 'NDIM 0 # ', this%xorigin
970  txt(lentxt:lentxt) = new_line('a')
971  write (iunit) txt
972  write (txt, '(3a, 1pg24.15)') 'YORIGIN ', 'DOUBLE ', 'NDIM 0 # ', this%yorigin
973  txt(lentxt:lentxt) = new_line('a')
974  write (iunit) txt
975  write (txt, '(3a, 1pg24.15)') 'ANGROT ', 'DOUBLE ', 'NDIM 0 # ', this%angrot
976  txt(lentxt:lentxt) = new_line('a')
977  write (iunit) txt
978  write (txt, '(3a, i0)') 'TOP ', 'DOUBLE ', 'NDIM 1 ', this%nodesuser
979  txt(lentxt:lentxt) = new_line('a')
980  write (iunit) txt
981  write (txt, '(3a, i0)') 'BOT ', 'DOUBLE ', 'NDIM 1 ', this%nodesuser
982  txt(lentxt:lentxt) = new_line('a')
983  write (iunit) txt
984  write (txt, '(3a, i0)') 'IA ', 'INTEGER ', 'NDIM 1 ', this%nodesuser + 1
985  txt(lentxt:lentxt) = new_line('a')
986  write (iunit) txt
987  write (txt, '(3a, i0)') 'JA ', 'INTEGER ', 'NDIM 1 ', this%con%nja
988  txt(lentxt:lentxt) = new_line('a')
989  write (iunit) txt
990  write (txt, '(3a, i0)') 'IDOMAIN ', 'INTEGER ', 'NDIM 1 ', this%nodesuser
991  txt(lentxt:lentxt) = new_line('a')
992  write (iunit) txt
993  write (txt, '(3a, i0)') 'ICELLTYPE ', 'INTEGER ', 'NDIM 1 ', this%nodesuser
994  txt(lentxt:lentxt) = new_line('a')
995  write (iunit) txt
996  !
997  ! -- if vertices have been read then write additional header information
998  if (this%nvert > 0) then
999  write (txt, '(3a, i0)') 'VERTICES ', 'DOUBLE ', 'NDIM 2 2 ', this%nvert
1000  txt(lentxt:lentxt) = new_line('a')
1001  write (iunit) txt
1002  write (txt, '(3a, i0)') 'CELLX ', 'DOUBLE ', 'NDIM 1 ', this%nodesuser
1003  txt(lentxt:lentxt) = new_line('a')
1004  write (iunit) txt
1005  write (txt, '(3a, i0)') 'CELLY ', 'DOUBLE ', 'NDIM 1 ', this%nodesuser
1006  txt(lentxt:lentxt) = new_line('a')
1007  write (iunit) txt
1008  write (txt, '(3a, i0)') 'IAVERT ', 'INTEGER ', 'NDIM 1 ', this%nodesuser + 1
1009  txt(lentxt:lentxt) = new_line('a')
1010  write (iunit) txt
1011  write (txt, '(3a, i0)') 'JAVERT ', 'INTEGER ', 'NDIM 1 ', size(this%javert)
1012  txt(lentxt:lentxt) = new_line('a')
1013  write (iunit) txt
1014  end if
1015  !
1016  ! -- if version 2 write character array headers
1017  if (version == 2) then
1018  if (found_crs) then
1019  write (txt, '(3a, i0)') 'CRS ', 'CHARACTER ', 'NDIM 1 ', &
1020  len_trim(crs)
1021  txt(lentxt:lentxt) = new_line('a')
1022  write (iunit) txt
1023  end if
1024  end if
1025  !
1026  ! -- write data
1027  write (iunit) this%nodesuser ! nodes
1028  write (iunit) this%nja ! nja
1029  write (iunit) this%xorigin ! xorigin
1030  write (iunit) this%yorigin ! yorigin
1031  write (iunit) this%angrot ! angrot
1032  write (iunit) this%top1d ! top
1033  write (iunit) this%bot1d ! bot
1034  write (iunit) this%con%iausr ! ia
1035  write (iunit) this%con%jausr ! ja
1036  write (iunit) this%idomain ! idomain
1037  write (iunit) icelltype ! icelltype
1038  !
1039  ! -- if vertices have been read then write additional data
1040  if (this%nvert > 0) then
1041  write (iunit) this%vertices ! vertices
1042  write (iunit) (this%cellxy(1, i), i=1, this%nodesuser) ! cellx
1043  write (iunit) (this%cellxy(2, i), i=1, this%nodesuser) ! celly
1044  write (iunit) this%iavert ! iavert
1045  write (iunit) this%javert ! javert
1046  end if
1047  !
1048  ! -- if version 2 write character array data
1049  if (version == 2) then
1050  if (found_crs) write (iunit) trim(crs) ! crs user input
1051  end if
1052  !
1053  ! -- Close the file
1054  close (iunit)
1055  !
1056  end subroutine write_grb
1057 
1058  !> @brief Get reduced node number from user node number
1059  !<
1060  function get_nodenumber_idx1(this, nodeu, icheck) result(nodenumber)
1061  class(disutype), intent(in) :: this
1062  integer(I4B), intent(in) :: nodeu
1063  integer(I4B), intent(in) :: icheck
1064  integer(I4B) :: nodenumber
1065  !
1066  if (icheck /= 0) then
1067  if (nodeu < 1 .or. nodeu > this%nodes) then
1068  write (errmsg, '(a,i0,a,i0,a)') &
1069  'Node number (', nodeu, ') is less than 1 or greater than nodes (', &
1070  this%nodes, ').'
1071  call store_error(errmsg)
1072  end if
1073  end if
1074  !
1075  ! -- set node number to passed in nodenumber since there is a one to one
1076  ! mapping for an unstructured grid
1077  if (this%nodes == this%nodesuser) then
1078  nodenumber = nodeu
1079  else
1080  nodenumber = this%nodereduced(nodeu)
1081  end if
1082  !
1083  end function get_nodenumber_idx1
1084 
1085  !> @brief Get normal vector components between the cell and a given neighbor
1086  !!
1087  !! The normal points outward from the shared face between noden and nodem.
1088  !<
1089  subroutine connection_normal(this, noden, nodem, ihc, xcomp, ycomp, zcomp, &
1090  ipos)
1091  ! -- dummy
1092  class(disutype) :: this
1093  integer(I4B), intent(in) :: noden !< cell (reduced nn)
1094  integer(I4B), intent(in) :: nodem !< neighbor (reduced nn)
1095  integer(I4B), intent(in) :: ihc !< horizontal connection flag
1096  real(DP), intent(inout) :: xcomp
1097  real(DP), intent(inout) :: ycomp
1098  real(DP), intent(inout) :: zcomp
1099  integer(I4B), intent(in) :: ipos
1100  ! -- local
1101  real(DP) :: angle, dmult
1102  !
1103  ! -- Set vector components based on ihc
1104  if (ihc == 0) then
1105  !
1106  ! -- connection is vertical
1107  xcomp = dzero
1108  ycomp = dzero
1109  if (nodem < noden) then
1110  !
1111  ! -- nodem must be above noden, so upward connection
1112  zcomp = done
1113  else
1114  !
1115  ! -- nodem must be below noden, so downward connection
1116  zcomp = -done
1117  end if
1118  else
1119  ! -- find from anglex, since anglex is symmetric, need to flip vector
1120  ! for lower triangle (nodem < noden)
1121  angle = this%con%anglex(this%con%jas(ipos))
1122  dmult = done
1123  if (nodem < noden) dmult = -done
1124  xcomp = cos(angle) * dmult
1125  ycomp = sin(angle) * dmult
1126  zcomp = dzero
1127  end if
1128  !
1129  end subroutine connection_normal
1130 
1131  !> @brief Get unit vector components between the cell and a given neighbor
1132  !!
1133  !! Saturation must be provided to compute cell center vertical coordinates.
1134  !! Also return the straight-line connection length.
1135  !<
1136  subroutine connection_vector(this, noden, nodem, nozee, satn, satm, ihc, &
1137  xcomp, ycomp, zcomp, conlen)
1138  ! -- dummy
1139  class(disutype) :: this
1140  integer(I4B), intent(in) :: noden
1141  integer(I4B), intent(in) :: nodem
1142  logical, intent(in) :: nozee
1143  real(DP), intent(in) :: satn
1144  real(DP), intent(in) :: satm
1145  integer(I4B), intent(in) :: ihc
1146  real(DP), intent(inout) :: xcomp
1147  real(DP), intent(inout) :: ycomp
1148  real(DP), intent(inout) :: zcomp
1149  real(DP), intent(inout) :: conlen
1150  ! -- local
1151  real(DP) :: xn, xm, yn, ym, zn, zm
1152  !
1153  ! -- Terminate with error if requesting unit vector components for problems
1154  ! without cell data
1155  if (size(this%cellxy, 2) < 1) then
1156  write (errmsg, '(a)') &
1157  'Cannot calculate unit vector components for DISU grid if VERTEX '// &
1158  'data are not specified'
1159  call store_error(errmsg, terminate=.true.)
1160  end if
1161  !
1162  ! -- get xy center coords
1163  xn = this%xc(noden)
1164  yn = this%yc(noden)
1165  xm = this%xc(nodem)
1166  ym = this%yc(nodem)
1167  !
1168  ! -- Set vector components based on ihc
1169  if (ihc == 0) then
1170  !
1171  ! -- vertical connection, calculate z as cell center elevation
1172  zn = this%bot(noden) + dhalf * (this%top(noden) - this%bot(noden))
1173  zm = this%bot(nodem) + dhalf * (this%top(nodem) - this%bot(nodem))
1174  else
1175  !
1176  ! -- horizontal connection, with possible z component due to cell offsets
1177  ! and/or water table conditions
1178  if (nozee) then
1179  zn = dzero
1180  zm = dzero
1181  else
1182  zn = this%bot(noden) + dhalf * satn * (this%top(noden) - this%bot(noden))
1183  zm = this%bot(nodem) + dhalf * satm * (this%top(nodem) - this%bot(nodem))
1184  end if
1185  end if
1186  !
1187  ! -- Use coords to find vector components and connection length
1188  call line_unit_vector(xn, yn, zn, xm, ym, zm, xcomp, ycomp, zcomp, &
1189  conlen)
1190  !
1191  end subroutine connection_vector
1192 
1193  !> @brief Get the discretization type
1194  !<
1195  subroutine get_dis_type(this, dis_type)
1196  ! -- dummy
1197  class(disutype), intent(in) :: this
1198  character(len=*), intent(out) :: dis_type
1199  !
1200  dis_type = "DISU"
1201  !
1202  end subroutine get_dis_type
1203 
1204  !> @brief Get the discretization type enumeration
1205  function get_dis_enum(this) result(dis_enum)
1206  use constantsmodule, only: disu
1207  class(disutype), intent(in) :: this
1208  integer(I4B) :: dis_enum
1209  dis_enum = disu
1210  end function get_dis_enum
1211 
1212  !> @brief Allocate and initialize scalar variables
1213  !<
1214  subroutine allocate_scalars(this, name_model, input_mempath)
1215  ! -- dummy
1216  class(disutype) :: this
1217  character(len=*), intent(in) :: name_model
1218  character(len=*), intent(in) :: input_mempath
1219  !
1220  ! -- Allocate parent scalars
1221  call this%DisBaseType%allocate_scalars(name_model, input_mempath)
1222  !
1223  ! -- Allocate variables for DISU
1224  call mem_allocate(this%njausr, 'NJAUSR', this%memoryPath)
1225  call mem_allocate(this%nvert, 'NVERT', this%memoryPath)
1226  call mem_allocate(this%voffsettol, 'VOFFSETTOL', this%memoryPath)
1227  call mem_allocate(this%iangledegx, 'IANGLEDEGX', this%memoryPath)
1228  !
1229  ! -- Set values
1230  this%ndim = 1
1231  this%njausr = 0
1232  this%nvert = 0
1233  this%voffsettol = dzero
1234  this%iangledegx = 0
1235  this%readFromFile = .false.
1236  !
1237  end subroutine allocate_scalars
1238 
1239  !> @brief Allocate and initialize arrays
1240  !<
1241  subroutine allocate_arrays(this)
1242  ! -- dummy
1243  class(disutype) :: this
1244  !
1245  ! -- Allocate arrays in DisBaseType (mshape, top, bot, area)
1246  call this%DisBaseType%allocate_arrays()
1247  !
1248  ! -- Allocate arrays in DISU
1249  if (this%nodes < this%nodesuser) then
1250  call mem_allocate(this%nodeuser, this%nodes, 'NODEUSER', this%memoryPath)
1251  call mem_allocate(this%nodereduced, this%nodesuser, 'NODEREDUCED', &
1252  this%memoryPath)
1253  else
1254  call mem_allocate(this%nodeuser, 1, 'NODEUSER', this%memoryPath)
1255  call mem_allocate(this%nodereduced, 1, 'NODEREDUCED', this%memoryPath)
1256  end if
1257  !
1258  ! -- Initialize
1259  this%mshape(1) = this%nodesuser
1260  !
1261  end subroutine allocate_arrays
1262 
1263  !> @brief Allocate arrays in memory manager
1264  !<
1265  subroutine allocate_arrays_mem(this)
1266  ! -- modules
1268  ! -- dummy
1269  class(disutype) :: this
1270  !
1271  call mem_allocate(this%idomain, this%nodes, 'IDOMAIN', this%memoryPath)
1272  call mem_allocate(this%vertices, 2, this%nvert, 'VERTICES', this%memoryPath)
1273  call mem_allocate(this%cellxy, 2, this%nodes, 'CELLXY', this%memoryPath)
1274  !
1275  end subroutine allocate_arrays_mem
1276 
1277  !> @brief Convert a string to a user nodenumber
1278  !!
1279  !! Parse and return user nodenumber.
1280  !! If flag_string is present and true, the first token may be
1281  !! non-numeric (e.g. boundary name). In this case, return -2.
1282  !<
1283  function nodeu_from_string(this, lloc, istart, istop, in, iout, line, &
1284  flag_string, allow_zero) result(nodeu)
1285  ! -- dummy
1286  class(disutype) :: this
1287  integer(I4B), intent(inout) :: lloc
1288  integer(I4B), intent(inout) :: istart
1289  integer(I4B), intent(inout) :: istop
1290  integer(I4B), intent(in) :: in
1291  integer(I4B), intent(in) :: iout
1292  character(len=*), intent(inout) :: line
1293  logical, optional, intent(in) :: flag_string
1294  logical, optional, intent(in) :: allow_zero
1295  integer(I4B) :: nodeu
1296  ! -- local
1297  integer(I4B) :: lloclocal, ndum, istat, n
1298  real(dp) :: r
1299  !
1300  if (present(flag_string)) then
1301  if (flag_string) then
1302  ! Check to see if first token in line can be read as an integer.
1303  lloclocal = lloc
1304  call urword(line, lloclocal, istart, istop, 1, ndum, r, iout, in)
1305  read (line(istart:istop), *, iostat=istat) n
1306  if (istat /= 0) then
1307  ! First token in line is not an integer; return flag to this effect.
1308  nodeu = -2
1309  return
1310  end if
1311  end if
1312  end if
1313  !
1314  call urword(line, lloc, istart, istop, 2, nodeu, r, iout, in)
1315  !
1316  if (nodeu == 0) then
1317  if (present(allow_zero)) then
1318  if (allow_zero) then
1319  return
1320  end if
1321  end if
1322  end if
1323  !
1324  if (nodeu < 1 .or. nodeu > this%nodesuser) then
1325  write (errmsg, '(a,i0,a)') &
1326  "Node number in list (", nodeu, ") is outside of the grid. "// &
1327  "Cell number cannot be determined in line '"// &
1328  trim(adjustl(line))//"'."
1329  call store_error(errmsg)
1330  call store_error_unit(in)
1331  end if
1332  !
1333  end function nodeu_from_string
1334 
1335  !> @brief Convert a cellid string to a user nodenumber
1336  !!
1337  !! If flag_string is present and true, the first token may be
1338  !! non-numeric (e.g. boundary name). In this case, return -2.
1339  !!
1340  !! If allow_zero is present and true, and all indices are zero, the
1341  !! result can be zero. If allow_zero is false, a zero in any index is an error.
1342  !<
1343  function nodeu_from_cellid(this, cellid, inunit, iout, flag_string, &
1344  allow_zero) result(nodeu)
1345  ! -- return
1346  integer(I4B) :: nodeu
1347  ! -- dummy
1348  class(disutype) :: this
1349  character(len=*), intent(inout) :: cellid
1350  integer(I4B), intent(in) :: inunit
1351  integer(I4B), intent(in) :: iout
1352  logical, optional, intent(in) :: flag_string
1353  logical, optional, intent(in) :: allow_zero
1354  ! -- local
1355  integer(I4B) :: lloclocal, istart, istop, ndum, n
1356  integer(I4B) :: istat
1357  real(dp) :: r
1358  !
1359  if (present(flag_string)) then
1360  if (flag_string) then
1361  ! Check to see if first token in cellid can be read as an integer.
1362  lloclocal = 1
1363  call urword(cellid, lloclocal, istart, istop, 1, ndum, r, iout, inunit)
1364  read (cellid(istart:istop), *, iostat=istat) n
1365  if (istat /= 0) then
1366  ! First token in cellid is not an integer; return flag to this effect.
1367  nodeu = -2
1368  return
1369  end if
1370  end if
1371  end if
1372  !
1373  lloclocal = 1
1374  call urword(cellid, lloclocal, istart, istop, 2, nodeu, r, iout, inunit)
1375  !
1376  if (nodeu == 0) then
1377  if (present(allow_zero)) then
1378  if (allow_zero) then
1379  return
1380  end if
1381  end if
1382  end if
1383  !
1384  if (nodeu < 1 .or. nodeu > this%nodesuser) then
1385  write (errmsg, '(a,i0,a)') &
1386  "Cell number cannot be determined for cellid ("// &
1387  trim(adjustl(cellid))//") and results in a user "// &
1388  "node number (", nodeu, ") that is outside of the grid."
1389  call store_error(errmsg)
1390  call store_error_unit(inunit)
1391  end if
1392  !
1393  end function nodeu_from_cellid
1394 
1395  !> @brief Indicates whether the grid discretization supports layers
1396  !<
1397  logical function supports_layers(this)
1398  ! -- dummy
1399  class(disutype) :: this
1400  !
1401  supports_layers = .false.
1402  !
1403  end function supports_layers
1404 
1405  !> @brief Get number of cells per layer (total nodes since DISU isn't layered)
1406  !<
1407  function get_ncpl(this)
1408  ! -- return
1409  integer(I4B) :: get_ncpl
1410  ! -- dummy
1411  class(disutype) :: this
1412  !
1413  get_ncpl = this%nodesuser
1414  !
1415  end function get_ncpl
1416 
1417  !> @brief Read an integer array
1418  !<
1419  subroutine read_int_array(this, line, lloc, istart, istop, iout, in, &
1420  iarray, aname)
1421  ! -- dummy
1422  class(disutype), intent(inout) :: this
1423  character(len=*), intent(inout) :: line
1424  integer(I4B), intent(inout) :: lloc
1425  integer(I4B), intent(inout) :: istart
1426  integer(I4B), intent(inout) :: istop
1427  integer(I4B), intent(in) :: in
1428  integer(I4B), intent(in) :: iout
1429  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: iarray
1430  character(len=*), intent(in) :: aname
1431  ! -- local
1432  integer(I4B) :: nval
1433  integer(I4B), dimension(:), pointer, contiguous :: itemp
1434  !
1435  ! -- Point the temporary pointer array, which is passed to the reading
1436  ! subroutine. The temporary array will point to ibuff if it is a
1437  ! reduced structured system, or to iarray if it is an unstructured
1438  ! model.
1439  if (this%nodes < this%nodesuser) then
1440  nval = this%nodesuser
1441  itemp => this%ibuff
1442  else
1443  nval = this%nodes
1444  itemp => iarray
1445  end if
1446  !
1447  ! -- Read the array
1448  ! -- Read unstructured input
1449  call readarray(in, itemp, aname, this%ndim, nval, iout, 0)
1450  !
1451  ! -- If reduced model, then need to copy from itemp(=>ibuff) to iarray
1452  if (this%nodes < this%nodesuser) then
1453  call this%fill_grid_array(itemp, iarray)
1454  end if
1455  !
1456  end subroutine read_int_array
1457 
1458  !> @brief Read a double precision array
1459  !<
1460  subroutine read_dbl_array(this, line, lloc, istart, istop, iout, in, &
1461  darray, aname)
1462  ! -- dummy
1463  class(disutype), intent(inout) :: this
1464  character(len=*), intent(inout) :: line
1465  integer(I4B), intent(inout) :: lloc
1466  integer(I4B), intent(inout) :: istart
1467  integer(I4B), intent(inout) :: istop
1468  integer(I4B), intent(in) :: in
1469  integer(I4B), intent(in) :: iout
1470  real(DP), dimension(:), pointer, contiguous, intent(inout) :: darray
1471  character(len=*), intent(in) :: aname
1472  ! -- local
1473  integer(I4B) :: nval
1474  real(DP), dimension(:), pointer, contiguous :: dtemp
1475  !
1476  ! -- Point the temporary pointer array, which is passed to the reading
1477  ! subroutine. The temporary array will point to dbuff if it is a
1478  ! reduced structured system, or to darray if it is an unstructured
1479  ! model.
1480  if (this%nodes < this%nodesuser) then
1481  nval = this%nodesuser
1482  dtemp => this%dbuff
1483  else
1484  nval = this%nodes
1485  dtemp => darray
1486  end if
1487  !
1488  ! -- Read the array
1489  call readarray(in, dtemp, aname, this%ndim, nval, iout, 0)
1490  !
1491  ! -- If reduced model, then need to copy from dtemp(=>dbuff) to darray
1492  if (this%nodes < this%nodesuser) then
1493  call this%fill_grid_array(dtemp, darray)
1494  end if
1495  !
1496  end subroutine read_dbl_array
1497 
1498  !> @brief Record a double precision array
1499  !!
1500  !! The array is written to a formatted or unformatted external file
1501  !! depending on the arguments.
1502  !<
1503  subroutine record_array(this, darray, iout, iprint, idataun, aname, &
1504  cdatafmp, nvaluesp, nwidthp, editdesc, dinact)
1505  ! -- dummy
1506  class(disutype), intent(inout) :: this
1507  real(DP), dimension(:), pointer, contiguous, intent(inout) :: darray !< double precision array to record
1508  integer(I4B), intent(in) :: iout !< ascii output unit number
1509  integer(I4B), intent(in) :: iprint !< whether to print the array
1510  integer(I4B), intent(in) :: idataun !< binary output unit number
1511  character(len=*), intent(in) :: aname !< text descriptor
1512  character(len=*), intent(in) :: cdatafmp ! write format
1513  integer(I4B), intent(in) :: nvaluesp !< values per line
1514  integer(I4B), intent(in) :: nwidthp !< number width
1515  character(len=*), intent(in) :: editdesc !< format type (I, G, F, S, E)
1516  real(DP), intent(in) :: dinact !< double precision value for cells excluded from model domain
1517  ! -- local
1518  integer(I4B) :: k, ifirst
1519  integer(I4B) :: nlay
1520  integer(I4B) :: nrow
1521  integer(I4B) :: ncol
1522  integer(I4B) :: nval
1523  integer(I4B) :: nodeu, noder
1524  integer(I4B) :: istart, istop
1525  real(DP), dimension(:), pointer, contiguous :: dtemp
1526  ! -- formats
1527  character(len=*), parameter :: fmthsv = &
1528  "(1X,/1X,a,' WILL BE SAVED ON UNIT ',I4, &
1529  &' AT END OF TIME STEP',I5,', STRESS PERIOD ',I4)"
1530  !
1531  ! -- set variables
1532  nlay = 1
1533  nrow = 1
1534  ncol = this%mshape(1)
1535  !
1536  ! -- If this is a reduced model, then copy the values from darray into
1537  ! dtemp.
1538  if (this%nodes < this%nodesuser) then
1539  nval = this%nodes
1540  dtemp => this%dbuff
1541  do nodeu = 1, this%nodesuser
1542  noder = this%get_nodenumber(nodeu, 0)
1543  if (noder <= 0) then
1544  dtemp(nodeu) = dinact
1545  cycle
1546  end if
1547  dtemp(nodeu) = darray(noder)
1548  end do
1549  else
1550  nval = this%nodes
1551  dtemp => darray
1552  end if
1553  !
1554  ! -- Print to iout if iprint /= 0
1555  if (iprint /= 0) then
1556  istart = 1
1557  do k = 1, nlay
1558  istop = istart + nrow * ncol - 1
1559  call ulaprufw(ncol, nrow, kstp, kper, k, iout, dtemp(istart:istop), &
1560  aname, cdatafmp, nvaluesp, nwidthp, editdesc)
1561  istart = istop + 1
1562  end do
1563  end if
1564  !
1565  ! -- Save array to an external file.
1566  if (idataun > 0) then
1567  ! -- write to binary file by layer
1568  ifirst = 1
1569  istart = 1
1570  do k = 1, nlay
1571  istop = istart + nrow * ncol - 1
1572  if (ifirst == 1) write (iout, fmthsv) &
1573  trim(adjustl(aname)), idataun, &
1574  kstp, kper
1575  ifirst = 0
1576  call ulasav(dtemp(istart:istop), aname, kstp, kper, &
1577  pertim, totim, ncol, nrow, k, idataun)
1578  istart = istop + 1
1579  end do
1580  elseif (idataun < 0) then
1581  !
1582  ! -- write entire array as one record
1583  call ubdsv1(kstp, kper, aname, -idataun, dtemp, ncol, nrow, nlay, &
1584  iout, delt, pertim, totim)
1585  end if
1586  !
1587  end subroutine record_array
1588 
1589  !> @brief Record list header for imeth=6
1590  !<
1591  subroutine record_srcdst_list_header(this, text, textmodel, textpackage, &
1592  dstmodel, dstpackage, naux, auxtxt, &
1593  ibdchn, nlist, iout)
1594  ! -- dummy
1595  class(disutype) :: this
1596  character(len=16), intent(in) :: text
1597  character(len=16), intent(in) :: textmodel
1598  character(len=16), intent(in) :: textpackage
1599  character(len=16), intent(in) :: dstmodel
1600  character(len=16), intent(in) :: dstpackage
1601  integer(I4B), intent(in) :: naux
1602  character(len=16), dimension(:), intent(in) :: auxtxt
1603  integer(I4B), intent(in) :: ibdchn
1604  integer(I4B), intent(in) :: nlist
1605  integer(I4B), intent(in) :: iout
1606  ! -- local
1607  integer(I4B) :: nlay, nrow, ncol
1608  !
1609  nlay = 1
1610  nrow = 1
1611  ncol = this%mshape(1)
1612  !
1613  ! -- Use ubdsv06 to write list header
1614  call ubdsv06(kstp, kper, text, textmodel, textpackage, dstmodel, dstpackage, &
1615  ibdchn, naux, auxtxt, ncol, nrow, nlay, &
1616  nlist, iout, delt, pertim, totim)
1617  !
1618  end subroutine record_srcdst_list_header
1619 
1620  !> @brief Cast base to DISU
1621  !<
1622  function castasdisutype(dis) result(disu)
1623  ! -- dummy
1624  class(*), pointer :: dis !< base pointer to DISU object
1625  ! -- return
1626  class(disutype), pointer :: disu !< the resulting DISU pointer
1627  !
1628  disu => null()
1629  select type (dis)
1630  class is (disutype)
1631  disu => dis
1632  end select
1633  !
1634  end function castasdisutype
1635 
1636 end module disumodule
subroutine, public iac_to_ia(iac, ia)
Convert an iac array into an ia array.
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
@ disu
DISV6 discretization.
Definition: Constants.f90:157
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:68
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
subroutine allocate_scalars(this, name_model, input_mempath)
Allocate and initialize scalar variables.
Definition: Disu.f90:1215
subroutine write_grb(this, icelltype)
Write a binary grid file.
Definition: Disu.f90:909
subroutine allocate_arrays(this)
Allocate and initialize arrays.
Definition: Disu.f90:1242
subroutine disu_load(this)
Transfer IDM data into this discretization object.
Definition: Disu.f90:165
subroutine source_connectivity(this)
Copy grid connectivity info from IDM into package.
Definition: Disu.f90:718
subroutine, public disu_cr(dis, name_model, input_mempath, inunit, iout)
Create a new unstructured discretization object.
Definition: Disu.f90:127
subroutine source_dimensions(this)
Copy dimensions from IDM into package.
Definition: Disu.f90:583
subroutine source_options(this)
Copy options from IDM into package.
Definition: Disu.f90:516
subroutine log_dimensions(this, found)
Write dimensions to list file.
Definition: Disu.f90:644
subroutine disu_da(this)
Deallocate variables.
Definition: Disu.f90:432
class(disutype) function, pointer, public castasdisutype(dis)
Cast base to DISU.
Definition: Disu.f90:1623
integer(i4b) function get_ncpl(this)
Get number of cells per layer (total nodes since DISU isn't layered)
Definition: Disu.f90:1408
subroutine define_cellverts(this, icell2d, ncvert, icvert)
Build data structures to hold cell vertex info.
Definition: Disu.f90:821
subroutine read_dbl_array(this, line, lloc, istart, istop, iout, in, darray, aname)
Read a double precision array.
Definition: Disu.f90:1462
integer(i4b) function nodeu_from_cellid(this, cellid, inunit, iout, flag_string, allow_zero)
Convert a cellid string to a user nodenumber.
Definition: Disu.f90:1345
subroutine log_options(this, found)
Write user options to list file.
Definition: Disu.f90:543
subroutine record_srcdst_list_header(this, text, textmodel, textpackage, dstmodel, dstpackage, naux, auxtxt, ibdchn, nlist, iout)
Record list header for imeth=6.
Definition: Disu.f90:1594
subroutine get_dis_type(this, dis_type)
Get the discretization type.
Definition: Disu.f90:1196
subroutine source_vertices(this)
Copy grid vertex data from IDM into package.
Definition: Disu.f90:789
subroutine source_cell2d(this)
Copy cell2d data from IDM into package.
Definition: Disu.f90:862
subroutine log_griddata(this, found)
Write griddata found to list file.
Definition: Disu.f90:689
subroutine allocate_arrays_mem(this)
Allocate arrays in memory manager.
Definition: Disu.f90:1266
subroutine source_griddata(this)
Copy grid data from IDM into package.
Definition: Disu.f90:668
subroutine nodeu_to_array(this, nodeu, arr)
Convert a user nodenumber to an array (nodenumber)
Definition: Disu.f90:493
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.
Definition: Disu.f90:1138
subroutine record_array(this, darray, iout, iprint, idataun, aname, cdatafmp, nvaluesp, nwidthp, editdesc, dinact)
Record a double precision array.
Definition: Disu.f90:1505
subroutine disu_df(this)
Define the discretization.
Definition: Disu.f90:192
logical function supports_layers(this)
Indicates whether the grid discretization supports layers.
Definition: Disu.f90:1398
subroutine read_int_array(this, line, lloc, istart, istop, iout, in, iarray, aname)
Read an integer array.
Definition: Disu.f90:1421
subroutine grid_finalize(this)
Finalize the grid.
Definition: Disu.f90:202
integer(i4b) function get_nodenumber_idx1(this, nodeu, icheck)
Get reduced node number from user node number.
Definition: Disu.f90:1061
subroutine nodeu_to_string(this, nodeu, str)
Convert a user nodenumber to a string (nodenumber)
Definition: Disu.f90:478
integer(i4b) function nodeu_from_string(this, lloc, istart, istop, in, iout, line, flag_string, allow_zero)
Convert a string to a user nodenumber.
Definition: Disu.f90:1285
subroutine disu_ck(this)
Check discretization info.
Definition: Disu.f90:312
integer(i4b) function get_dis_enum(this)
Get the discretization type enumeration.
Definition: Disu.f90:1206
subroutine log_connectivity(this, found, iac)
Write griddata found to list file.
Definition: Disu.f90:752
subroutine connection_normal(this, noden, nodem, ihc, xcomp, ycomp, zcomp, ipos)
Get normal vector components between the cell and a given neighbor.
Definition: Disu.f90:1091
subroutine, public line_unit_vector(x0, y0, z0, x1, y1, z1, xcomp, ycomp, zcomp, vmag)
Calculate the vector components (xcomp, ycomp, and zcomp) for a line defined by two points,...
Definition: DisvGeom.f90:475
subroutine, public ubdsv1(kstp, kper, text, ibdchn, buff, ncol, nrow, nlay, iout, delt, pertim, totim)
Record cell-by-cell flow terms for one component of flow as a 3-D array with extra record to indicate...
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public ulaprufw(ncol, nrow, kstp, kper, ilay, iout, buf, text, userfmt, nvalues, nwidth, editdesc)
Print 1 layer array with user formatting in wrap format.
subroutine, public ubdsv06(kstp, kper, text, modelnam1, paknam1, modelnam2, paknam2, ibdchn, naux, auxtxt, ncol, nrow, nlay, nlist, iout, delt, pertim, totim)
Write header records for cell-by-cell flow terms for one component of flow.
subroutine, public ulasav(buf, text, kstp, kper, pertim, totim, ncol, nrow, ilay, ichn)
Save 1 layer array on disk.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
This module defines variable data types.
Definition: kind.f90:8
subroutine, public memorystore_remove(component, subcomponent, context)
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
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_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
character(len=linelength) idm_context
real(dp), pointer, public pertim
time relative to start of stress period
Definition: tdis.f90:30
real(dp), pointer, public totim
time relative to start of simulation
Definition: tdis.f90:32
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
real(dp), pointer, public delt
length of the current time step
Definition: tdis.f90:29
Unstructured grid discretization.
Definition: Disu.f90:28