MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
arrayhandlersmodule Module Reference

Data Types

interface  expandarraywrapper
 
interface  expandarray
 
interface  expandarray2d
 
interface  extendptrarray
 
interface  concatarray
 
interface  ifind
 

Functions/Subroutines

subroutine expand_integer_wrapper (nsize, array, minvalue, loginc)
 
subroutine expand_integer (array, increment)
 
subroutine expand_double (array, increment)
 
subroutine expand_logical (array, increment)
 
subroutine expand_character (array, increment)
 
subroutine expand_integer_2d (array, increment1, increment2)
 
subroutine expand_double_2d (array, increment1, increment2)
 
subroutine extend_double (array, increment)
 
subroutine extend_integer (array, increment)
 
subroutine extend_string (array, increment)
 
subroutine concat_integer (array, array_to_add)
 Concatenate integer arrays. More...
 
integer(i4b) function ifind_character (array, str)
 Find the 1st array element containing str, or -1 if not found. More...
 
integer(i4b) function ifind_integer (iarray, ival)
 Find the first element containing ival, or -1 if not found. More...
 
subroutine, public remove_character (array, ipos)
 Remove the element at ipos from the array. More...
 

Function/Subroutine Documentation

◆ concat_integer()

subroutine arrayhandlersmodule::concat_integer ( integer(i4b), dimension(:), pointer, contiguous  array,
integer(i4b), dimension(:), pointer, contiguous  array_to_add 
)
private

Definition at line 459 of file ArrayHandlers.f90.

460  integer(I4B), dimension(:), pointer, contiguous :: array
461  integer(I4B), dimension(:), pointer, contiguous :: array_to_add
462  ! local
463  integer(I4B) :: i, n
464 
465  n = size(array)
466  call extendptrarray(array, increment=size(array_to_add))
467  do i = 1, size(array_to_add)
468  array(n + i) = array_to_add(i)
469  end do

◆ expand_character()

subroutine arrayhandlersmodule::expand_character ( character(len=*), dimension(:), intent(inout), allocatable  array,
integer(i4b), intent(in), optional  increment 
)
private

Definition at line 205 of file ArrayHandlers.f90.

206  ! -- dummy
207  character(len=*), allocatable, intent(inout) :: array(:)
208  integer(I4B), optional, intent(in) :: increment
209  ! -- local
210  character(len=MAXCHARLEN), allocatable, dimension(:) :: temp
211  integer(I4B) :: i, inc, nold, nnew, lenc
212 
213  ! -- check character length
214  lenc = len(array)
215  if (lenc > maxcharlen) &
216  call pstop(138, 'Error in ArrayHandlersModule: '// &
217  'Need to increase MAXCHARLEN. Stopping...')
218 
219  ! -- default to expanding by 1
220  if (present(increment)) then
221  inc = increment
222  if (inc == 0) return
223  if (inc < 0) call pstop(1, "increment must be nonnegative")
224  else
225  inc = 1
226  end if
227 
228  ! -- expand array to the requested size, keeping
229  ! existing items, or allocate if still needed
230  ! TODO: may be able to use mold here, e.g.:
231  ! allocate(values(num), mold=proto)
232  if (allocated(array)) then
233  nold = size(array)
234  nnew = nold + inc
235  allocate (temp(nold))
236  do i = 1, nold
237  temp(i) = array(i)
238  end do
239  deallocate (array)
240  allocate (array(nnew))
241  do i = 1, nold
242  array(i) = temp(i)
243  end do
244  do i = nold + 1, nnew
245  array(i) = ''
246  end do
247  deallocate (temp)
248  else
249  allocate (array(inc))
250  end if
251 

◆ expand_double()

subroutine arrayhandlersmodule::expand_double ( real(dp), dimension(:), intent(inout), allocatable  array,
integer(i4b), intent(in), optional  increment 
)
private

Definition at line 139 of file ArrayHandlers.f90.

