MODFLOW 6  version 6.7.0.dev0
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 write_struct_vector (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 614 of file StructArray.f90.

615  class(StructArrayType) :: this !< StructArrayType
616  integer(I4B) :: i, j, k, newsize
617  integer(I4B), dimension(:), pointer, contiguous :: p_int1d
618  integer(I4B), dimension(:, :), pointer, contiguous :: p_int2d
619  real(DP), dimension(:), pointer, contiguous :: p_dbl1d
620  type(CharacterStringType), dimension(:), pointer, contiguous :: p_charstr1d
621  integer(I4B) :: reallocate_mult
622 
623  ! set growth rate
624  reallocate_mult = 2
625 
626  do j = 1, this%ncol
627  ! reallocate based on memtype
628  select case (this%struct_vectors(j)%memtype)
629  case (1) ! memtype integer
630  ! check if more space needed
631  if (this%nrow > this%struct_vectors(j)%size) then
632  ! calculate new size
633  newsize = this%struct_vectors(j)%size * reallocate_mult
634  ! allocate new vector
635  allocate (p_int1d(newsize))
636 
637  ! copy from old to new
638  do i = 1, this%struct_vectors(j)%size
639  p_int1d(i) = this%struct_vectors(j)%int1d(i)
640  end do
641 
642  ! deallocate old vector
643  deallocate (this%struct_vectors(j)%int1d)
644 
645  ! update struct array object
646  this%struct_vectors(j)%int1d => p_int1d
647  this%struct_vectors(j)%size = newsize
648  end if
649  case (2) ! memtype real
650  if (this%nrow > this%struct_vectors(j)%size) then
651  newsize = this%struct_vectors(j)%size * reallocate_mult
652  allocate (p_dbl1d(newsize))
653 
654  do i = 1, this%struct_vectors(j)%size
655  p_dbl1d(i) = this%struct_vectors(j)%dbl1d(i)
656  end do
657 
658  deallocate (this%struct_vectors(j)%dbl1d)
659 
660  this%struct_vectors(j)%dbl1d => p_dbl1d
661  this%struct_vectors(j)%size = newsize
662  end if
663  !
664  case (3) ! memtype charstring
665  if (this%nrow > this%struct_vectors(j)%size) then
666  newsize = this%struct_vectors(j)%size * reallocate_mult
667  allocate (p_charstr1d(newsize))
668 
669  do i = 1, this%struct_vectors(j)%size
670  p_charstr1d(i) = this%struct_vectors(j)%charstr1d(i)
671  call this%struct_vectors(j)%charstr1d(i)%destroy()
672  end do
673 
674  deallocate (this%struct_vectors(j)%charstr1d)
675 
676  this%struct_vectors(j)%charstr1d => p_charstr1d
677  this%struct_vectors(j)%size = newsize
678  end if
679  case (5)
680  if (this%nrow > this%struct_vectors(j)%size) then
681  newsize = this%struct_vectors(j)%size * reallocate_mult
682  allocate (p_int2d(this%struct_vectors(j)%intshape, newsize))
683 
684  do i = 1, this%struct_vectors(j)%size
685  do k = 1, this%struct_vectors(j)%intshape
686  p_int2d(k, i) = this%struct_vectors(j)%int2d(k, i)
687  end do
688  end do
689 
690  deallocate (this%struct_vectors(j)%int2d)
691 
692  this%struct_vectors(j)%int2d => p_int2d
693  this%struct_vectors(j)%size = newsize
694  end if
695  ! TODO: case (6)
696  case default
697  errmsg = 'IDM unimplemented. StructArray::check_reallocate &
698  &unsupported memtype.'
699  call store_error(errmsg, terminate=.true.)
700  end select
701  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 
414  ! set varname
415  varname = this%struct_vectors(icol)%idt%mf6varname
416  ! check if already mem managed variable
417  call get_isize(varname, this%mempath, isize)
418 
419  ! allocate and load based on memtype
420  select case (this%struct_vectors(icol)%memtype)
421  case (1) ! memtype integer
422  if (isize > -1) then
423  ! variable exists, reallocate and append
424  call mem_setptr(p_int1d, varname, this%mempath)
425  ! Currently deferred vectors are appended to managed
426  ! memory vectors when they are already allocated
427  ! (e.g. SIMNAM SolutionGroup)
428  call mem_reallocate(p_int1d, this%nrow + isize, varname, this%mempath)
429 
430  do i = 1, this%nrow
431  p_int1d(isize + i) = this%struct_vectors(icol)%int1d(i)
432  end do
433  else
434  ! allocate memory manager vector
435  call mem_allocate(p_int1d, this%nrow, varname, this%mempath)
436 
437  ! load local vector to managed memory
438  do i = 1, this%nrow
439  p_int1d(i) = this%struct_vectors(icol)%int1d(i)
440  end do
441  end if
442 
443  ! deallocate local memory
444  deallocate (this%struct_vectors(icol)%int1d)
445 
446  ! update structvector
447  this%struct_vectors(icol)%int1d => p_int1d
448  this%struct_vectors(icol)%size = this%nrow
449  case (2) ! memtype real
450  if (isize > -1) then
451  call mem_setptr(p_dbl1d, varname, this%mempath)
452  call mem_reallocate(p_dbl1d, this%nrow + isize, varname, &
453  this%mempath)
454  do i = 1, this%nrow
455  p_dbl1d(isize + i) = this%struct_vectors(icol)%dbl1d(i)
456  end do
457  else
458  call mem_allocate(p_dbl1d, this%nrow, varname, this%mempath)
459 
460  do i = 1, this%nrow
461  p_dbl1d(i) = this%struct_vectors(icol)%dbl1d(i)
462  end do
463  end if
464 
465  deallocate (this%struct_vectors(icol)%dbl1d)
466 
467  this%struct_vectors(icol)%dbl1d => p_dbl1d
468  this%struct_vectors(icol)%size = this%nrow
469  !
470  case (3) ! memtype charstring
471  if (isize > -1) then
472  call mem_setptr(p_charstr1d, varname, this%mempath)
473  call mem_reallocate(p_charstr1d, linelength, this%nrow + isize, varname, &
474  this%mempath)
475  do i = 1, this%nrow
476  p_charstr1d(isize + i) = this%struct_vectors(icol)%charstr1d(i)
477  end do
478  else
479  call mem_allocate(p_charstr1d, linelength, this%nrow, varname, &
480  this%mempath)
481  do i = 1, this%nrow
482  p_charstr1d(i) = this%struct_vectors(icol)%charstr1d(i)
483  call this%struct_vectors(icol)%charstr1d(i)%destroy()
484  end do
485  end if
486 
487  deallocate (this%struct_vectors(icol)%charstr1d)
488 
489  this%struct_vectors(icol)%charstr1d => p_charstr1d
490  this%struct_vectors(icol)%size = this%nrow
491  case (4) ! memtype intvector
492  ! no-op
493  case (5)
494  if (isize > -1) then
495  call mem_setptr(p_int2d, varname, this%mempath)
496  call mem_reallocate(p_int2d, this%struct_vectors(icol)%intshape, &
497  this%nrow, varname, this%mempath)
498 
499  do i = 1, this%nrow
500  do j = 1, this%struct_vectors(icol)%intshape
501  p_int2d(j, isize + i) = this%struct_vectors(icol)%int2d(j, i)
502  end do
503  end do
504  else
505  call mem_allocate(p_int2d, this%struct_vectors(icol)%intshape, &
506  this%nrow, varname, this%mempath)
507  do i = 1, this%nrow
508  do j = 1, this%struct_vectors(icol)%intshape
509  p_int2d(j, i) = this%struct_vectors(icol)%int2d(j, i)
510  end do
511  end do
512  end if
513 
514  deallocate (this%struct_vectors(icol)%int2d)
515 
516  this%struct_vectors(icol)%int2d => p_int2d
517  this%struct_vectors(icol)%size = this%nrow
518 
519  ! TODO: case (6)
520  case default
521  errmsg = 'IDM unimplemented. StructArray::load_deferred_vector &
522  &unsupported memtype.'
523  call store_error(errmsg, terminate=.true.)
524  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 567 of file StructArray.f90.

568  class(StructArrayType) :: this !< StructArrayType
569  integer(I4B), intent(in) :: iout !< unit number for output
570  integer(I4B) :: j
571  integer(I4B), dimension(:), pointer, contiguous :: int1d
572 
573  ! idm variable logging
574  do j = 1, this%ncol
575  ! log based on memtype
576  select case (this%struct_vectors(j)%memtype)
577  case (1) ! memtype integer
578  call idm_log_var(this%struct_vectors(j)%int1d, &
579  this%struct_vectors(j)%idt%tagname, &
580  this%mempath, iout)
581  case (2) ! memtype real
582  if (this%struct_vectors(j)%ts_strlocs%count() > 0) then
583  call idm_log_var(this%struct_vectors(j)%idt%tagname, &
584  this%mempath, iout, .false.)
585  else
586  call idm_log_var(this%struct_vectors(j)%dbl1d, &
587  this%struct_vectors(j)%idt%tagname, &
588  this%mempath, iout)
589  end if
590  case (4) ! memtype intvector
591  call mem_setptr(int1d, this%struct_vectors(j)%idt%mf6varname, &
592  this%mempath)
593  call idm_log_var(int1d, this%struct_vectors(j)%idt%tagname, &
594  this%mempath, iout)
595  case (5) ! memtype int2d
596  call idm_log_var(this%struct_vectors(j)%int2d, &
597  this%struct_vectors(j)%idt%tagname, &
598  this%mempath, iout)
599  case (6) ! memtype dbl2d
600  if (this%struct_vectors(j)%ts_strlocs%count() > 0) then
601  call idm_log_var(this%struct_vectors(j)%idt%tagname, &
602  this%mempath, iout, .false.)
603  else
604  call idm_log_var(this%struct_vectors(j)%dbl2d, &
605  this%struct_vectors(j)%idt%tagname, &
606  this%mempath, iout)
607  end if
608  end select
609  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 529 of file StructArray.f90.

530  class(StructArrayType) :: this !< StructArrayType
531  integer(I4B) :: icol, j
532  integer(I4B), dimension(:), pointer, contiguous :: p_intvector
533  character(len=LENVARNAME) :: varname
534 
535  do icol = 1, this%ncol
536  ! set varname
537  varname = this%struct_vectors(icol)%idt%mf6varname
538 
539  if (this%struct_vectors(icol)%memtype == 4) then
540  ! intvectors always need to be loaded
541  ! size intvector to number of values read
542  call this%struct_vectors(icol)%intvector%shrink_to_fit()
543 
544  ! allocate memory manager vector
545  call mem_allocate(p_intvector, &
546  this%struct_vectors(icol)%intvector%size, &
547  varname, this%mempath)
548 
549  ! load local vector to managed memory
550  do j = 1, this%struct_vectors(icol)%intvector%size
551  p_intvector(j) = this%struct_vectors(icol)%intvector%at(j)
552  end do
553 
554  ! cleanup local memory
555  call this%struct_vectors(icol)%intvector%destroy()
556  deallocate (this%struct_vectors(icol)%intvector)
557  nullify (this%struct_vectors(icol)%intvector_shape)
558  else if (this%deferred_shape) then
559  ! load as shape wasn't known
560  call this%load_deferred_vector(icol)
561  end if
562  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 827 of file StructArray.f90.

828  class(StructArrayType) :: this !< StructArrayType
829  integer(I4B), intent(in) :: inunit !< unit number for binary input
830  integer(I4B), intent(in) :: iout !< unit number for output
831  integer(I4B) :: irow, ierr
832  integer(I4B) :: j, k
833  integer(I4B) :: intval, numval
834  character(len=LINELENGTH) :: fname
835  character(len=*), parameter :: fmtlsterronly = &
836  "('Error reading LIST from file: ',&
837  &1x,a,1x,' on UNIT: ',I0)"
838 
839  ! set error and exit if deferred shape
840  if (this%deferred_shape) then
841  errmsg = 'IDM unimplemented. StructArray::read_from_binary deferred shape &
842  &not supported for binary inputs.'
843  call store_error(errmsg, terminate=.true.)
844  end if
845  ! initialize
846  irow = 0
847  ierr = 0
848  readloop: do
849  ! update irow index
850  irow = irow + 1
851  ! handle line reads by column memtype
852  do j = 1, this%ncol
853  select case (this%struct_vectors(j)%memtype)
854  case (1) ! memtype integer
855  read (inunit, iostat=ierr) this%struct_vectors(j)%int1d(irow)
856  case (2) ! memtype real
857  read (inunit, iostat=ierr) this%struct_vectors(j)%dbl1d(irow)
858  case (3) ! memtype charstring
859  errmsg = 'List style binary inputs not supported &
860  &for text columns, tag='// &
861  trim(this%struct_vectors(j)%idt%tagname)//'.'
862  call store_error(errmsg, terminate=.true.)
863  case (4) ! memtype intvector
864  ! get shape for this row
865  numval = this%struct_vectors(j)%intvector_shape(irow)
866  ! read and store row values
867  do k = 1, numval
868  if (ierr == 0) then
869  read (inunit, iostat=ierr) intval
870  call this%struct_vectors(j)%intvector%push_back(intval)
871  end if
872  end do
873  case (5) ! memtype int2d
874  ! read and store row values
875  do k = 1, this%struct_vectors(j)%intshape
876  if (ierr == 0) then
877  read (inunit, iostat=ierr) this%struct_vectors(j)%int2d(k, irow)
878  end if
879  end do
880  case (6) ! memtype dbl2d
881  do k = 1, this%struct_vectors(j)%intshape
882  if (ierr == 0) then
883  read (inunit, iostat=ierr) this%struct_vectors(j)%dbl2d(k, irow)
884  end if
885  end do
886  end select
887 
888  ! handle error cases
889  select case (ierr)
890  case (0)
891  ! no error
892  case (:-1)
893  ! End of block was encountered
894  irow = irow - 1
895  exit readloop
896  case (1:)
897  ! Error
898  inquire (unit=inunit, name=fname)
899  write (errmsg, fmtlsterronly) trim(adjustl(fname)), inunit
900  call store_error(errmsg, terminate=.true.)
901  case default
902  end select
903  end do
904  if (irow == this%nrow) exit readloop
905  end do readloop
906 
907  ! Stop if errors were detected
908  !if (count_errors() > 0) then
909  ! call store_error_unit(inunit)
910  !end if
911 
912  ! if deferred shape vectors were read, load to input path
913  call this%memload_vectors()
914 
915  ! log loaded variables
916  if (iout > 0) then
917  call this%log_structarray_vars(iout)
918  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 786 of file StructArray.f90.

