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

This module contains the StructArrayModule. More...

Data Types

type  structarraytype
 type for structured array More...
 

Functions/Subroutines

type(structarraytype) function, pointer, public constructstructarray (mf6_input, ncol, nrow, blocknum, mempath, component_mempath)
 constructor for a struct_array More...
 
subroutine, public destructstructarray (struct_array)
 destructor for a struct_array More...
 
subroutine mem_create_vector (this, icol, idt)
 create new vector in StructArrayType More...
 
integer(i4b) function count (this)
 
subroutine set_pointer (sv, sv_target)
 
type(structvectortype) function, pointer get (this, idx)
 
subroutine allocate_int_type (this, sv)
 allocate integer input type More...
 
subroutine allocate_dbl_type (this, sv)
 allocate double input type More...
 
subroutine allocate_charstr_type (this, sv)
 allocate charstr input type More...
 
subroutine allocate_int1d_type (this, sv)
 allocate int1d input type More...
 
subroutine allocate_dbl1d_type (this, sv)
 allocate dbl1d input type More...
 
subroutine load_deferred_vector (this, icol)
 
subroutine memload_vectors (this)
 load deferred vectors into managed memory More...
 
subroutine log_structarray_vars (this, iout)
 log information about the StructArrayType More...
 
subroutine check_reallocate (this)
 reallocate local memory for deferred vectors if necessary More...
 
subroutine read_param (this, parser, sv_col, irow, timeseries, iout, auxcol)
 
integer(i4b) function read_from_parser (this, parser, timeseries, iout)
 read from the block parser to fill the StructArrayType More...
 
integer(i4b) function read_from_binary (this, inunit, iout)
 read from binary input to fill the StructArrayType More...
 

Detailed Description

This module contains the routines for reading a structured list, which consists of a separate vector for each column in the list.

Function/Subroutine Documentation

◆ allocate_charstr_type()