140  ! -- dummy
141  real(DP), allocatable, intent(inout) :: array(:)
142  integer(I4B), optional, intent(in) :: increment
143  ! -- local
144  integer(I4B) :: inc, lb, n
145  real(DP), allocatable, dimension(:) :: temp
146 
147  ! -- default to expanding by 1
148  if (present(increment)) then
149  inc = increment
150  if (inc == 0) return
151  if (inc < 0) call pstop(1, "increment must be nonnegative")
152  else
153  inc = 1
154  end if
155 
156  ! -- expand array to the requested size, keeping
157  ! existing items and the existing lower bound,
158  ! or allocate the array if still unallocated
159  if (allocated(array)) then
160  lb = lbound(array, 1)
161  n = size(array)
162  allocate (temp(lb:(lb + n + inc - 1)))
163  temp(lb:(lb + n - 1)) = array
164  deallocate (array)
165  call move_alloc(temp, array)
166  else
167  allocate (array(inc))
168  end if
169 

◆ expand_double_2d()

subroutine arrayhandlersmodule::expand_double_2d ( real(dp), dimension(:, :), intent(inout), allocatable  array,
integer(i4b), intent(in), optional  increment1,
integer(i4b), intent(in), optional  increment2 
)
private

Definition at line 302 of file ArrayHandlers.f90.

303  ! -- dummy
304  real(DP), allocatable, intent(inout) :: array(:, :)
305  integer(I4B), optional, intent(in) :: increment1
306  integer(I4B), optional, intent(in) :: increment2
307  ! -- local
308  integer(I4B) :: inc1, inc2, lb1, lb2, n1, n2
309  real(DP), allocatable, dimension(:, :) :: temp
310 
311  ! -- default to expanding both dimensions by 1
312  if (present(increment1)) then
313  inc1 = increment1
314  else
315  inc1 = 1
316  end if
317  if (present(increment2)) then
318  inc2 = increment2
319  else
320  inc2 = 1
321  end if
322  if (inc1 == 0 .and. inc2 == 0) return
323  if (inc1 < 0 .or. inc2 < 0) &
324  call pstop(1, "increments must be nonnegative")
325 
326  ! -- expand array to the requested size, keeping
327  ! existing items and the existing lower bound,
328  ! or allocate the array if still unallocated
329  if (allocated(array)) then
330  lb1 = lbound(array, 1)
331  lb2 = lbound(array, 2)
332  n1 = size(array, 1)
333  n2 = size(array, 2)
334  allocate (temp( &
335  lb1:(lb1 + n1 + inc1 - 1), &
336  lb2:(lb2 + n2 + inc2 - 1)))
337  temp( &
338  lb1:(lb1 + n1 - 1), &
339  lb2:(lb2 + n2 - 1)) = array
340  deallocate (array)
341  call move_alloc(temp, array)
342  else
343  allocate (array(inc1, inc2))
344  end if
345 

◆ expand_integer()

subroutine arrayhandlersmodule::expand_integer ( integer(i4b), dimension(:), intent(inout), allocatable  array,
integer(i4b), intent(in), optional  increment 
)
private

Definition at line 107 of file ArrayHandlers.f90.

108  ! -- dummy
109  integer(I4B), allocatable, intent(inout) :: array(:)
110  integer(I4B), optional, intent(in) :: increment
111  ! -- local
112  integer(I4B) :: inc, lb, n
113  integer(I4B), allocatable, dimension(:) :: temp
114 
115  ! -- default to expanding by 1
116  if (present(increment)) then
117  inc = increment
118  if (inc == 0) return
119  if (inc < 0) call pstop(1, "increment must be nonnegative")
120  else
121  inc = 1
122  end if
123 
124  ! -- expand array to the requested size, keeping
125  ! existing items and the existing lower bound,
126  ! or allocate the array if still unallocated
127  if (allocated(array)) then
128  lb = lbound(array, 1)
129  n = size(array)
130  allocate (temp(lb:(lb + n + inc - 1)))
131  temp(lb:(lb + n - 1)) = array
132  deallocate (array)
133  call move_alloc(temp, array)
134  else
135  allocate (array(inc))
136  end if

◆ expand_integer_2d()

subroutine arrayhandlersmodule::expand_integer_2d ( integer(i4b), dimension(:, :), intent(inout), allocatable  array,
integer(i4b), intent(in), optional  increment1,
integer(i4b), intent(in), optional  increment2 
)
private

Definition at line 256 of file ArrayHandlers.f90.

257  ! -- dummy
258  integer(I4B), allocatable, intent(inout) :: array(:, :)
259  integer(I4B), optional, intent(in) :: increment1
260  integer(I4B), optional, intent(in) :: increment2
261  ! -- local
262  integer(I4B) :: inc1, inc2, lb1, lb2, n1, n2
263  integer(I4B), allocatable, dimension(:, :) :: temp
264 
265  ! -- default to expanding both dimensions by 1
266  if (present(increment1)) then
267  inc1 = increment1
268  else
269  inc1 = 1
270  end if
271  if (present(increment2)) then
272  inc2 = increment2
273  else
274  inc2 = 1
275  end if
276  if (inc1 == 0 .and. inc2 == 0) return
277  if (inc1 < 0 .or. inc2 < 0) &
278  call pstop(1, "increments must be nonnegative")
279 
280  ! -- expand array to the requested size, keeping
281  ! existing items and the existing lower bound,
282  ! or allocate the array if still unallocated
283  if (allocated(array)) then
284  lb1 = lbound(array, 1)
285  lb2 = lbound(array, 2)
286  n1 = size(array, 1)
287  n2 = size(array, 2)
288  allocate (temp( &
289  lb1:(lb1 + n1 + inc1 - 1), &
290  lb2:(lb2 + n2 + inc2 - 1)))
291  temp( &
292  lb1:(lb1 + n1 - 1), &
293  lb2:(lb2 + n2 - 1)) = array
294  deallocate (array)
295  call move_alloc(temp, array)
296  else
297  allocate (array(inc1, inc2))
298  end if
299 

◆ expand_integer_wrapper()

subroutine arrayhandlersmodule::expand_integer_wrapper ( integer(i4b), intent(in)  nsize,
integer(i4b), dimension(:), intent(inout), allocatable  array,
integer(i4b), intent(in), optional  minvalue,
logical(lgp), intent(in), optional  loginc 
)
private

Definition at line 50 of file ArrayHandlers.f90.

51  ! -- dummy
52  integer(I4B), intent(in) :: nsize
53  integer(I4B), allocatable, intent(inout) :: array(:)
54  integer(I4B), intent(in), optional :: minvalue
55  logical(LGP), intent(in), optional :: loginc
56  ! -- local
57  logical(LGP) :: log_increment
58  integer(I4B) :: minimum_increment
59  integer(I4B) :: increment
60  integer(I4B) :: isize
61  integer(I4B) :: n
62  !
63  ! -- process optional variables
64  if (present(minvalue)) then
65  minimum_increment = minvalue
66  else
67  minimum_increment = 100
68  end if
69  if (present(loginc)) then
70  log_increment = loginc
71  else
72  log_increment = .false.
73  end if
74  !
75  ! -- determine current size of the array
76  isize = size(array)
77  !
78  ! -- expand the array if necessary
79  if (nsize > isize) then
80  !
81  ! -- increase array size by 1, 10, 100, 1000, etc.
82  ! from 1 to 9, 10 to 99, 100 to 999, 1000 to 10000, etc.
83  if (loginc) then
84  increment = int(log10(real(nsize, dp)), i4b)
85  increment = int(dten**increment, i4b)
86  !
87  ! -- increase increment by a multiplier and a value no
88  ! smaller than a default or specified minimum size
89  else
90  increment = int(nsize * 0.2_dp)
91  increment = max(minimum_increment, increment)
92  end if
93  !
94  ! -- expand the array
95  call expandarray(array, increment)
96  !
97  ! -- initialize expanded array elements
98  do n = isize + 1, size(array)
99  array(n) = 0
100  end do
101  end if
102 

