39 integer(I4B) :: blocknum
40 logical(LGP) :: deferred_shape = .false.
41 integer(I4B) :: deferred_size_init = 5
42 character(len=LENMEMPATH) :: mempath
43 character(len=LENMEMPATH) :: component_mempath
45 integer(I4B),
dimension(:),
allocatable :: startidx
46 integer(I4B),
dimension(:),
allocatable :: numcols
72 component_mempath)
result(struct_array)
74 integer(I4B),
intent(in) :: ncol
75 integer(I4B),
intent(in) :: nrow
76 integer(I4B),
intent(in) :: blocknum
77 character(len=*),
intent(in) :: mempath
78 character(len=*),
intent(in) :: component_mempath
82 allocate (struct_array)
85 struct_array%mf6_input = mf6_input
88 struct_array%ncol = ncol
91 struct_array%nrow = nrow
92 if (struct_array%nrow == -1)
then
94 struct_array%deferred_shape = .true.
98 if (blocknum > 0)
then
99 struct_array%blocknum = blocknum
101 struct_array%blocknum = 0
105 struct_array%mempath = mempath
106 struct_array%component_mempath = component_mempath
109 allocate (struct_array%struct_vectors(ncol))
110 allocate (struct_array%startidx(ncol))
111 allocate (struct_array%numcols(ncol))
118 deallocate (struct_array%struct_vectors)
119 deallocate (struct_array%startidx)
120 deallocate (struct_array%numcols)
121 deallocate (struct_array)
122 nullify (struct_array)
129 integer(I4B),
intent(in) :: icol
132 integer(I4B) :: numcol
140 if (this%deferred_shape)
then
141 sv%size = this%deferred_size_init
147 select case (idt%datatype)
149 call this%allocate_int_type(sv)
151 call this%allocate_dbl_type(sv)
152 case (
'STRING',
'KEYWORD')
153 call this%allocate_charstr_type(sv)
155 call this%allocate_int1d_type(sv)
156 if (sv%memtype == 5)
then
160 call this%allocate_dbl1d_type(sv)
163 errmsg =
'IDM unimplemented. StructArray::mem_create_vector &
164 &type='//trim(idt%datatype)
169 this%struct_vectors(icol) = sv
170 this%numcols(icol) = numcol
172 this%startidx(icol) = 1
174 this%startidx(icol) = this%startidx(icol - 1) + this%numcols(icol - 1)
180 integer(I4B) ::
count
181 count =
size(this%struct_vectors)
190 function get(this, idx)
result(sv)
192 integer(I4B),
intent(in) :: idx
202 integer(I4B),
dimension(:),
pointer,
contiguous :: int1d
203 integer(I4B) :: j, nrow
205 if (this%deferred_shape)
then
207 nrow = this%deferred_size_init
208 allocate (int1d(this%deferred_size_init))
212 call mem_allocate(int1d, this%nrow, sv%idt%mf6varname, this%mempath)
229 real(DP),
dimension(:),
pointer,
contiguous :: dbl1d
230 integer(I4B) :: j, nrow
232 if (this%deferred_shape)
then
234 nrow = this%deferred_size_init
235 allocate (dbl1d(this%deferred_size_init))
239 call mem_allocate(dbl1d, this%nrow, sv%idt%mf6varname, this%mempath)
259 if (this%deferred_shape)
then
260 allocate (charstr1d(this%deferred_size_init))
263 sv%idt%mf6varname, this%mempath)
271 sv%charstr1d => charstr1d
282 integer(I4B),
dimension(:, :),
pointer,
contiguous :: int2d
284 integer(I4B),
pointer :: ncelldim, exgid
285 character(len=LENMEMPATH) :: input_mempath
286 character(len=LENMODELNAME) :: mname
289 integer(I4B) :: nrow, n, m
291 if (sv%idt%shape ==
'NCELLDIM')
then
293 if (this%mf6_input%component_type ==
'EXG')
then
295 call mem_setptr(exgid,
'EXGID', this%mf6_input%mempath)
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)
305 mname = charstr1d(exgid)
309 call mem_setptr(ncelldim, sv%idt%shape, input_mempath)
311 call mem_setptr(ncelldim, sv%idt%shape, this%component_mempath)
314 if (this%deferred_shape)
then
316 nrow = this%deferred_size_init
317 allocate (int2d(ncelldim, this%deferred_size_init))
322 sv%idt%mf6varname, this%mempath)
334 sv%intshape => ncelldim
339 call intvector%init()
341 sv%intvector => intvector
344 call mem_setptr(sv%intvector_shape, sv%idt%shape, this%mempath)
354 real(DP),
dimension(:, :),
pointer,
contiguous :: dbl2d
355 integer(I4B),
pointer :: naux, nseg, nseg_1
356 integer(I4B) :: nseg1_isize, n, m
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)
372 else if (sv%idt%shape ==
'NSEG-1')
then
374 call get_isize(
'NSEG_1', this%mempath, nseg1_isize)
376 if (nseg1_isize < 0)
then
380 call mem_setptr(nseg_1,
'NSEG_1', this%mempath)
384 call mem_allocate(dbl2d, nseg_1, this%nrow, sv%idt%mf6varname, this%mempath)
395 sv%intshape => nseg_1
397 errmsg =
'IDM unimplemented. StructArray::allocate_dbl1d_type &
398 & unsupported shape "'//trim(sv%idt%shape)//
'".'
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
412 character(len=LENVARNAME) :: varname
413 logical(LGP) :: overwrite
416 if (this%struct_vectors(icol)%idt%blockname ==
'SOLUTIONGROUP') &
420 varname = this%struct_vectors(icol)%idt%mf6varname
422 call get_isize(varname, this%mempath, isize)
425 select case (this%struct_vectors(icol)%memtype)
429 call mem_setptr(p_int1d, varname, this%mempath)
433 if (this%nrow > isize)
then
440 p_int1d(i) = this%struct_vectors(icol)%int1d(i)
443 if (isize > this%nrow)
then
445 do i = this%nrow + 1, isize
451 call mem_reallocate(p_int1d, this%nrow + isize, varname, this%mempath)
455 p_int1d(isize + i) = this%struct_vectors(icol)%int1d(i)
460 call mem_allocate(p_int1d, this%nrow, varname, this%mempath)
464 p_int1d(i) = this%struct_vectors(icol)%int1d(i)
469 deallocate (this%struct_vectors(icol)%int1d)
472 this%struct_vectors(icol)%int1d => p_int1d
473 this%struct_vectors(icol)%size = this%nrow
476 call mem_setptr(p_dbl1d, varname, this%mempath)
479 if (this%nrow > isize)
then
484 p_dbl1d(i) = this%struct_vectors(icol)%dbl1d(i)
487 if (isize > this%nrow)
then
488 do i = this%nrow + 1, isize
496 p_dbl1d(isize + i) = this%struct_vectors(icol)%dbl1d(i)
500 call mem_allocate(p_dbl1d, this%nrow, varname, this%mempath)
503 p_dbl1d(i) = this%struct_vectors(icol)%dbl1d(i)
507 deallocate (this%struct_vectors(icol)%dbl1d)
509 this%struct_vectors(icol)%dbl1d => p_dbl1d
510 this%struct_vectors(icol)%size = this%nrow
514 call mem_setptr(p_charstr1d, varname, this%mempath)
517 if (this%nrow > isize)
then
523 p_charstr1d(i) = this%struct_vectors(icol)%charstr1d(i)
526 if (isize > this%nrow)
then
527 do i = this%nrow + 1, isize
533 varname, this%mempath)
535 p_charstr1d(isize + i) = this%struct_vectors(icol)%charstr1d(i)
542 p_charstr1d(i) = this%struct_vectors(icol)%charstr1d(i)
543 call this%struct_vectors(icol)%charstr1d(i)%destroy()
547 deallocate (this%struct_vectors(icol)%charstr1d)
549 this%struct_vectors(icol)%charstr1d => p_charstr1d
550 this%struct_vectors(icol)%size = this%nrow
552 errmsg =
'StructArray::load_deferred_vector &
553 &intvector reallocate unimplemented.'
557 errmsg =
'StructArray::load_deferred_vector &
558 &int2d reallocate unimplemented.'
561 call mem_allocate(p_int2d, this%struct_vectors(icol)%intshape, &
562 this%nrow, varname, this%mempath)
564 do j = 1, this%struct_vectors(icol)%intshape
565 p_int2d(j, i) = this%struct_vectors(icol)%int2d(j, i)
570 deallocate (this%struct_vectors(icol)%int2d)
572 this%struct_vectors(icol)%int2d => p_int2d
573 this%struct_vectors(icol)%size = this%nrow
575 errmsg =
'StructArray::load_deferred_vector &
576 &dbl2d reallocate unimplemented.'
586 integer(I4B) :: icol, j
587 integer(I4B),
dimension(:),
pointer,
contiguous :: p_intvector
588 character(len=LENVARNAME) :: varname
590 do icol = 1, this%ncol
592 varname = this%struct_vectors(icol)%idt%mf6varname
594 if (this%struct_vectors(icol)%memtype == 4)
then
597 call this%struct_vectors(icol)%intvector%shrink_to_fit()
601 this%struct_vectors(icol)%intvector%size, &
602 varname, this%mempath)
605 do j = 1, this%struct_vectors(icol)%intvector%size
606 p_intvector(j) = this%struct_vectors(icol)%intvector%at(j)
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
615 call this%load_deferred_vector(icol)
624 integer(I4B),
intent(in) :: iout
626 integer(I4B),
dimension(:),
pointer,
contiguous :: int1d
631 select case (this%struct_vectors(j)%memtype)
634 this%struct_vectors(j)%idt%tagname, &
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.)
642 this%struct_vectors(j)%idt%tagname, &
646 call mem_setptr(int1d, this%struct_vectors(j)%idt%mf6varname, &
648 call idm_log_var(int1d, this%struct_vectors(j)%idt%tagname, &
652 this%struct_vectors(j)%idt%tagname, &
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.)
660 this%struct_vectors(j)%idt%tagname, &
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
676 integer(I4B) :: reallocate_mult
683 select case (this%struct_vectors(j)%memtype)
686 if (this%nrow > this%struct_vectors(j)%size)
then
688 newsize = this%struct_vectors(j)%size * reallocate_mult
690 allocate (p_int1d(newsize))
693 do i = 1, this%struct_vectors(j)%size
694 p_int1d(i) = this%struct_vectors(j)%int1d(i)
698 deallocate (this%struct_vectors(j)%int1d)
701 this%struct_vectors(j)%int1d => p_int1d
702 this%struct_vectors(j)%size = newsize
705 if (this%nrow > this%struct_vectors(j)%size)
then
706 newsize = this%struct_vectors(j)%size * reallocate_mult
707 allocate (p_dbl1d(newsize))
709 do i = 1, this%struct_vectors(j)%size
710 p_dbl1d(i) = this%struct_vectors(j)%dbl1d(i)
713 deallocate (this%struct_vectors(j)%dbl1d)
715 this%struct_vectors(j)%dbl1d => p_dbl1d
716 this%struct_vectors(j)%size = newsize
720 if (this%nrow > this%struct_vectors(j)%size)
then
721 newsize = this%struct_vectors(j)%size * reallocate_mult
722 allocate (p_charstr1d(newsize))
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()
729 deallocate (this%struct_vectors(j)%charstr1d)
731 this%struct_vectors(j)%charstr1d => p_charstr1d
732 this%struct_vectors(j)%size = newsize
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))
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)
745 deallocate (this%struct_vectors(j)%int2d)
747 this%struct_vectors(j)%int2d => p_int2d
748 this%struct_vectors(j)%size = newsize
752 errmsg =
'IDM unimplemented. StructArray::check_reallocate &
753 &unsupported memtype.'
759 subroutine read_param(this, parser, sv_col, irow, timeseries, iout, auxcol)
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
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
772 select case (this%struct_vectors(sv_col)%memtype)
775 if (sv_col == 1 .and. this%blocknum > 0)
then
777 this%struct_vectors(sv_col)%int1d(irow) = this%blocknum
780 this%struct_vectors(sv_col)%int1d(irow) = parser%GetInteger()
783 if (this%struct_vectors(sv_col)%idt%timeseries .and. timeseries)
then
784 call parser%GetString(str)
785 if (
present(auxcol))
then
790 this%struct_vectors(sv_col)%dbl1d(irow) = &
791 this%struct_vectors(sv_col)%read_token(str, this%startidx(sv_col), &
794 this%struct_vectors(sv_col)%dbl1d(irow) = parser%GetDouble()
797 if (this%struct_vectors(sv_col)%idt%shape /=
'')
then
799 if (sv_col == this%ncol)
then
800 call parser%GetRemainingLine(line)
801 this%struct_vectors(sv_col)%charstr1d(irow) = line
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
812 numval = this%struct_vectors(sv_col)%intvector_shape(irow)
815 intval = parser%GetInteger()
816 call this%struct_vectors(sv_col)%intvector%push_back(intval)
820 do n = 1, this%struct_vectors(sv_col)%intshape
821 this%struct_vectors(sv_col)%int2d(n, irow) = parser%GetInteger()
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)
832 this%struct_vectors(sv_col)%dbl2d(n, irow) = parser%GetDouble()
843 logical(LGP),
intent(in) :: timeseries
844 integer(I4B),
intent(in) :: iout
845 integer(I4B) :: irow, j
846 logical(LGP) :: endofblock
854 call parser%GetNextLine(endofblock)
858 else if (this%deferred_shape)
then
860 this%nrow = this%nrow + 1
862 call this%check_reallocate()
868 call this%read_param(parser, j, irow, timeseries, iout)
872 call this%memload_vectors()
875 call this%log_structarray_vars(iout)
883 integer(I4B),
intent(in) :: inunit
884 integer(I4B),
intent(in) :: iout
885 integer(I4B) :: irow, ierr
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)"
894 if (this%deferred_shape)
then
895 errmsg =
'IDM unimplemented. StructArray::read_from_binary deferred shape &
896 ¬ supported for binary inputs.'
907 select case (this%struct_vectors(j)%memtype)
909 read (inunit, iostat=ierr) this%struct_vectors(j)%int1d(irow)
911 read (inunit, iostat=ierr) this%struct_vectors(j)%dbl1d(irow)
913 errmsg =
'List style binary inputs not supported &
914 &for text columns, tag='// &
915 trim(this%struct_vectors(j)%idt%tagname)//
'.'
919 numval = this%struct_vectors(j)%intvector_shape(irow)
923 read (inunit, iostat=ierr) intval
924 call this%struct_vectors(j)%intvector%push_back(intval)
929 do k = 1, this%struct_vectors(j)%intshape
931 read (inunit, iostat=ierr) this%struct_vectors(j)%int2d(k, irow)
935 do k = 1, this%struct_vectors(j)%intshape
937 read (inunit, iostat=ierr) this%struct_vectors(j)%dbl2d(k, irow)
952 inquire (unit=inunit, name=fname)
953 write (
errmsg, fmtlsterronly) trim(adjustl(fname)), inunit
958 if (irow == this%nrow)
exit readloop
967 call this%memload_vectors()
971 call this%log_structarray_vars(iout)
This module contains block parser methods.
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
integer(i4b), parameter lenmodelname
maximum length of the model name
real(dp), parameter dnodata
real no data constant
integer(i4b), parameter lenvarname
maximum length of a variable name
integer(i4b), parameter izero
integer constant zero
real(dp), parameter dzero
real constant zero
integer(i4b), parameter lenmempath
maximum length of the memory path
This module contains the Input Data Model Logger Module.
This module defines variable data types.
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
This module contains simulation variables.
character(len=maxcharlen) errmsg
error message string
character(len=linelength) idm_context
This module contains the StructArrayModule.
integer(i4b) function count(this)
subroutine mem_create_vector(this, icol, idt)
create new vector in StructArrayType
type(structarraytype) function, pointer, public constructstructarray(mf6_input, ncol, nrow, blocknum, mempath, component_mempath)
constructor for a struct_array
integer(i4b) function read_from_parser(this, parser, timeseries, iout)
read from the block parser to fill the StructArrayType
integer(i4b) function read_from_binary(this, inunit, iout)
read from binary input to fill the StructArrayType
subroutine read_param(this, parser, sv_col, irow, timeseries, iout, auxcol)
subroutine memload_vectors(this)
load deferred vectors into managed memory
subroutine set_pointer(sv, sv_target)
subroutine allocate_dbl1d_type(this, sv)
allocate dbl1d input type
subroutine check_reallocate(this)
reallocate local memory for deferred vectors if necessary
subroutine load_deferred_vector(this, icol)
subroutine allocate_dbl_type(this, sv)
allocate double input type
subroutine allocate_charstr_type(this, sv)
allocate charstr input type
subroutine allocate_int_type(this, sv)
allocate integer input type
subroutine log_structarray_vars(this, iout)
log information about the StructArrayType
subroutine, public destructstructarray(struct_array)
destructor for a struct_array
subroutine allocate_int1d_type(this, sv)
allocate int1d input type
type(structvectortype) function, pointer get(this, idx)
This module contains the StructVectorModule.
This class is used to store a single deferred-length character string. It was designed to work in an ...
type for structured array
derived type for generic vector