787  class(StructArrayType) :: this !< StructArrayType
788  type(BlockParserType) :: parser !< block parser to read from
789  logical(LGP), intent(in) :: timeseries
790  integer(I4B), intent(in) :: iout !< unit number for output
791  integer(I4B) :: irow, j
792  logical(LGP) :: endOfBlock
793 
794  ! initialize index irow
795  irow = 0
796 
797  ! read entire block
798  do
799  ! read next line
800  call parser%GetNextLine(endofblock)
801  if (endofblock) then
802  ! no more lines
803  exit
804  else if (this%deferred_shape) then
805  ! shape unknown, track lines read
806  this%nrow = this%nrow + 1
807  ! check and update memory allocation
808  call this%check_reallocate()
809  end if
810  ! update irow index
811  irow = irow + 1
812  ! handle line reads by column memtype
813  do j = 1, this%ncol
814  call this%write_struct_vector(parser, j, irow, timeseries, iout)
815  end do
816  end do
817  ! if deferred shape vectors were read, load to input path
818  call this%memload_vectors()
819  ! log loaded variables
820  if (iout > 0) then
821  call this%log_structarray_vars(iout)
822  end if

◆ 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:

◆ write_struct_vector()

subroutine structarraymodule::write_struct_vector ( 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 704 of file StructArray.f90.

706  class(StructArrayType) :: this !< StructArrayType
707  type(BlockParserType), intent(inout) :: parser !< block parser to read from
708  integer(I4B), intent(in) :: sv_col
709  integer(I4B), intent(in) :: irow
710  logical(LGP), intent(in) :: timeseries
711  integer(I4B), intent(in) :: iout !< unit number for output
712  integer(I4B), optional, intent(in) :: auxcol
713  integer(I4B) :: n, intval, numval, icol
714  character(len=LINELENGTH) :: str
715  character(len=:), allocatable :: line
716  logical(LGP) :: preserve_case
717 
718  select case (this%struct_vectors(sv_col)%memtype)
719  case (1) ! memtype integer
720  ! if reloadable block and first col, store blocknum
721  if (sv_col == 1 .and. this%blocknum > 0) then
722  ! store blocknum
723  this%struct_vectors(sv_col)%int1d(irow) = this%blocknum
724  else
725  ! read and store int
726  this%struct_vectors(sv_col)%int1d(irow) = parser%GetInteger()
727  end if
728  case (2) ! memtype real
729  if (this%struct_vectors(sv_col)%idt%timeseries .and. timeseries) then
730  call parser%GetString(str)
731  if (present(auxcol)) then
732  icol = auxcol
733  else
734  icol = 1
735  end if
736  this%struct_vectors(sv_col)%dbl1d(irow) = &
737  this%struct_vectors(sv_col)%read_token(str, this%startidx(sv_col), &
738  icol, irow)
739  else
740  this%struct_vectors(sv_col)%dbl1d(irow) = parser%GetDouble()
741  end if
742  case (3) ! memtype charstring
743  if (this%struct_vectors(sv_col)%idt%shape /= '') then
744  ! if last column with any shape, store rest of line
745  if (sv_col == this%ncol) then
746  call parser%GetRemainingLine(line)
747  this%struct_vectors(sv_col)%charstr1d(irow) = line
748  deallocate (line)
749  end if
750  else
751  ! read string token
752  preserve_case = (.not. this%struct_vectors(sv_col)%idt%preserve_case)
753  call parser%GetString(str, preserve_case)
754  this%struct_vectors(sv_col)%charstr1d(irow) = str
755  end if
756  case (4) ! memtype intvector
757  ! get shape for this row
758  numval = this%struct_vectors(sv_col)%intvector_shape(irow)
759  ! read and store row values
760  do n = 1, numval
761  intval = parser%GetInteger()
762  call this%struct_vectors(sv_col)%intvector%push_back(intval)
763  end do
764  case (5) ! memtype int2d
765  ! read and store row values
766  do n = 1, this%struct_vectors(sv_col)%intshape
767  this%struct_vectors(sv_col)%int2d(n, irow) = parser%GetInteger()
768  end do
769  case (6) ! memtype dbl2d
770  ! read and store row values
771  do n = 1, this%struct_vectors(sv_col)%intshape
772  if (this%struct_vectors(sv_col)%idt%timeseries .and. timeseries) then
773  call parser%GetString(str)
774  icol = this%startidx(sv_col) + n - 1
775  this%struct_vectors(sv_col)%dbl2d(n, irow) = &
776  this%struct_vectors(sv_col)%read_token(str, icol, n, irow)
777  else
778  this%struct_vectors(sv_col)%dbl2d(n, irow) = parser%GetDouble()
779  end if
780  end do
781  end select