◆ expand_logical()

subroutine arrayhandlersmodule::expand_logical ( logical(lgp), dimension(:), intent(inout), allocatable  array,
integer(i4b), intent(in), optional  increment 
)
private

Definition at line 172 of file ArrayHandlers.f90.

173  ! -- dummy
174  logical(LGP), allocatable, intent(inout) :: array(:)
175  integer(I4B), optional, intent(in) :: increment
176  ! -- local
177  integer(I4B) :: inc, lb, n
178  logical(LGP), allocatable, dimension(:) :: temp
179 
180  ! -- default to expanding by 1
181  if (present(increment)) then
182  inc = increment
183  if (inc == 0) return
184  if (inc < 0) call pstop(1, "increment must be nonnegative")
185  else
186  inc = 1
187  end if
188 
189  ! -- expand array to the requested size, keeping
190  ! existing items and the existing lower bound,
191  ! or allocate the array if still unallocated
192  if (allocated(array)) then
193  lb = lbound(array, 1)
194  n = size(array)
195  allocate (temp(lb:(lb + n + inc - 1)))
196  temp(lb:(lb + n - 1)) = array
197  deallocate (array)
198  call move_alloc(temp, array)
199  else
200  allocate (array(inc))
201  end if
202 

◆ extend_double()

subroutine arrayhandlersmodule::extend_double ( real(dp), dimension(:), intent(inout), pointer, contiguous  array,
integer(i4b), intent(in), optional  increment 
)
private

Definition at line 350 of file ArrayHandlers.f90.

351  ! -- dummy
352  real(DP), dimension(:), pointer, contiguous, intent(inout) :: array
353  integer(I4B), optional, intent(in) :: increment
354  ! -- local
355  character(len=100) :: ermsg
356  integer(I4B) :: i, inc, lb, n, istat
357  real(DP), dimension(:), pointer, contiguous :: temp => null()
358 
359  ! -- default to expanding by 1
360  if (present(increment)) then
361  inc = increment
362  if (inc == 0) return
363  if (inc < 0) call pstop(1, "increment must be nonnegative")
364  else
365  inc = 1
366  end if
367 
368  ! -- expand array to the requested size, keeping
369  ! existing items and the existing lower bound,
370  ! or allocate the array if still unallocated
371  if (associated(array)) then
372  lb = lbound(array, 1)
373  n = size(array)
374  allocate (temp(lb:(lb + n + inc - 1)), stat=istat, errmsg=ermsg)
375  if (istat /= 0) &
376  call pstop(138, 'Error in ArrayHandlersModule, '// &
377  'could not increase array size:'//ermsg)
378  do i = lb, lb + n - 1
379  temp(i) = array(i)
380  end do
381  deallocate (array)
382  array => temp
383  else
384  allocate (array(inc))
385  end if
386 

◆ extend_integer()

subroutine arrayhandlersmodule::extend_integer ( integer(i4b), dimension(:), intent(inout), pointer, contiguous  array,
integer(i4b), intent(in), optional  increment 
)
private

Definition at line 389 of file ArrayHandlers.f90.

390  ! -- dummy
391  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: array
392  integer(I4B), optional, intent(in) :: increment
393  ! -- local
394  character(len=100) :: ermsg
395  integer(I4B) :: i, inc, lb, n, istat
396  integer(I4B), dimension(:), pointer, contiguous :: temp => null()
397 
398  ! -- default to expanding by 1
399  if (present(increment)) then
400  inc = increment
401  if (inc == 0) return
402  if (inc < 0) call pstop(1, "increment must be nonnegative")
403  else
404  inc = 1
405  end if
406 
407  ! -- expand array to the requested size, keeping
408  ! existing items and the existing lower bound,
409  ! or allocate the array if still unallocated
410  if (associated(array)) then
411  lb = lbound(array, 1)
412  n = size(array)
413  allocate (temp(lb:(lb + n + inc - 1)), stat=istat, errmsg=ermsg)
414  if (istat /= 0) &
415  call pstop(138, 'Error in ArrayHandlersModule, '// &
416  'could not increase array size:'//ermsg)
417  do i = lb, lb + n - 1
418  temp(i) = array(i)
419  end do
420  deallocate (array)
421  array => temp
422  else
423  allocate (array(inc))
424  end if
425 

◆ extend_string()

subroutine arrayhandlersmodule::extend_string ( character(len=*), dimension(:), pointer, contiguous  array,
integer(i4b), optional  increment 
)
private

Definition at line 428 of file ArrayHandlers.f90.

429  ! -- dummy
430  character(len=*), dimension(:), pointer, contiguous :: array
431  integer(I4B), optional :: increment
432  ! -- local
433  integer(I4B) :: inc, i, n
434  character(len=len(array)), dimension(:), pointer, contiguous :: temp
435 
436  if (present(increment)) then
437  inc = increment
438  if (inc == 0) return
439  if (inc < 0) call pstop(1, "increment must be nonnegative")
440  else
441  inc = 1
442  end if
443 
444  if (associated(array)) then
445  n = size(array)
446  temp => array
447  allocate (array(n + inc))
448  do i = 1, n
449  array(i) = temp(i)
450  end do
451  deallocate (temp)
452  else
453  allocate (array(inc))
454  end if
455 

◆ ifind_character()

integer(i4b) function arrayhandlersmodule::ifind_character ( character(len=*), dimension(:)  array,
character(len=*)  str 
)
private

Definition at line 473 of file ArrayHandlers.f90.

474  ! -- return
475  integer(I4B) :: ifind_character
476  ! -- dummy
477  character(len=*), dimension(:) :: array
478  character(len=*) :: str
479  ! -- local
480  integer(I4B) :: i
481 
482  ifind_character = -1
483  findloop: do i = 1, size(array)
484  if (array(i) == str) then
485  ifind_character = i
486  exit findloop
487  end if
488  end do findloop
Here is the caller graph for this function:

◆ ifind_integer()

integer(i4b) function arrayhandlersmodule::ifind_integer ( integer(i4b), dimension(:)  iarray,
integer(i4b)  ival 
)
private

Definition at line 492 of file ArrayHandlers.f90.

493  ! -- return
494  integer(I4B) :: ifind_integer
495  ! -- dummy
496  integer(I4B), dimension(:) :: iarray
497  integer(I4B) :: ival
498  ! -- local
499  integer(I4B) :: i
500 
501  ifind_integer = -1
502  findloop: do i = 1, size(iarray)
503  if (iarray(i) == ival) then
504  ifind_integer = i
505  exit findloop
506  end if
507  end do findloop
Here is the caller graph for this function:

◆ remove_character()

subroutine, public arrayhandlersmodule::remove_character ( character(len=*), dimension(:), intent(inout), allocatable  array,
integer(i4b), intent(in)  ipos 
)

Definition at line 511 of file ArrayHandlers.f90.

512  ! -- dummy
513  character(len=*), allocatable, intent(inout) :: array(:)
514  integer(I4B), intent(in) :: ipos
515  ! -- local
516  character(len=MAXCHARLEN), allocatable, dimension(:) :: temp
517  integer(I4B) :: i, inew, n
518 
519  ! -- check character length
520  if (len(array) > maxcharlen) &
521  call pstop(138, 'Error in ArrayHandlersModule: '// &
522  'Need to increase MAXCHARLEN. Stopping...')
523 
524  ! -- calculate size
525  n = size(array)
526 
527  ! -- copy array to temp
528  allocate (temp(n))
529  do i = 1, n
530  temp(i) = array(i)
531  end do
532 
533  ! -- de/reallocate and copy back to array,
534  ! omitting the specified element
535  deallocate (array)
536  allocate (array(n - 1))
537  inew = 1
538  do i = 1, n
539  if (i /= ipos) then
540  array(inew) = temp(i)
541  inew = inew + 1
542  end if
543  end do
544  deallocate (temp)
545 
Here is the call graph for this function: