FV3 Bundle
ncdw_mresize.F90
Go to the documentation of this file.
8  use ncdw_climsg, only: &
9 #ifdef enable_action_msgs
10  nclayer_enable_action, nclayer_actionm, &
11 #endif
12 #ifdef _DEBUG_MEM_
13  nclayer_debug, &
14 #endif
15  nclayer_error
16 
17  implicit none
18 
19  contains
20  ! For all subroutines: update_acount_in specifies wheter to
21  ! update acount or not. By default, this is true. This is useful
22  ! for preallocation, when you aren't actually adding entries,
23  ! so you're just allocating ahead of time and NOT adding
24  ! elements, thus not adding to acount.
25 
26  ! nc_diag_metadata_resize - input integer(i_byte)
27  ! Corresponding NetCDF4 type: byte
28  subroutine nc_diag_metadata_resize_byte(addl_num_entries, update_acount_in)
29  integer(i_llong), intent(in) :: addl_num_entries
30  logical, intent(in), optional :: update_acount_in
31 
32  ! This is the Size Count index (sc_index) - we'll just set
33  ! this and then just change the variable we're altering
34  ! every time.
35  integer(i_long) :: sc_index
36  integer(i_long) :: sc_index_vi
37 
38  logical :: update_acount
39 
40  ! Assume true by default
41  if (.NOT. present(update_acount_in)) then
42  update_acount = .true.
43  else
44  update_acount = update_acount_in
45  end if
46 
47  ! Here, we increment the count by the number of additional entries,
48  ! and the size by that amount as well.
49  !
50  ! If we didn't allocate yet, we simply set the count to the number of
51  ! initial entries, and then allocate that number + our default
52  ! initialization amount. Our initial size is that number + the initial
53  ! amount.
54 
55  ! NLAYER_BYTE is located at the first index, 1.
56  ! sc_index_vi is just sc_index + 6, 6 being the number of single types
57  sc_index = 1
58  sc_index_vi = sc_index + 6
59 
60  if (allocated(diag_metadata_store%m_byte)) then
61  if (update_acount) diag_metadata_store%acount(sc_index) = diag_metadata_store%acount(sc_index) + addl_num_entries
62  if (diag_metadata_store%acount(sc_index) >= diag_metadata_store%asize(sc_index)) then
63 #ifdef ENABLE_ACTION_MSGS
64  if (nclayer_enable_action) then
65  call nclayer_actionm("nc_diag_metadata_resize_byte: doing reallocation!")
66  end if
67 #endif
68  call nc_diag_realloc(diag_metadata_store%m_byte, int8(addl_num_entries + (nlayer_default_ent * (nlayer_multi_base ** diag_metadata_store%alloc_m_multi(sc_index)))))
69  diag_metadata_store%asize(sc_index) = size(diag_metadata_store%m_byte)
70 
71  diag_metadata_store%alloc_m_multi(sc_index) = diag_metadata_store%alloc_m_multi(sc_index) + 1
72  end if
73  else
74  if (update_acount) diag_metadata_store%acount(sc_index) = addl_num_entries
75  allocate(diag_metadata_store%m_byte(addl_num_entries + nlayer_default_ent))
76  diag_metadata_store%asize(sc_index) = addl_num_entries + nlayer_default_ent
77  end if
78  end subroutine nc_diag_metadata_resize_byte
79 
80  ! nc_diag_metadata_resize - input integer(i_short)
81  ! Corresponding NetCDF4 type: short
82  subroutine nc_diag_metadata_resize_short(addl_num_entries, update_acount_in)
83  integer(i_llong), intent(in) :: addl_num_entries
84  logical, intent(in), optional :: update_acount_in
85 
86  ! This is the Size Count index (sc_index) - we'll just set
87  ! this and then just change the variable we're altering
88  ! every time.
89  integer(i_long) :: sc_index
90  integer(i_long) :: sc_index_vi
91 
92  logical :: update_acount
93 
94  ! Assume true by default
95  if (.NOT. present(update_acount_in)) then
96  update_acount = .true.
97  else
98  update_acount = update_acount_in
99  end if
100 
101  ! Here, we increment the count by the number of additional entries,
102  ! and the size by that amount as well.
103  !
104  ! If we didn't allocate yet, we simply set the count to the number of
105  ! initial entries, and then allocate that number + our default
106  ! initialization amount. Our initial size is that number + the initial
107  ! amount.
108 
109  ! NLAYER_SHORT is located at the second index, 2.
110  ! sc_index_vi is just sc_index + 6, 6 being the number of single types
111  sc_index = 2
112  sc_index_vi = sc_index + 6
113 
114  if (allocated(diag_metadata_store%m_short)) then
115  if (update_acount) diag_metadata_store%acount(sc_index) = diag_metadata_store%acount(sc_index) + addl_num_entries
116  if (diag_metadata_store%acount(sc_index) >= diag_metadata_store%asize(sc_index)) then
117 #ifdef ENABLE_ACTION_MSGS
118  if (nclayer_enable_action) then
119  call nclayer_actionm("nc_diag_metadata_resize_short: doing reallocation!")
120  end if
121 #endif
122  call nc_diag_realloc(diag_metadata_store%m_short, int8(addl_num_entries + (nlayer_default_ent * (nlayer_multi_base ** diag_metadata_store%alloc_m_multi(sc_index)))))
123  diag_metadata_store%asize(sc_index) = size(diag_metadata_store%m_short)
124 
125  diag_metadata_store%alloc_m_multi(sc_index) = diag_metadata_store%alloc_m_multi(sc_index) + 1
126  end if
127  else
128  if (update_acount) diag_metadata_store%acount(sc_index) = addl_num_entries
129  allocate(diag_metadata_store%m_short(addl_num_entries + nlayer_default_ent))
130  diag_metadata_store%asize(sc_index) = addl_num_entries + nlayer_default_ent
131  end if
132  end subroutine nc_diag_metadata_resize_short
133 
134  ! nc_diag_metadata_resize - input integer(i_long)
135  ! Corresponding NetCDF4 type: int (old: long)
136  subroutine nc_diag_metadata_resize_long(addl_num_entries, update_acount_in)
137  integer(i_llong), intent(in) :: addl_num_entries
138  logical, intent(in), optional :: update_acount_in
139 
140  ! Did we realloc at all?
141  !logical :: metadata_realloc
142 
143  ! This is the Size Count index (sc_index) - we'll just set
144  ! this and then just change the variable we're altering
145  ! every time.
146  integer(i_long) :: sc_index
147  integer(i_long) :: sc_index_vi
148 
149 #ifdef _DEBUG_MEM_
150  character(len=200) :: debugstr
151 #endif
152 
153  logical :: update_acount
154 
155  ! Assume true by default
156  if (.NOT. present(update_acount_in)) then
157  update_acount = .true.
158  else
159  update_acount = update_acount_in
160  end if
161 
162  ! Default is false - no realloc done.
163  !metadata_realloc = .FALSE.
164 
165  ! Here, we increment the count by the number of additional entries,
166  ! and the size by that amount as well.
167  !
168  ! If we didn't allocate yet, we simply set the count to the number of
169  ! initial entries, and then allocate that number + our default
170  ! initialization amount. Our initial size is that number + the initial
171  ! amount.
172 
173  ! NLAYER_LONG is located at the third index, 3.
174  ! sc_index_vi is just sc_index + 6, 6 being the number of single types
175  sc_index = 3
176  sc_index_vi = sc_index + 6
177 
178  if (allocated(diag_metadata_store%m_long)) then
179  if (update_acount) diag_metadata_store%acount(sc_index) = diag_metadata_store%acount(sc_index) + addl_num_entries
180 
181 #ifdef _DEBUG_MEM_
182  write (debugstr, "(A, I1, A, I7, A, I7)") "In sc_index ", sc_index, ", the acount/asize is: ", diag_metadata_store%acount(sc_index), "/", diag_metadata_store%asize(sc_index)
183  call nclayer_debug(debugstr)
184 #endif
185 
186  if (diag_metadata_store%acount(sc_index) >= diag_metadata_store%asize(sc_index)) then
187 #ifdef _DEBUG_MEM_
188  call nclayer_debug("acount < asize, reallocating.")
189  print *, "Start long realloc..."
190 #endif
191 #ifdef ENABLE_ACTION_MSGS
192  if (nclayer_enable_action) then
193  call nclayer_actionm("nc_diag_metadata_resize_long: doing reallocation!")
194  end if
195 #endif
196  call nc_diag_realloc(diag_metadata_store%m_long, int8(addl_num_entries + (nlayer_default_ent * (nlayer_multi_base ** diag_metadata_store%alloc_m_multi(sc_index)))))
197  diag_metadata_store%asize(sc_index) = size(diag_metadata_store%m_long)
198 
199  diag_metadata_store%alloc_m_multi(sc_index) = diag_metadata_store%alloc_m_multi(sc_index) + 1
200 
201 #ifdef _DEBUG_MEM_
202  print *, "alloc_m_multi increased to:"
203  print *, diag_metadata_store%alloc_m_multi(sc_index)
204 #endif
205  end if
206  else
207  if (update_acount) diag_metadata_store%acount(sc_index) = addl_num_entries
208  allocate(diag_metadata_store%m_long(addl_num_entries + nlayer_default_ent))
209  diag_metadata_store%asize(sc_index) = addl_num_entries + nlayer_default_ent
210  end if
211  end subroutine nc_diag_metadata_resize_long
212 
213  ! nc_diag_metadata_resize - input real(r_single)
214  ! Corresponding NetCDF4 type: float (or real)
215  subroutine nc_diag_metadata_resize_rsingle(addl_num_entries, update_acount_in)
216  integer(i_llong), intent(in) :: addl_num_entries
217  logical, intent(in), optional :: update_acount_in
218 
219  ! This is the Size Count index (sc_index) - we'll just set
220  ! this and then just change the variable we're altering
221  ! every time.
222  integer(i_long) :: sc_index
223  integer(i_long) :: sc_index_vi
224 
225  logical :: update_acount
226 
227  ! Assume true by default
228  if (.NOT. present(update_acount_in)) then
229  update_acount = .true.
230  else
231  update_acount = update_acount_in
232  end if
233 
234  ! Here, we increment the count by the number of additional entries,
235  ! and the size by that amount as well.
236  !
237  ! If we didn't allocate yet, we simply set the count to the number of
238  ! initial entries, and then allocate that number + our default
239  ! initialization amount. Our initial size is that number + the initial
240  ! amount.
241 
242  ! NLAYER_FLOAT is located at the fourth index, 4.
243  ! sc_index_vi is just sc_index + 6, 6 being the number of single types
244  sc_index = 4
245  sc_index_vi = sc_index + 6
246 
247  if (allocated(diag_metadata_store%m_rsingle)) then
248  if (update_acount) diag_metadata_store%acount(sc_index) = diag_metadata_store%acount(sc_index) + addl_num_entries
249  if (diag_metadata_store%acount(sc_index) >= diag_metadata_store%asize(sc_index)) then
250 #ifdef _DEBUG_MEM_
251  print *, "realloc needed for metadata rsingle!"
252  write (*, "(A, I0, A, I0, A)") "(size needed / size available: ", diag_metadata_store%acount(sc_index), " / ", diag_metadata_store%asize(sc_index), ")"
253 #endif
254 #ifdef ENABLE_ACTION_MSGS
255  if (nclayer_enable_action) then
256  call nclayer_actionm("nc_diag_metadata_resize_rsingle: doing reallocation!")
257  end if
258 #endif
259  call nc_diag_realloc(diag_metadata_store%m_rsingle, int8(addl_num_entries + (nlayer_default_ent * (nlayer_multi_base ** diag_metadata_store%alloc_m_multi(sc_index)))))
260  diag_metadata_store%asize(sc_index) = size(diag_metadata_store%m_rsingle)
261 
262  diag_metadata_store%alloc_m_multi(sc_index) = diag_metadata_store%alloc_m_multi(sc_index) + 1
263  end if
264  else
265  if (update_acount) diag_metadata_store%acount(sc_index) = addl_num_entries
266  allocate(diag_metadata_store%m_rsingle(addl_num_entries + nlayer_default_ent))
267  diag_metadata_store%asize(sc_index) = addl_num_entries + nlayer_default_ent
268  end if
269  end subroutine nc_diag_metadata_resize_rsingle
270 
271  ! nc_diag_metadata_resize - input real(r_double)
272  ! Corresponding NetCDF4 type: double
273  subroutine nc_diag_metadata_resize_rdouble(addl_num_entries, update_acount_in)
274  integer(i_llong), intent(in) :: addl_num_entries
275  logical, intent(in), optional :: update_acount_in
276 
277  ! This is the Size Count index (sc_index) - we'll just set
278  ! this and then just change the variable we're altering
279  ! every time.
280  integer(i_long) :: sc_index
281  integer(i_long) :: sc_index_vi
282 
283  logical :: update_acount
284 
285  ! Assume true by default
286  if (.NOT. present(update_acount_in)) then
287  update_acount = .true.
288  else
289  update_acount = update_acount_in
290  end if
291  ! Here, we increment the count by the number of additional entries,
292  ! and the size by that amount as well.
293  !
294  ! If we didn't allocate yet, we simply set the count to the number of
295  ! initial entries, and then allocate that number + our default
296  ! initialization amount. Our initial size is that number + the initial
297  ! amount.
298 
299  ! NLAYER_DOUBLE is located at the fifth index, 5.
300  ! sc_index_vi is just sc_index + 6, 6 being the number of single types
301  sc_index = 5
302  sc_index_vi = sc_index + 6
303 
304  if (allocated(diag_metadata_store%m_rdouble)) then
305  if (update_acount) diag_metadata_store%acount(sc_index) = diag_metadata_store%acount(sc_index) + addl_num_entries
306  if (diag_metadata_store%acount(sc_index) >= diag_metadata_store%asize(sc_index)) then
307 #ifdef ENABLE_ACTION_MSGS
308  if (nclayer_enable_action) then
309  call nclayer_actionm("nc_diag_metadata_resize_rdouble: doing reallocation!")
310  end if
311 #endif
312  call nc_diag_realloc(diag_metadata_store%m_rdouble, int8(addl_num_entries + (nlayer_default_ent * (nlayer_multi_base ** diag_metadata_store%alloc_m_multi(sc_index)))))
313  diag_metadata_store%asize(sc_index) = size(diag_metadata_store%m_rdouble)
314 
315  diag_metadata_store%alloc_m_multi(sc_index) = diag_metadata_store%alloc_m_multi(sc_index) + 1
316  end if
317  else
318  if (update_acount) diag_metadata_store%acount(sc_index) = addl_num_entries
319  allocate(diag_metadata_store%m_rdouble(addl_num_entries + nlayer_default_ent))
320  diag_metadata_store%asize(sc_index) = addl_num_entries + nlayer_default_ent
321  end if
322  end subroutine nc_diag_metadata_resize_rdouble
323 
324  ! nc_diag_metadata_resize - input character(len=*)
325  ! Corresponding NetCDF4 type: string? char?
326  subroutine nc_diag_metadata_resize_string(addl_num_entries, update_acount_in)
327  integer(i_llong), intent(in) :: addl_num_entries
328  logical, intent(in), optional :: update_acount_in
329 
330  ! This is the Size Count index (sc_index) - we'll just set
331  ! this and then just change the variable we're altering
332  ! every time.
333  integer(i_long) :: sc_index
334  integer(i_long) :: sc_index_vi
335 
336  logical :: update_acount
337 
338  ! Assume true by default
339  if (.NOT. present(update_acount_in)) then
340  update_acount = .true.
341  else
342  update_acount = update_acount_in
343  end if
344  ! Here, we increment the count by the number of additional entries,
345  ! and the size by that amount as well.
346  !
347  ! If we didn't allocate yet, we simply set the count to the number of
348  ! initial entries, and then allocate that number + our default
349  ! initialization amount. Our initial size is that number + the initial
350  ! amount.
351 
352  ! NLAYER_BYTE is located at the sixth index, 6.
353  ! sc_index_vi is just sc_index + 6, 6 being the number of single types
354  sc_index = 6
355  sc_index_vi = sc_index + 6
356 
357  if (allocated(diag_metadata_store%m_string)) then
358  if (update_acount) diag_metadata_store%acount(sc_index) = diag_metadata_store%acount(sc_index) + addl_num_entries
359  if (diag_metadata_store%acount(sc_index) >= diag_metadata_store%asize(sc_index)) then
360 #ifdef ENABLE_ACTION_MSGS
361  if (nclayer_enable_action) then
362  call nclayer_actionm("nc_diag_metadata_resize_string: doing reallocation!")
363  end if
364 #endif
365  call nc_diag_realloc(diag_metadata_store%m_string, int8(addl_num_entries + (nlayer_default_ent * (nlayer_multi_base ** diag_metadata_store%alloc_m_multi(sc_index)))))
366  diag_metadata_store%asize(sc_index) = size(diag_metadata_store%m_string)
367 
368  diag_metadata_store%alloc_m_multi(sc_index) = diag_metadata_store%alloc_m_multi(sc_index) + 1
369  end if
370  else
371  if (update_acount) diag_metadata_store%acount(sc_index) = addl_num_entries
372  allocate(diag_metadata_store%m_string(addl_num_entries + nlayer_default_ent))
373  diag_metadata_store%asize(sc_index) = addl_num_entries + nlayer_default_ent
374  end if
375  end subroutine nc_diag_metadata_resize_string
376 
377  subroutine nc_diag_metadata_resize_iarr_type(addl_num_entries)
378  integer(i_llong), intent(in) :: addl_num_entries
379 
380  type(diag_md_iarr), dimension(:), allocatable :: tmp_stor_i_arr
381 
382 #ifdef ENABLE_ACTION_MSGS
383  if (nclayer_enable_action) then
384  call nclayer_actionm("nc_diag_metadata_resize_iarr_type: doing reallocation!")
385  end if
386 #endif
387 
388  ! We need to realloc ourselves here...
389  allocate(tmp_stor_i_arr(size(diag_metadata_store%stor_i_arr) + addl_num_entries))
390  tmp_stor_i_arr(1:size(diag_metadata_store%stor_i_arr)) = diag_metadata_store%stor_i_arr
391  deallocate(diag_metadata_store%stor_i_arr)
392  allocate(diag_metadata_store%stor_i_arr(size(tmp_stor_i_arr)))
393  diag_metadata_store%stor_i_arr = tmp_stor_i_arr
394  deallocate(tmp_stor_i_arr)
395  end subroutine nc_diag_metadata_resize_iarr_type
396 
397  subroutine nc_diag_metadata_resize_iarr(iarr_index, addl_num_entries, update_icount_in)
398  integer(i_long), intent(in) :: iarr_index
399  integer(i_llong), intent(in) :: addl_num_entries
400  logical, intent(in), optional :: update_icount_in
401 
402  logical :: update_icount
403 
404  integer(i_llong) :: addl_num_entries_r
405 
406  ! Assume true by default
407  if (.NOT. present(update_icount_in)) then
408  update_icount = .true.
409  else
410  update_icount = update_icount_in
411  end if
412 
413  if (allocated(diag_metadata_store%stor_i_arr(iarr_index)%index_arr)) then
414  if (update_icount) diag_metadata_store%stor_i_arr(iarr_index)%icount = &
415  diag_metadata_store%stor_i_arr(iarr_index)%icount + addl_num_entries
416  if (diag_metadata_store%stor_i_arr(iarr_index)%icount >= diag_metadata_store%stor_i_arr(iarr_index)%isize) then
417 #ifdef _DEBUG_MEM_
418  print *, "realloc needed for metadata iarr!"
419  write (*, "(A, I0, A, I0, A)") "(size needed / size available: ", diag_metadata_store%stor_i_arr(iarr_index)%icount, " / ", diag_metadata_store%stor_i_arr(iarr_index)%isize, ")"
420  print *, diag_metadata_store%alloc_sia_multi(iarr_index)
421  print *, int8(nlayer_multi_base ** int8(diag_metadata_store%alloc_sia_multi(iarr_index)))
422 #endif
423 #ifdef ENABLE_ACTION_MSGS
424  if (nclayer_enable_action) then
425  call nclayer_actionm("nc_diag_metadata_resize_iarr: doing reallocation!")
426  end if
427 #endif
428  if (update_icount) then
429  addl_num_entries_r = addl_num_entries + (int8(nlayer_default_ent) * (nlayer_multi_base ** int8(diag_metadata_store%alloc_sia_multi(iarr_index))))
430  else
431  addl_num_entries_r = addl_num_entries + nlayer_default_ent
432  end if
433 #ifdef _DEBUG_MEM_
434  print *, " ** addl_num_entries_r = "
435  print *, addl_num_entries_r
436 #endif
437  call nc_diag_realloc(diag_metadata_store%stor_i_arr(iarr_index)%index_arr, addl_num_entries_r)
438 
439 #ifdef _DEBUG_MEM_
440  print *, " ** realloc done"
441 #endif
442  diag_metadata_store%stor_i_arr(iarr_index)%isize = size(diag_metadata_store%stor_i_arr(iarr_index)%index_arr)
443 
444  if (update_icount) diag_metadata_store%alloc_sia_multi(iarr_index) = diag_metadata_store%alloc_sia_multi(iarr_index) + 1
445  end if
446  else
447  if (update_icount) diag_metadata_store%stor_i_arr(iarr_index)%icount = addl_num_entries
448  allocate(diag_metadata_store%stor_i_arr(iarr_index)%index_arr(addl_num_entries + nlayer_default_ent))
449  diag_metadata_store%stor_i_arr(iarr_index)%isize = addl_num_entries + nlayer_default_ent
450  end if
451  end subroutine nc_diag_metadata_resize_iarr
452 end module ncdw_mresize
subroutine nc_diag_metadata_resize_rdouble(addl_num_entries, update_acount_in)
integer(i_long), parameter nlayer_multi_base
Definition: ncdw_types.F90:27
integer, parameter, public i_byte
Definition: ncd_kinds.F90:45
type(diag_metadata), allocatable diag_metadata_store
Definition: ncdw_state.f90:17
integer, parameter, public i_long
Definition: ncd_kinds.F90:47
subroutine nc_diag_metadata_resize_rsingle(addl_num_entries, update_acount_in)
subroutine nc_diag_metadata_resize_string(addl_num_entries, update_acount_in)
subroutine nc_diag_metadata_resize_long(addl_num_entries, update_acount_in)
subroutine nc_diag_metadata_resize_iarr_type(addl_num_entries)
subroutine nc_diag_metadata_resize_byte(addl_num_entries, update_acount_in)
integer, parameter, public i_short
Definition: ncd_kinds.F90:46
subroutine nc_diag_metadata_resize_short(addl_num_entries, update_acount_in)
integer(i_short), parameter nlayer_default_ent
Definition: ncdw_types.F90:18
integer, parameter, public r_double
Definition: ncd_kinds.F90:80
integer, parameter, public r_single
Definition: ncd_kinds.F90:79
integer, parameter, public i_llong
Definition: ncd_kinds.F90:49
subroutine nc_diag_metadata_resize_iarr(iarr_index, addl_num_entries, update_icount_in)