27 is_optional, chunksizes)
29 class(fmsnetcdffile_t),
intent(inout) :: fileobj
30 character(len=*),
intent(in) :: variable_name
31 class(*),
intent(in),
target :: vdata
33 character(len=*),
dimension(1),
intent(in),
optional :: dimensions
34 logical,
intent(in),
optional :: is_optional
36 integer,
intent(in),
optional :: chunksizes(:)
39 character(len=8) :: buf
41 if (fileobj%is_readonly .and.
present(is_optional))
then
42 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
46 call add_restart_var_to_array(fileobj, variable_name)
47 fileobj%restart_vars(fileobj%num_restart_vars)%data0d => vdata
48 if (.not. fileobj%is_readonly)
then
49 call get_data_type_string(vdata, buf)
50 if (
present(dimensions))
then
51 if (.not. is_dimension_unlimited(fileobj, dimensions(1), .true.))
then
52 call error(
"a scalar input variable can only have an unlimited dimension.")
55 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
56 chunksizes=chunksizes)
63 dimensions, is_optional, &
65 type(fmsnetcdffile_t),
intent(inout) :: fileobj
66 character(len=*),
intent(in) :: variable_name
67 class(*),
intent(in),
target :: vdata
69 character(len=*),
dimension(1),
intent(in),
optional :: dimensions
70 logical,
intent(in),
optional :: is_optional
72 integer,
intent(in),
optional :: chunksizes(:)
76 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
77 chunksizes=chunksizes)
83 dimensions, is_optional, &
85 class(fmsnetcdffile_t),
intent(inout) :: fileobj
86 character(len=*),
intent(in) :: variable_name
87 class(*),
dimension(:),
intent(in),
target :: vdata
89 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
90 logical,
intent(in),
optional :: is_optional
92 integer,
intent(in),
optional :: chunksizes(:)
95 character(len=8) :: buf
99 if (fileobj%is_readonly .and.
present(is_optional))
then
100 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
104 call add_restart_var_to_array(fileobj, variable_name)
105 fileobj%restart_vars(fileobj%num_restart_vars)%data1d => vdata
106 if (.not. fileobj%is_readonly)
then
107 call get_data_type_string(vdata, buf)
108 if (.not.
present(dimensions))
then
109 call error(
"dimension names required if the file is not read-only.")
111 ndims =
size(dimensions)
112 vdata_rank =
size(shape(vdata))
113 if (ndims .eq. vdata_rank+1)
then
114 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
115 call error(
"the slowest dimension must be unlimited.")
117 elseif (ndims .ne. vdata_rank)
then
118 call error(
"rank mismatch between vdata and dimensions arrays.")
120 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
121 chunksizes=chunksizes)
128 dimensions, is_optional, &
130 type(fmsnetcdffile_t),
intent(inout) :: fileobj
131 character(len=*),
intent(in) :: variable_name
132 class(*),
dimension(:),
intent(in),
target :: vdata
134 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
135 logical,
intent(in),
optional :: is_optional
137 integer,
intent(in),
optional :: chunksizes(:)
141 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
142 chunksizes=chunksizes)
148 dimensions, is_optional, &
150 class(fmsnetcdffile_t),
intent(inout) :: fileobj
151 character(len=*),
intent(in) :: variable_name
152 class(*),
dimension(:,:),
intent(in),
target :: vdata
154 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
155 logical,
intent(in),
optional :: is_optional
157 integer,
intent(in),
optional :: chunksizes(:)
160 character(len=8) :: buf
162 integer :: vdata_rank
164 if (fileobj%is_readonly .and.
present(is_optional))
then
165 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
169 call add_restart_var_to_array(fileobj, variable_name)
170 fileobj%restart_vars(fileobj%num_restart_vars)%data2d => vdata
171 if (.not. fileobj%is_readonly)
then
172 call get_data_type_string(vdata, buf)
173 if (.not.
present(dimensions))
then
174 call error(
"dimension names required if the file is not read-only.")
176 ndims =
size(dimensions)
177 vdata_rank =
size(shape(vdata))
178 if (ndims .eq. vdata_rank+1)
then
179 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
180 call error(
"the slowest dimension must be unlimited.")
182 elseif (ndims .ne. vdata_rank)
then
183 call error(
"rank mismatch between vdata and dimensions arrays.")
185 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
186 chunksizes=chunksizes)
193 dimensions, is_optional, &
195 type(fmsnetcdffile_t),
intent(inout) :: fileobj
196 character(len=*),
intent(in) :: variable_name
197 class(*),
dimension(:,:),
intent(in),
target :: vdata
199 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
200 logical,
intent(in),
optional :: is_optional
202 integer,
intent(in),
optional :: chunksizes(:)
206 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
207 chunksizes=chunksizes)
213 dimensions, is_optional, &
215 class(fmsnetcdffile_t),
intent(inout) :: fileobj
216 character(len=*),
intent(in) :: variable_name
217 class(*),
dimension(:,:,:),
intent(in),
target :: vdata
219 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
220 logical,
intent(in),
optional :: is_optional
222 integer,
intent(in),
optional :: chunksizes(:)
225 character(len=8) :: buf
227 integer :: vdata_rank
229 if (fileobj%is_readonly .and.
present(is_optional))
then
230 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
234 call add_restart_var_to_array(fileobj, variable_name)
235 fileobj%restart_vars(fileobj%num_restart_vars)%data3d => vdata
236 if (.not. fileobj%is_readonly)
then
237 call get_data_type_string(vdata, buf)
238 if (.not.
present(dimensions))
then
239 call error(
"dimension names required if the file is not read-only.")
241 ndims =
size(dimensions)
242 vdata_rank =
size(shape(vdata))
243 if (ndims .eq. vdata_rank+1)
then
244 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
245 call error(
"the slowest dimension must be unlimited.")
247 elseif (ndims .ne. vdata_rank)
then
248 call error(
"rank mismatch between vdata and dimensions arrays.")
250 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
251 chunksizes=chunksizes)
258 dimensions, is_optional, &
260 type(fmsnetcdffile_t),
intent(inout) :: fileobj
261 character(len=*),
intent(in) :: variable_name
262 class(*),
dimension(:,:,:),
intent(in),
target :: vdata
264 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
265 logical,
intent(in),
optional :: is_optional
267 integer,
intent(in),
optional :: chunksizes(:)
271 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
272 chunksizes=chunksizes)
278 dimensions, is_optional, &
280 class(fmsnetcdffile_t),
intent(inout) :: fileobj
281 character(len=*),
intent(in) :: variable_name
282 class(*),
dimension(:,:,:,:),
intent(in),
target :: vdata
284 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
285 logical,
intent(in),
optional :: is_optional
287 integer,
intent(in),
optional :: chunksizes(:)
290 character(len=8) :: buf
292 integer :: vdata_rank
294 if (fileobj%is_readonly .and.
present(is_optional))
then
295 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
299 call add_restart_var_to_array(fileobj, variable_name)
300 fileobj%restart_vars(fileobj%num_restart_vars)%data4d => vdata
301 if (.not. fileobj%is_readonly)
then
302 call get_data_type_string(vdata, buf)
303 if (.not.
present(dimensions))
then
304 call error(
"dimension names required if the file is not read-only.")
306 ndims =
size(dimensions)
307 vdata_rank =
size(shape(vdata))
308 if (ndims .eq. vdata_rank+1)
then
309 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
310 call error(
"the slowest dimension must be unlimited.")
312 elseif (ndims .ne. vdata_rank)
then
313 call error(
"rank mismatch between vdata and dimensions arrays.")
315 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
316 chunksizes=chunksizes)
323 dimensions, is_optional, &
325 type(fmsnetcdffile_t),
intent(inout) :: fileobj
326 character(len=*),
intent(in) :: variable_name
327 class(*),
dimension(:,:,:,:),
intent(in),
target :: vdata
329 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
330 logical,
intent(in),
optional :: is_optional
332 integer,
intent(in),
optional :: chunksizes(:)
336 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
337 chunksizes=chunksizes)
343 dimensions, is_optional, &
345 class(fmsnetcdffile_t),
intent(inout) :: fileobj
346 character(len=*),
intent(in) :: variable_name
347 class(*),
dimension(:,:,:,:,:),
intent(in),
target :: vdata
349 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
350 logical,
intent(in),
optional :: is_optional
352 integer,
intent(in),
optional :: chunksizes(:)
355 character(len=8) :: buf
357 integer :: vdata_rank
359 if (fileobj%is_readonly .and.
present(is_optional))
then
360 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
364 call add_restart_var_to_array(fileobj, variable_name)
365 fileobj%restart_vars(fileobj%num_restart_vars)%data5d => vdata
366 if (.not. fileobj%is_readonly)
then
367 call get_data_type_string(vdata, buf)
368 if (.not.
present(dimensions))
then
369 call error(
"dimension names required if the file is not read-only.")
371 ndims =
size(dimensions)
372 vdata_rank =
size(shape(vdata))
373 if (ndims .eq. vdata_rank+1)
then
374 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
375 call error(
"the slowest dimension must be unlimited.")
377 elseif (ndims .ne. vdata_rank)
then
378 call error(
"rank mismatch between vdata and dimensions arrays.")
380 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
381 chunksizes=chunksizes)
388 dimensions, is_optional, &
390 type(fmsnetcdffile_t),
intent(inout) :: fileobj
391 character(len=*),
intent(in) :: variable_name
392 class(*),
dimension(:,:,:,:,:),
intent(in),
target :: vdata
394 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
395 logical,
intent(in),
optional :: is_optional
397 integer,
intent(in),
optional :: chunksizes(:)
401 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
402 chunksizes=chunksizes)
407 x_halo, y_halo, jshift, ishift, is_optional)
408 type(fmsnetcdffile_t),
intent(inout) :: fileobj
409 character(len=*),
intent(in) :: variable_name
410 class(*),
dimension(:,:),
intent(in),
target :: vdata
411 integer,
dimension(4),
intent(in) :: indices
413 integer,
dimension(:),
intent(in) :: global_size
414 integer,
dimension(:),
intent(in) :: pelist
416 logical,
intent(in) :: is_root_pe
418 integer,
intent(in),
optional :: x_halo
419 integer,
intent(in),
optional :: y_halo
420 integer,
intent(in),
optional :: jshift
421 integer,
intent(in),
optional :: ishift
422 logical,
intent(in),
optional :: is_optional
425 integer :: current_var
426 character(len=7) :: dimnames(4)
429 if (fileobj%is_readonly .and.
present(is_optional))
then
430 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
436 call set_dimensions(fileobj, fileobj%bc_dimensions, dimnames, global_size)
440 current_var = fileobj%num_restart_vars
441 fileobj%restart_vars(current_var)%is_bc_variable = .true.
442 fileobj%restart_vars(current_var)%bc_info%is_root_pe = is_root_pe
444 allocate(fileobj%restart_vars(current_var)%bc_info%indices(4))
445 fileobj%restart_vars(current_var)%bc_info%indices = indices
447 allocate(fileobj%restart_vars(current_var)%bc_info%global_size(2))
448 fileobj%restart_vars(current_var)%bc_info%global_size = global_size
450 if (any(fileobj%io_root .eq. pelist(:)))
then
451 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)))
452 fileobj%restart_vars(current_var)%bc_info%pelist = pelist
453 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .true.
455 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)+1))
456 fileobj%restart_vars(current_var)%bc_info%pelist = (/ fileobj%io_root, pelist(:) /)
457 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .false.
460 fileobj%restart_vars(current_var)%bc_info%x_halo = 0
461 fileobj%restart_vars(current_var)%bc_info%y_halo = 0
462 fileobj%restart_vars(current_var)%bc_info%ishift = 0
463 fileobj%restart_vars(current_var)%bc_info%jshift = 0
465 if (
present(x_halo)) fileobj%restart_vars(current_var)%bc_info%x_halo = x_halo
466 if (
present(y_halo)) fileobj%restart_vars(current_var)%bc_info%y_halo = y_halo
467 if (
present(ishift)) fileobj%restart_vars(current_var)%bc_info%ishift = ishift
468 if (
present(jshift)) fileobj%restart_vars(current_var)%bc_info%jshift = jshift
474 x_halo, y_halo, jshift, ishift, is_optional)
475 type(fmsnetcdffile_t),
intent(inout) :: fileobj
476 character(len=*),
intent(in) :: variable_name
477 class(*),
dimension(:,:,:),
intent(in),
target :: vdata
478 integer,
dimension(4),
intent(in) :: indices
480 integer,
dimension(:),
intent(in) :: global_size
482 integer,
dimension(:),
intent(in) :: pelist
484 logical,
intent(in) :: is_root_pe
486 integer,
intent(in),
optional :: x_halo
487 integer,
intent(in),
optional :: y_halo
488 integer,
intent(in),
optional :: jshift
489 integer,
intent(in),
optional :: ishift
490 logical,
intent(in),
optional :: is_optional
493 integer :: current_var
494 character(len=7) :: dimnames(4)
497 if (fileobj%is_readonly .and.
present(is_optional))
then
498 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
504 call set_dimensions(fileobj, fileobj%bc_dimensions, dimnames, global_size)
508 current_var = fileobj%num_restart_vars
509 fileobj%restart_vars(current_var)%is_bc_variable = .true.
510 fileobj%restart_vars(current_var)%bc_info%is_root_pe = is_root_pe
512 allocate(fileobj%restart_vars(current_var)%bc_info%indices(4))
513 fileobj%restart_vars(current_var)%bc_info%indices = indices
515 allocate(fileobj%restart_vars(current_var)%bc_info%global_size(3))
516 fileobj%restart_vars(current_var)%bc_info%global_size = global_size
518 if (any(fileobj%io_root .eq. pelist(:)))
then
519 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)))
520 fileobj%restart_vars(current_var)%bc_info%pelist = pelist
521 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .true.
523 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)+1))
524 fileobj%restart_vars(current_var)%bc_info%pelist = (/ fileobj%io_root, pelist(:) /)
525 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .false.
528 fileobj%restart_vars(current_var)%bc_info%x_halo = 0
529 fileobj%restart_vars(current_var)%bc_info%y_halo = 0
530 fileobj%restart_vars(current_var)%bc_info%ishift = 0
531 fileobj%restart_vars(current_var)%bc_info%jshift = 0
533 if (
present(x_halo)) fileobj%restart_vars(current_var)%bc_info%x_halo = x_halo
534 if (
present(y_halo)) fileobj%restart_vars(current_var)%bc_info%y_halo = y_halo
535 if (
present(ishift)) fileobj%restart_vars(current_var)%bc_info%ishift = ishift
536 if (
present(jshift)) fileobj%restart_vars(current_var)%bc_info%jshift = jshift
543 type(fmsnetcdffile_t),
intent(inout) :: fileobj
544 type(dimension_information),
intent(inout) :: bc_dimensions
545 character(len=7),
intent(inout) :: dimnames(4)
550 integer,
dimension(:),
intent(in) :: global_size
554 character(len=1) :: suffix
555 character(len=7) :: axisname
556 integer :: i, found_index
558 if (.not. dimension_exists(fileobj,
"Time"))
call netcdf_add_dimension(fileobj,
"Time", unlimited)
559 dimnames(
size(global_size)+1) =
"Time"
563 do i = 1, bc_dimensions%cur_dim_len(1)
564 if (bc_dimensions%xlen(i) .eq. global_size(1))
then
566 write(suffix,
'(I1)') i
567 axisname =
'xaxis_'//suffix
568 dimnames(1) = axisname
574 if (found_index .eq. 0)
then
575 bc_dimensions%cur_dim_len(1) = bc_dimensions%cur_dim_len(1) + 1
576 bc_dimensions%xlen(bc_dimensions%cur_dim_len(1)) = global_size(1)
577 write(suffix,
'(I1)') bc_dimensions%cur_dim_len(1)
578 axisname =
'xaxis_'//suffix
579 call netcdf_add_dimension(fileobj, axisname, global_size(1))
580 dimnames(1) = axisname
585 do i = 1, bc_dimensions%cur_dim_len(2)
586 if (bc_dimensions%ylen(i) .eq. global_size(2))
then
588 write(suffix,
'(I1)') i
589 axisname =
'yaxis_'//suffix
590 dimnames(2) = axisname
596 if (found_index .eq. 0)
then
597 bc_dimensions%cur_dim_len(2) = bc_dimensions%cur_dim_len(2) + 1
598 bc_dimensions%ylen(bc_dimensions%cur_dim_len(2)) = global_size(2)
599 write(suffix,
'(I1)') bc_dimensions%cur_dim_len(2)
600 axisname =
'yaxis_'//suffix
601 call netcdf_add_dimension(fileobj, axisname, global_size(2))
602 dimnames(2) = axisname
606 if (
size(global_size) .eq. 3)
then
609 do i = 1, bc_dimensions%cur_dim_len(3)
610 if (bc_dimensions%zlen(i) .eq. global_size(3))
then
612 write(suffix,
'(I1)') i
613 axisname =
'zaxis_'//suffix
614 dimnames(3) = axisname
620 if (found_index .eq. 0)
then
621 bc_dimensions%cur_dim_len(3) = bc_dimensions%cur_dim_len(3) + 1
622 bc_dimensions%zlen(bc_dimensions%cur_dim_len(3)) = global_size(3)
623 write(suffix,
'(I1)') bc_dimensions%cur_dim_len(3)
624 axisname =
'zaxis_'//suffix
625 call netcdf_add_dimension(fileobj, axisname, global_size(3))
626 dimnames(3) = axisname
subroutine netcdf_add_restart_variable_4d(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Add a restart variable to a netcdf file.
subroutine netcdf_add_restart_variable_0d(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Add a restart variable to a netcdf file.
subroutine set_dimensions(fileobj, bc_dimensions, dimnames, global_size)
Updates the dimension information (bc_dimensions) for the give fileobj and outputs the dimensions nam...
subroutine netcdf_add_restart_variable_3d(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Add a restart variable to a netcdf file.
subroutine netcdf_add_restart_variable_5d_wrap(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Wrapper to distinguish interfaces.
subroutine netcdf_add_restart_variable_1d_wrap(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Wrapper to distinguish interfaces.
subroutine netcdf_add_restart_variable_0d_wrap(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Wrapper to distinguish interfaces.
subroutine netcdf_add_restart_variable_3d_wrap(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Wrapper to distinguish interfaces.
subroutine netcdf_add_restart_variable_1d(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Add a restart variable to a netcdf file.
subroutine register_restart_region_3d(fileobj, variable_name, vdata, indices, global_size, pelist, is_root_pe, x_halo, y_halo, jshift, ishift, is_optional)
Registers a regional 3D variable and stores the information needed.
subroutine netcdf_add_restart_variable_2d(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Add a restart variable to a netcdf file.
subroutine netcdf_add_restart_variable_4d_wrap(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Wrapper to distinguish interfaces.
subroutine netcdf_add_restart_variable_5d(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Add a restart variable to a netcdf file.
subroutine netcdf_add_restart_variable_2d_wrap(fileobj, variable_name, vdata, dimensions, is_optional, chunksizes)
Wrapper to distinguish interfaces.
subroutine register_restart_region_2d(fileobj, variable_name, vdata, indices, global_size, pelist, is_root_pe, x_halo, y_halo, jshift, ishift, is_optional)
Registers a regional 2D variable and stores the information needed.