subroutine structarraymodule::allocate_charstr_type ( class(structarraytype this,
type(structvectortype), intent(inout)  sv 
)
private
Parameters
thisStructArrayType

Definition at line 253 of file StructArray.f90.

254  class(StructArrayType) :: this !< StructArrayType
255  type(StructVectorType), intent(inout) :: sv
256  type(CharacterStringType), dimension(:), pointer, contiguous :: charstr1d
257  integer(I4B) :: j
258 
259  if (this%deferred_shape) then
260  allocate (charstr1d(this%deferred_size_init))
261  else
262  call mem_allocate(charstr1d, linelength, this%nrow, &
263  sv%idt%mf6varname, this%mempath)
264  end if
265 
266  do j = 1, this%nrow
267  charstr1d(j) = ''
268  end do
269 
270  sv%memtype = 3
271  sv%charstr1d => charstr1d

◆ allocate_dbl1d_type()

subroutine structarraymodule::allocate_dbl1d_type ( class(structarraytype this,
type(structvectortype), intent(inout)  sv 
)
Parameters
thisStructArrayType

Definition at line 350 of file StructArray.f90.

351  use memorymanagermodule, only: get_isize
352  class(StructArrayType) :: this !< StructArrayType
353  type(StructVectorType), intent(inout) :: sv
354  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
355  integer(I4B), pointer :: naux, nseg, nseg_1
356  integer(I4B) :: nseg1_isize, n, m
357 
358  if (sv%idt%shape == 'NAUX') then
359  call mem_setptr(naux, sv%idt%shape, this%mempath)
360  call mem_allocate(dbl2d, naux, this%nrow, sv%idt%mf6varname, this%mempath)
361 
362  ! initialize
363  do m = 1, this%nrow
364  do n = 1, naux
365  dbl2d(n, m) = dzero
366  end do
367  end do
368 
369  sv%memtype = 6
370  sv%dbl2d => dbl2d
371  sv%intshape => naux
372  else if (sv%idt%shape == 'NSEG-1') then
373  call mem_setptr(nseg, 'NSEG', this%mempath)
374  call get_isize('NSEG_1', this%mempath, nseg1_isize)
375 
376  if (nseg1_isize < 0) then
377  call mem_allocate(nseg_1, 'NSEG_1', this%mempath)
378  nseg_1 = nseg - 1
379  else
380  call mem_setptr(nseg_1, 'NSEG_1', this%mempath)
381  end if
382 
383  ! allocate
384  call mem_allocate(dbl2d, nseg_1, this%nrow, sv%idt%mf6varname, this%mempath)
385 
386  ! initialize
387  do m = 1, this%nrow
388  do n = 1, nseg_1
389  dbl2d(n, m) = dzero
390  end do
391  end do
392 
393  sv%memtype = 6
394  sv%dbl2d => dbl2d
395  sv%intshape => nseg_1
396  else
397  errmsg = 'IDM unimplemented. StructArray::allocate_dbl1d_type &
398  & unsupported shape "'//trim(sv%idt%shape)//'".'
399  call store_error(errmsg, terminate=.true.)
400  end if
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
Here is the call graph for this function:

◆ allocate_dbl_type()

subroutine structarraymodule::allocate_dbl_type ( class(structarraytype this,
type(structvectortype), intent(inout)  sv 
)
private
Parameters
thisStructArrayType

Definition at line 226 of file StructArray.f90.

227  class(StructArrayType) :: this !< StructArrayType
228  type(StructVectorType), intent(inout) :: sv
229  real(DP), dimension(:), pointer, contiguous :: dbl1d
230  integer(I4B) :: j, nrow
231 
232  if (this%deferred_shape) then
233  ! shape not known, allocate locally
234  nrow = this%deferred_size_init
235  allocate (dbl1d(this%deferred_size_init))
236  else
237  ! shape known, allocate in managed memory
238  nrow = this%nrow
239  call mem_allocate(dbl1d, this%nrow, sv%idt%mf6varname, this%mempath)
240  end if
241 
242  ! initialize
243  do j = 1, nrow
244  dbl1d(j) = dzero
245  end do
246 
247  sv%memtype = 2
248  sv%dbl1d => dbl1d

◆ allocate_int1d_type()

subroutine structarraymodule::allocate_int1d_type ( class(structarraytype this,
type(structvectortype), intent(inout)  sv 
)
private
Parameters
thisStructArrayType

Definition at line 276 of file StructArray.f90.

277  use constantsmodule, only: lenmodelname
280  class(StructArrayType) :: this !< StructArrayType
281  type(StructVectorType), intent(inout) :: sv
282  integer(I4B), dimension(:, :), pointer, contiguous :: int2d
283  type(STLVecInt), pointer :: intvector
284  integer(I4B), pointer :: ncelldim, exgid
285  character(len=LENMEMPATH) :: input_mempath
286  character(len=LENMODELNAME) :: mname
287  type(CharacterStringType), dimension(:), contiguous, &
288  pointer :: charstr1d
289  integer(I4B) :: nrow, n, m
290 
291  if (sv%idt%shape == 'NCELLDIM') then
292  ! if EXCHANGE set to NCELLDIM of appropriate model
293  if (this%mf6_input%component_type == 'EXG') then
294  ! set pointer to EXGID
295  call mem_setptr(exgid, 'EXGID', this%mf6_input%mempath)
296  ! set pointer to appropriate exchange model array
297  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
298  if (sv%idt%tagname == 'CELLIDM1') then
299  call mem_setptr(charstr1d, 'EXGMNAMEA', input_mempath)
300  else if (sv%idt%tagname == 'CELLIDM2') then
301  call mem_setptr(charstr1d, 'EXGMNAMEB', input_mempath)
302  end if
303 
304  ! set the model name
305  mname = charstr1d(exgid)
306 
307  ! set ncelldim pointer
308  input_mempath = create_mem_path(component=mname, context=idm_context)
309  call mem_setptr(ncelldim, sv%idt%shape, input_mempath)
310  else
311  call mem_setptr(ncelldim, sv%idt%shape, this%component_mempath)
312  end if
313 
314  if (this%deferred_shape) then
315  ! shape not known, allocate locally
316  nrow = this%deferred_size_init
317  allocate (int2d(ncelldim, this%deferred_size_init))
318  else
319  ! shape known, allocate in managed memory
320  nrow = this%nrow
321  call mem_allocate(int2d, ncelldim, this%nrow, &
322  sv%idt%mf6varname, this%mempath)
323  end if
324 
325  ! initialize
326  do m = 1, nrow
327  do n = 1, ncelldim
328  int2d(n, m) = izero
329  end do
330  end do
331 
332  sv%memtype = 5
333  sv%int2d => int2d
334  sv%intshape => ncelldim
335  else
336  ! allocate intvector object
337  allocate (intvector)
338  ! initialize STLVecInt
339  call intvector%init()
340  sv%memtype = 4
341  sv%intvector => intvector
342  sv%size = -1
343  ! set pointer to dynamic shape
344  call mem_setptr(sv%intvector_shape, sv%idt%shape, this%mempath)
345  end if
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:22
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=linelength) idm_context
Here is the call graph for this function:

◆ allocate_int_type()

subroutine structarraymodule::allocate_int_type ( class(structarraytype this,
type(structvectortype), intent(inout)  sv 
)
private
Parameters
thisStructArrayType

Definition at line 199 of file StructArray.f90.

200  class(StructArrayType) :: this !< StructArrayType
201  type(StructVectorType), intent(inout) :: sv
202  integer(I4B), dimension(:), pointer, contiguous :: int1d
203  integer(I4B) :: j, nrow
204 
205  if (this%deferred_shape) then
206  ! shape not known, allocate locally
207  nrow = this%deferred_size_init
208  allocate (int1d(this%deferred_size_init))
209  else
210  ! shape known, allocate in managed memory
211  nrow = this%nrow
212  call mem_allocate(int1d, this%nrow, sv%idt%mf6varname, this%mempath)
213  end if
214 
215  ! initialize vector values
216  do j = 1, nrow
217  int1d(j) = izero
218  end do
219 
220  sv%memtype = 1
221  sv%int1d => int1d

◆ check_reallocate()

subroutine structarraymodule::check_reallocate ( class(structarraytype this)
private
Parameters
thisStructArrayType

Definition at line 669 of file StructArray.f90.

670  class(StructArrayType) :: this !< StructArrayType
671  integer(I4B) :: i, j, k, newsize
672  integer(I4B), dimension(:), pointer, contiguous :: p_int1d
673  integer(I4B), dimension(:, :), pointer, contiguous :: p_int2d
674  real(DP), dimension(:), pointer, contiguous :: p_dbl1d
675  type(CharacterStringType), dimension(:), pointer, contiguous :: p_charstr1d
676  integer(I4B) :: reallocate_mult
677 
678  ! set growth rate
679  reallocate_mult = 2
680 
681  do j = 1, this%ncol
682  ! reallocate based on memtype
683  select case (this%struct_vectors(j)%memtype)
684  case (1) ! memtype integer
685  ! check if more space needed
686  if (this%nrow > this%struct_vectors(j)%size) then
687  ! calculate new size
688  newsize = this%struct_vectors(j)%size * reallocate_mult
689  ! allocate new vector
690  allocate (p_int1d(newsize))
691 
692  ! copy from old to new
693  do i = 1, this%struct_vectors(j)%size
694  p_int1d(i) = this%struct_vectors(j)%int1d(i)
695  end do
696 
697  ! deallocate old vector
698  deallocate (this%struct_vectors(j)%int1d)
699 
700  ! update struct array object
701  this%struct_vectors(j)%int1d => p_int1d
702  this%struct_vectors(j)%size = newsize
703  end if
704  case (2) ! memtype real
705  if (this%nrow > this%struct_vectors(j)%size) then
706  newsize = this%struct_vectors(j)%size * reallocate_mult
707  allocate (p_dbl1d(newsize))
708 
709  do i = 1, this%struct_vectors(j)%size
710  p_dbl1d(i) = this%struct_vectors(j)%dbl1d(i)
711  end do
712 
713  deallocate (this%struct_vectors(j)%dbl1d)
714 
715  this%struct_vectors(j)%dbl1d => p_dbl1d
716  this%struct_vectors(j)%size = newsize
717  end if
718  !
719  case (3) ! memtype charstring
720  if (this%nrow > this%struct_vectors(j)%size) then
721  newsize = this%struct_vectors(j)%size * reallocate_mult
722  allocate (p_charstr1d(newsize))
723 
724  do i = 1, this%struct_vectors(j)%size
725  p_charstr1d(i) = this%struct_vectors(j)%charstr1d(i)
726  call this%struct_vectors(j)%charstr1d(i)%destroy()
727  end do
728 
729  deallocate (this%struct_vectors(j)%charstr1d)
730 
731  this%struct_vectors(j)%charstr1d => p_charstr1d
732  this%struct_vectors(j)%size = newsize
733  end if
734  case (5)
735  if (this%nrow > this%struct_vectors(j)%size) then
736  newsize = this%struct_vectors(j)%size * reallocate_mult
737  allocate (p_int2d(this%struct_vectors(j)%intshape, newsize))
738 
739  do i = 1, this%struct_vectors(j)%size
740  do k = 1, this%struct_vectors(j)%intshape
741  p_int2d(k, i) = this%struct_vectors(j)%int2d(k, i)
742  end do
743  end do
744 
745  deallocate (this%struct_vectors(j)%int2d)
746 
747  this%struct_vectors(j)%int2d => p_int2d
748  this%struct_vectors(j)%size = newsize
749  end if
750  ! TODO: case (6)
751  case default
752  errmsg = 'IDM unimplemented. StructArray::check_reallocate &
753  &unsupported memtype.'
754  call store_error(errmsg, terminate=.true.)
755  end select
756  end do
Here is the call graph for this function:

◆ constructstructarray()

type(structarraytype) function, pointer, public structarraymodule::constructstructarray ( type(modflowinputtype), intent(in)  mf6_input,
integer(i4b), intent(in)  ncol,
integer(i4b), intent(in)  nrow,
integer(i4b), intent(in)  blocknum,
character(len=*), intent(in)  mempath,
character(len=*), intent(in)  component_mempath 
)
Parameters
[in]ncolnumber of columns in the StructArrayType
[in]nrownumber of rows in the StructArrayType
[in]blocknumvalid block number or 0
[in]mempathmemory path for storing the vector
Returns
new StructArrayType

Definition at line 71 of file StructArray.f90.

73  type(ModflowInputType), intent(in) :: mf6_input
74  integer(I4B), intent(in) :: ncol !< number of columns in the StructArrayType
75  integer(I4B), intent(in) :: nrow !< number of rows in the StructArrayType
76  integer(I4B), intent(in) :: blocknum !< valid block number or 0
77  character(len=*), intent(in) :: mempath !< memory path for storing the vector
78  character(len=*), intent(in) :: component_mempath
79  type(StructArrayType), pointer :: struct_array !< new StructArrayType
80 
81  ! allocate StructArrayType
82  allocate (struct_array)
83 
84  ! set description of input
85  struct_array%mf6_input = mf6_input
86 
87  ! set number of arrays
88  struct_array%ncol = ncol
89 
90  ! set rows if known or set deferred
91  struct_array%nrow = nrow
92  if (struct_array%nrow == -1) then
93  struct_array%nrow = 0
94  struct_array%deferred_shape = .true.
95  end if
96 
97  ! set blocknum
98  if (blocknum > 0) then
99  struct_array%blocknum = blocknum
100  else
101  struct_array%blocknum = 0
102  end if
103 
104  ! set mempath
105  struct_array%mempath = mempath
106  struct_array%component_mempath = component_mempath
107 
108  ! allocate StructVectorType objects
109  allocate (struct_array%struct_vectors(ncol))
110  allocate (struct_array%startidx(ncol))
111  allocate (struct_array%numcols(ncol))
Here is the caller graph for this function:

◆ count()

integer(i4b) function structarraymodule::count ( class(structarraytype this)
private
Parameters
thisStructArrayType

Definition at line 178 of file StructArray.f90.

179  class(StructArrayType) :: this !< StructArrayType
180  integer(I4B) :: count
181  count = size(this%struct_vectors)

◆ destructstructarray()

subroutine, public structarraymodule::destructstructarray ( type(structarraytype), intent(inout), pointer  struct_array)
Parameters
[in,out]struct_arrayStructArrayType to destroy

Definition at line 116 of file StructArray.f90.

117  type(StructArrayType), pointer, intent(inout) :: struct_array !< StructArrayType to destroy
118  deallocate (struct_array%struct_vectors)
119  deallocate (struct_array%startidx)
120  deallocate (struct_array%numcols)
121  deallocate (struct_array)
122  nullify (struct_array)
Here is the caller graph for this function:

◆ get()

type(structvectortype) function, pointer structarraymodule::get ( class(structarraytype this,
integer(i4b), intent(in)  idx 
)
private
Parameters
thisStructArrayType

Definition at line 190 of file StructArray.f90.

191  class(StructArrayType) :: this !< StructArrayType
192  integer(I4B), intent(in) :: idx
193  type(StructVectorType), pointer :: sv
194  call set_pointer(sv, this%struct_vectors(idx))
Here is the call graph for this function:

◆ load_deferred_vector()

subroutine structarraymodule::load_deferred_vector ( class(structarraytype this,
integer(i4b), intent(in)  icol 
)
Parameters
thisStructArrayType

Definition at line 403 of file StructArray.f90.

404  use memorymanagermodule, only: get_isize
405  class(StructArrayType) :: this !< StructArrayType
406  integer(I4B), intent(in) :: icol
407  integer(I4B) :: i, j, isize
408  integer(I4B), dimension(:), pointer, contiguous :: p_int1d
409  integer(I4B), dimension(:, :), pointer, contiguous :: p_int2d
410  real(DP), dimension(:), pointer, contiguous :: p_dbl1d
411  type(CharacterStringType), dimension(:), pointer, contiguous :: p_charstr1d
412  character(len=LENVARNAME) :: varname
413  logical(LGP) :: overwrite
414 
415  overwrite = .true.
416  if (this%struct_vectors(icol)%idt%blockname == 'SOLUTIONGROUP') &
417  overwrite = .false.
418 
419  ! set varname
420  varname = this%struct_vectors(icol)%idt%mf6varname
421  ! check if already mem managed variable
422  call get_isize(varname, this%mempath, isize)
423 
424  ! allocate and load based on memtype
425  select case (this%struct_vectors(icol)%memtype)
426  case (1) ! memtype integer
427  if (isize > -1) then
428  ! variable exists, reallocate and append
429  call mem_setptr(p_int1d, varname, this%mempath)
430 
431  if (overwrite) then
432  ! overwrite existing array
433  if (this%nrow > isize) then
434  ! reallocate
435  call mem_reallocate(p_int1d, this%nrow, varname, this%mempath)
436  end if
437 
438  ! write new data
439  do i = 1, this%nrow
440  p_int1d(i) = this%struct_vectors(icol)%int1d(i)
441  end do
442 
443  if (isize > this%nrow) then
444  ! initialize excess space
445  do i = this%nrow + 1, isize
446  p_int1d(i) = izero
447  end do
448  end if
449  else
450  ! reallocate to new size
451  call mem_reallocate(p_int1d, this%nrow + isize, varname, this%mempath)
452 
453  ! write new data after existing
454  do i = 1, this%nrow
455  p_int1d(isize + i) = this%struct_vectors(icol)%int1d(i)
456  end do
457  end if
458  else
459  ! allocate memory manager vector
460  call mem_allocate(p_int1d, this%nrow, varname, this%mempath)
461 
462  ! load local vector to managed memory
463  do i = 1, this%nrow
464  p_int1d(i) = this%struct_vectors(icol)%int1d(i)
465  end do
466  end if
467 
468  ! deallocate local memory
469  deallocate (this%struct_vectors(icol)%int1d)
470 
471  ! update structvector
472  this%struct_vectors(icol)%int1d => p_int1d
473  this%struct_vectors(icol)%size = this%nrow
474  case (2) ! memtype real
475  if (isize > -1) then
476  call mem_setptr(p_dbl1d, varname, this%mempath)
477 
478  if (overwrite) then
479  if (this%nrow > isize) then
480  call mem_reallocate(p_dbl1d, this%nrow, varname, this%mempath)
481  end if
482 
483  do i = 1, this%nrow
484  p_dbl1d(i) = this%struct_vectors(icol)%dbl1d(i)
485  end do
486 
487  if (isize > this%nrow) then
488  do i = this%nrow + 1, isize
489  p_dbl1d(i) = dzero
490  end do
491  end if
492  else
493  call mem_reallocate(p_dbl1d, this%nrow + isize, varname, &
494  this%mempath)
495  do i = 1, this%nrow
496  p_dbl1d(isize + i) = this%struct_vectors(icol)%dbl1d(i)
497  end do
498  end if
499  else
500  call mem_allocate(p_dbl1d, this%nrow, varname, this%mempath)
501 
502  do i = 1, this%nrow
503  p_dbl1d(i) = this%struct_vectors(icol)%dbl1d(i)
504  end do
505  end if
506 
507  deallocate (this%struct_vectors(icol)%dbl1d)
508 
509  this%struct_vectors(icol)%dbl1d => p_dbl1d
510  this%struct_vectors(icol)%size = this%nrow
511  !
512  case (3) ! memtype charstring
513  if (isize > -1) then
514  call mem_setptr(p_charstr1d, varname, this%mempath)
515 
516  if (overwrite) then
517  if (this%nrow > isize) then
518  call mem_reallocate(p_charstr1d, linelength, this%nrow, varname, &
519  this%mempath)
520  end if
521 
522  do i = 1, this%nrow
523  p_charstr1d(i) = this%struct_vectors(icol)%charstr1d(i)
524  end do
525 
526  if (isize > this%nrow) then
527  do i = this%nrow + 1, isize
528  p_charstr1d(i) = ''
529  end do
530  end if
531  else
532  call mem_reallocate(p_charstr1d, linelength, this%nrow + isize, &
533  varname, this%mempath)
534  do i = 1, this%nrow
535  p_charstr1d(isize + i) = this%struct_vectors(icol)%charstr1d(i)
536  end do
537  end if
538  else
539  call mem_allocate(p_charstr1d, linelength, this%nrow, varname, &
540  this%mempath)
541  do i = 1, this%nrow
542  p_charstr1d(i) = this%struct_vectors(icol)%charstr1d(i)
543  call this%struct_vectors(icol)%charstr1d(i)%destroy()
544  end do
545  end if
546 
547  deallocate (this%struct_vectors(icol)%charstr1d)
548 
549  this%struct_vectors(icol)%charstr1d => p_charstr1d
550  this%struct_vectors(icol)%size = this%nrow
551  case (4) ! memtype intvector
552  errmsg = 'StructArray::load_deferred_vector &
553  &intvector reallocate unimplemented.'
554  call store_error(errmsg, terminate=.true.)
555  case (5)
556  if (isize > -1) then
557  errmsg = 'StructArray::load_deferred_vector &
558  &int2d reallocate unimplemented.'
559  call store_error(errmsg, terminate=.true.)
560  else
561  call mem_allocate(p_int2d, this%struct_vectors(icol)%intshape, &
562  this%nrow, varname, this%mempath)
563  do i = 1, this%nrow
564  do j = 1, this%struct_vectors(icol)%intshape
565  p_int2d(j, i) = this%struct_vectors(icol)%int2d(j, i)
566  end do
567  end do
568  end if
569 
570  deallocate (this%struct_vectors(icol)%int2d)
571 
572  this%struct_vectors(icol)%int2d => p_int2d
573  this%struct_vectors(icol)%size = this%nrow
574  case (6)
575  errmsg = 'StructArray::load_deferred_vector &
576  &dbl2d reallocate unimplemented.'
577  call store_error(errmsg, terminate=.true.)
578  case default
579  end select
Here is the call graph for this function:

◆ log_structarray_vars()

subroutine structarraymodule::log_structarray_vars ( class(structarraytype this,
integer(i4b), intent(in)  iout 
)
private
Parameters
thisStructArrayType
[in]ioutunit number for output

Definition at line 622 of file StructArray.f90.

623  class(StructArrayType) :: this !< StructArrayType
624  integer(I4B), intent(in) :: iout !< unit number for output
625  integer(I4B) :: j
626  integer(I4B), dimension(:), pointer, contiguous :: int1d
627 
628  ! idm variable logging
629  do j = 1, this%ncol
630  ! log based on memtype
631  select case (this%struct_vectors(j)%memtype)
632  case (1) ! memtype integer
633  call idm_log_var(this%struct_vectors(j)%int1d, &
634  this%struct_vectors(j)%idt%tagname, &
635  this%mempath, iout)
636  case (2) ! memtype real
637  if (this%struct_vectors(j)%ts_strlocs%count() > 0) then
638  call idm_log_var(this%struct_vectors(j)%idt%tagname, &
639  this%mempath, iout, .false.)
640  else
641  call idm_log_var(this%struct_vectors(j)%dbl1d, &
642  this%struct_vectors(j)%idt%tagname, &
643  this%mempath, iout)
644  end if
645  case (4) ! memtype intvector
646  call mem_setptr(int1d, this%struct_vectors(j)%idt%mf6varname, &
647  this%mempath)
648  call idm_log_var(int1d, this%struct_vectors(j)%idt%tagname, &
649  this%mempath, iout)
650  case (5) ! memtype int2d
651  call idm_log_var(this%struct_vectors(j)%int2d, &
652  this%struct_vectors(j)%idt%tagname, &
653  this%mempath, iout)
654  case (6) ! memtype dbl2d
655  if (this%struct_vectors(j)%ts_strlocs%count() > 0) then
656  call idm_log_var(this%struct_vectors(j)%idt%tagname, &
657  this%mempath, iout, .false.)
658  else
659  call idm_log_var(this%struct_vectors(j)%dbl2d, &
660  this%struct_vectors(j)%idt%tagname, &
661  this%mempath, iout)
662  end if
663  end select
664  end do

◆ mem_create_vector()

subroutine structarraymodule::mem_create_vector ( class(structarraytype this,
integer(i4b), intent(in)  icol,
type(inputparamdefinitiontype), pointer  idt 
)
private
Parameters
thisStructArrayType
[in]icolcolumn to create

Definition at line 127 of file StructArray.f90.

128  class(StructArrayType) :: this !< StructArrayType
129  integer(I4B), intent(in) :: icol !< column to create
130  type(InputParamDefinitionType), pointer :: idt
131  type(StructVectorType) :: sv
132  integer(I4B) :: numcol
133 
134  ! initialize
135  numcol = 1
136  sv%idt => idt
137  sv%icol = icol
138 
139  ! set size
140  if (this%deferred_shape) then
141  sv%size = this%deferred_size_init
142  else
143  sv%size = this%nrow
144  end if
145 
146  ! allocate array memory for StructVectorType
147  select case (idt%datatype)
148  case ('INTEGER')
149  call this%allocate_int_type(sv)
150  case ('DOUBLE')
151  call this%allocate_dbl_type(sv)
152  case ('STRING', 'KEYWORD')
153  call this%allocate_charstr_type(sv)
154  case ('INTEGER1D')
155  call this%allocate_int1d_type(sv)
156  if (sv%memtype == 5) then
157  numcol = sv%intshape
158  end if
159  case ('DOUBLE1D')
160  call this%allocate_dbl1d_type(sv)
161  numcol = sv%intshape
162  case default
163  errmsg = 'IDM unimplemented. StructArray::mem_create_vector &
164  &type='//trim(idt%datatype)
165  call store_error(errmsg, .true.)
166  end select
167 
168  ! set the object in the Struct Array
169  this%struct_vectors(icol) = sv
170  this%numcols(icol) = numcol
171  if (icol == 1) then
172  this%startidx(icol) = 1
173  else
174  this%startidx(icol) = this%startidx(icol - 1) + this%numcols(icol - 1)
175  end if
Here is the call graph for this function:

◆ memload_vectors()

subroutine structarraymodule::memload_vectors ( class(structarraytype this)
Parameters
thisStructArrayType

Definition at line 584 of file StructArray.f90.

585  class(StructArrayType) :: this !< StructArrayType
586  integer(I4B) :: icol, j
587  integer(I4B), dimension(:), pointer, contiguous :: p_intvector
588  character(len=LENVARNAME) :: varname
589 
590  do icol = 1, this%ncol
591  ! set varname
592  varname = this%struct_vectors(icol)%idt%mf6varname
593 
594  if (this%struct_vectors(icol)%memtype == 4) then
595  ! intvectors always need to be loaded
596  ! size intvector to number of values read
597  call this%struct_vectors(icol)%intvector%shrink_to_fit()
598 
599  ! allocate memory manager vector
600  call mem_allocate(p_intvector, &
601  this%struct_vectors(icol)%intvector%size, &
602  varname, this%mempath)
603 
604  ! load local vector to managed memory
605  do j = 1, this%struct_vectors(icol)%intvector%size
606  p_intvector(j) = this%struct_vectors(icol)%intvector%at(j)
607  end do
608 
609  ! cleanup local memory
610  call this%struct_vectors(icol)%intvector%destroy()
611  deallocate (this%struct_vectors(icol)%intvector)
612  nullify (this%struct_vectors(icol)%intvector_shape)
613  else if (this%deferred_shape) then
614  ! load as shape wasn't known
615  call this%load_deferred_vector(icol)
616  end if
617  end do

◆ read_from_binary()

integer(i4b) function structarraymodule::read_from_binary ( class(structarraytype this,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout 
)
private
Parameters
thisStructArrayType
[in]inunitunit number for binary input
[in]ioutunit number for output

Definition at line 881 of file StructArray.f90.

882  class(StructArrayType) :: this !< StructArrayType
883  integer(I4B), intent(in) :: inunit !< unit number for binary input
884  integer(I4B), intent(in) :: iout !< unit number for output
885  integer(I4B) :: irow, ierr
886  integer(I4B) :: j, k
887  integer(I4B) :: intval, numval
888  character(len=LINELENGTH) :: fname
889  character(len=*), parameter :: fmtlsterronly = &
890  "('Error reading LIST from file: ',&
891  &1x,a,1x,' on UNIT: ',I0)"
892 
893  ! set error and exit if deferred shape
894  if (this%deferred_shape) then
895  errmsg = 'IDM unimplemented. StructArray::read_from_binary deferred shape &
896  &not supported for binary inputs.'
897  call store_error(errmsg, terminate=.true.)
898  end if
899  ! initialize
900  irow = 0
901  ierr = 0
902  readloop: do
903  ! update irow index
904  irow = irow + 1
905  ! handle line reads by column memtype
906  do j = 1, this%ncol
907  select case (this%struct_vectors(j)%memtype)
908  case (1) ! memtype integer
909  read (inunit, iostat=ierr) this%struct_vectors(j)%int1d(irow)
910  case (2) ! memtype real
911  read (inunit, iostat=ierr) this%struct_vectors(j)%dbl1d(irow)
912  case (3) ! memtype charstring
913  errmsg = 'List style binary inputs not supported &
914  &for text columns, tag='// &
915  trim(this%struct_vectors(j)%idt%tagname)//'.'
916  call store_error(errmsg, terminate=.true.)
917  case (4) ! memtype intvector
918  ! get shape for this row
919  numval = this%struct_vectors(j)%intvector_shape(irow)
920  ! read and store row values
921  do k = 1, numval
922  if (ierr == 0) then
923  read (inunit, iostat=ierr) intval
924  call this%struct_vectors(j)%intvector%push_back(intval)
925  end if
926  end do
927  case (5) ! memtype int2d
928  ! read and store row values
929  do k = 1, this%struct_vectors(j)%intshape
930  if (ierr == 0) then
931  read (inunit, iostat=ierr) this%struct_vectors(j)%int2d(k, irow)
932  end if
933  end do
934  case (6) ! memtype dbl2d
935  do k = 1, this%struct_vectors(j)%intshape
936  if (ierr == 0) then
937  read (inunit, iostat=ierr) this%struct_vectors(j)%dbl2d(k, irow)
938  end if
939  end do
940  end select
941 
942  ! handle error cases
943  select case (ierr)
944  case (0)
945  ! no error
946  case (:-1)
947  ! End of block was encountered
948  irow = irow - 1
949  exit readloop
950  case (1:)
951  ! Error
952  inquire (unit=inunit, name=fname)
953  write (errmsg, fmtlsterronly) trim(adjustl(fname)), inunit
954  call store_error(errmsg, terminate=.true.)
955  case default
956  end select
957  end do
958  if (irow == this%nrow) exit readloop
959  end do readloop
960 
961  ! Stop if errors were detected
962  !if (count_errors() > 0) then
963  ! call store_error_unit(inunit)
964  !end if
965 
966  ! if deferred shape vectors were read, load to input path
967  call this%memload_vectors()
968 
969  ! log loaded variables
970  if (iout > 0) then
971  call this%log_structarray_vars(iout)
972  end if
Here is the call graph for this function:

◆ read_from_parser()

integer(i4b) function structarraymodule::read_from_parser ( class(structarraytype this,
type(blockparsertype parser,
logical(lgp), intent(in)  timeseries,
integer(i4b), intent(in)  iout 
)
private
Parameters
thisStructArrayType
parserblock parser to read from
[in]ioutunit number for output

Definition at line 840 of file StructArray.f90.

841  class(StructArrayType) :: this !< StructArrayType
842  type(BlockParserType) :: parser !< block parser to read from
843  logical(LGP), intent(in) :: timeseries
844  integer(I4B), intent(in) :: iout !< unit number for output
845  integer(I4B) :: irow, j
846  logical(LGP) :: endOfBlock
847 
848  ! initialize index irow
849  irow = 0
850 
851  ! read entire block
852  do
853  ! read next line
854  call parser%GetNextLine(endofblock)
855  if (endofblock) then
856  ! no more lines
857  exit
858  else if (this%deferred_shape) then
859  ! shape unknown, track lines read
860  this%nrow = this%nrow + 1
861  ! check and update memory allocation
862  call this%check_reallocate()
863  end if
864  ! update irow index
865  irow = irow + 1
866  ! handle line reads by column memtype
867  do j = 1, this%ncol
868  call this%read_param(parser, j, irow, timeseries, iout)
869  end do
870  end do
871  ! if deferred shape vectors were read, load to input path
872  call this%memload_vectors()
873  ! log loaded variables
874  if (iout > 0) then
875  call this%log_structarray_vars(iout)
876  end if

◆ read_param()

subroutine structarraymodule::read_param ( class(structarraytype this,
type(blockparsertype), intent(inout)  parser,
integer(i4b), intent(in)  sv_col,
integer(i4b), intent(in)  irow,
logical(lgp), intent(in)  timeseries,
integer(i4b), intent(in)  iout,
integer(i4b), intent(in), optional  auxcol 
)
private
Parameters
thisStructArrayType
[in,out]parserblock parser to read from
[in]ioutunit number for output

Definition at line 759 of file StructArray.f90.

760  class(StructArrayType) :: this !< StructArrayType
761  type(BlockParserType), intent(inout) :: parser !< block parser to read from
762  integer(I4B), intent(in) :: sv_col
763  integer(I4B), intent(in) :: irow
764  logical(LGP), intent(in) :: timeseries
765  integer(I4B), intent(in) :: iout !< unit number for output
766  integer(I4B), optional, intent(in) :: auxcol
767  integer(I4B) :: n, intval, numval, icol
768  character(len=LINELENGTH) :: str
769  character(len=:), allocatable :: line
770  logical(LGP) :: preserve_case
771 
772  select case (this%struct_vectors(sv_col)%memtype)
773  case (1) ! memtype integer
774  ! if reloadable block and first col, store blocknum
775  if (sv_col == 1 .and. this%blocknum > 0) then
776  ! store blocknum
777  this%struct_vectors(sv_col)%int1d(irow) = this%blocknum
778  else
779  ! read and store int
780  this%struct_vectors(sv_col)%int1d(irow) = parser%GetInteger()
781  end if
782  case (2) ! memtype real
783  if (this%struct_vectors(sv_col)%idt%timeseries .and. timeseries) then
784  call parser%GetString(str)
785  if (present(auxcol)) then
786  icol = auxcol
787  else
788  icol = 1
789  end if
790  this%struct_vectors(sv_col)%dbl1d(irow) = &
791  this%struct_vectors(sv_col)%read_token(str, this%startidx(sv_col), &
792  icol, irow)
793  else
794  this%struct_vectors(sv_col)%dbl1d(irow) = parser%GetDouble()
795  end if
796  case (3) ! memtype charstring
797  if (this%struct_vectors(sv_col)%idt%shape /= '') then
798  ! if last column with any shape, store rest of line
799  if (sv_col == this%ncol) then
800  call parser%GetRemainingLine(line)
801  this%struct_vectors(sv_col)%charstr1d(irow) = line
802  deallocate (line)
803  end if
804  else
805  ! read string token
806  preserve_case = (.not. this%struct_vectors(sv_col)%idt%preserve_case)
807  call parser%GetString(str, preserve_case)
808  this%struct_vectors(sv_col)%charstr1d(irow) = str
809  end if
810  case (4) ! memtype intvector
811  ! get shape for this row
812  numval = this%struct_vectors(sv_col)%intvector_shape(irow)
813  ! read and store row values
814  do n = 1, numval
815  intval = parser%GetInteger()
816  call this%struct_vectors(sv_col)%intvector%push_back(intval)
817  end do
818  case (5) ! memtype int2d
819  ! read and store row values
820  do n = 1, this%struct_vectors(sv_col)%intshape
821  this%struct_vectors(sv_col)%int2d(n, irow) = parser%GetInteger()
822  end do
823  case (6) ! memtype dbl2d
824  ! read and store row values
825  do n = 1, this%struct_vectors(sv_col)%intshape
826  if (this%struct_vectors(sv_col)%idt%timeseries .and. timeseries) then
827  call parser%GetString(str)
828  icol = this%startidx(sv_col) + n - 1
829  this%struct_vectors(sv_col)%dbl2d(n, irow) = &
830  this%struct_vectors(sv_col)%read_token(str, icol, n, irow)
831  else
832  this%struct_vectors(sv_col)%dbl2d(n, irow) = parser%GetDouble()
833  end if
834  end do
835  end select

◆ set_pointer()

subroutine structarraymodule::set_pointer ( type(structvectortype), pointer  sv,
type(structvectortype), target  sv_target 
)
private

Definition at line 184 of file StructArray.f90.

185  type(StructVectorType), pointer :: sv
186  type(StructVectorType), target :: sv_target
187  sv => sv_target
Here is the caller graph for this function: