28 is_optional, chunksizes)
30 class(fmsnetcdffile_t),
intent(inout) :: fileobj
31 character(len=*),
intent(in) :: variable_name
32 class(*),
intent(in),
target :: vdata
34 character(len=*),
dimension(1),
intent(in),
optional :: dimensions
35 logical,
intent(in),
optional :: is_optional
37 integer,
intent(in),
optional :: chunksizes(:)
40 character(len=8) :: buf
42 if (fileobj%is_readonly .and.
present(is_optional))
then
43 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
47 call add_restart_var_to_array(fileobj, variable_name)
48 fileobj%restart_vars(fileobj%num_restart_vars)%data0d => vdata
49 if (.not. fileobj%is_readonly)
then
50 call get_data_type_string(vdata, buf)
51 if (
present(dimensions))
then
52 if (.not. is_dimension_unlimited(fileobj, dimensions(1), .true.))
then
53 call error(
"a scalar input variable can only have an unlimited dimension.")
56 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
57 chunksizes=chunksizes)
64 dimensions, is_optional, &
66 type(fmsnetcdffile_t),
intent(inout) :: fileobj
67 character(len=*),
intent(in) :: variable_name
68 class(*),
intent(in),
target :: vdata
70 character(len=*),
dimension(1),
intent(in),
optional :: dimensions
71 logical,
intent(in),
optional :: is_optional
73 integer,
intent(in),
optional :: chunksizes(:)
77 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
78 chunksizes=chunksizes)
84 dimensions, is_optional, &
86 class(fmsnetcdffile_t),
intent(inout) :: fileobj
87 character(len=*),
intent(in) :: variable_name
88 class(*),
dimension(:),
intent(in),
target :: vdata
90 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
91 logical,
intent(in),
optional :: is_optional
93 integer,
intent(in),
optional :: chunksizes(:)
96 character(len=8) :: buf
100 if (fileobj%is_readonly .and.
present(is_optional))
then
101 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
105 call add_restart_var_to_array(fileobj, variable_name)
106 fileobj%restart_vars(fileobj%num_restart_vars)%data1d => vdata
107 if (.not. fileobj%is_readonly)
then
108 call get_data_type_string(vdata, buf)
109 if (.not.
present(dimensions))
then
110 call error(
"dimension names required if the file is not read-only.")
112 ndims =
size(dimensions)
113 vdata_rank =
size(shape(vdata))
114 if (ndims .eq. vdata_rank+1)
then
115 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
116 call error(
"the slowest dimension must be unlimited.")
118 elseif (ndims .ne. vdata_rank)
then
119 call error(
"rank mismatch between vdata and dimensions arrays.")
121 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
122 chunksizes=chunksizes)
129 dimensions, is_optional, &
131 type(fmsnetcdffile_t),
intent(inout) :: fileobj
132 character(len=*),
intent(in) :: variable_name
133 class(*),
dimension(:),
intent(in),
target :: vdata
135 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
136 logical,
intent(in),
optional :: is_optional
138 integer,
intent(in),
optional :: chunksizes(:)
142 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
143 chunksizes=chunksizes)
149 dimensions, is_optional, &
151 class(fmsnetcdffile_t),
intent(inout) :: fileobj
152 character(len=*),
intent(in) :: variable_name
153 class(*),
dimension(:,:),
intent(in),
target :: vdata
155 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
156 logical,
intent(in),
optional :: is_optional
158 integer,
intent(in),
optional :: chunksizes(:)
161 character(len=8) :: buf
163 integer :: vdata_rank
165 if (fileobj%is_readonly .and.
present(is_optional))
then
166 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
170 call add_restart_var_to_array(fileobj, variable_name)
171 fileobj%restart_vars(fileobj%num_restart_vars)%data2d => vdata
172 if (.not. fileobj%is_readonly)
then
173 call get_data_type_string(vdata, buf)
174 if (.not.
present(dimensions))
then
175 call error(
"dimension names required if the file is not read-only.")
177 ndims =
size(dimensions)
178 vdata_rank =
size(shape(vdata))
179 if (ndims .eq. vdata_rank+1)
then
180 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
181 call error(
"the slowest dimension must be unlimited.")
183 elseif (ndims .ne. vdata_rank)
then
184 call error(
"rank mismatch between vdata and dimensions arrays.")
186 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
187 chunksizes=chunksizes)
194 dimensions, is_optional, &
196 type(fmsnetcdffile_t),
intent(inout) :: fileobj
197 character(len=*),
intent(in) :: variable_name
198 class(*),
dimension(:,:),
intent(in),
target :: vdata
200 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
201 logical,
intent(in),
optional :: is_optional
203 integer,
intent(in),
optional :: chunksizes(:)
207 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
208 chunksizes=chunksizes)
214 dimensions, is_optional, &
216 class(fmsnetcdffile_t),
intent(inout) :: fileobj
217 character(len=*),
intent(in) :: variable_name
218 class(*),
dimension(:,:,:),
intent(in),
target :: vdata
220 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
221 logical,
intent(in),
optional :: is_optional
223 integer,
intent(in),
optional :: chunksizes(:)
226 character(len=8) :: buf
228 integer :: vdata_rank
230 if (fileobj%is_readonly .and.
present(is_optional))
then
231 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
235 call add_restart_var_to_array(fileobj, variable_name)
236 fileobj%restart_vars(fileobj%num_restart_vars)%data3d => vdata
237 if (.not. fileobj%is_readonly)
then
238 call get_data_type_string(vdata, buf)
239 if (.not.
present(dimensions))
then
240 call error(
"dimension names required if the file is not read-only.")
242 ndims =
size(dimensions)
243 vdata_rank =
size(shape(vdata))
244 if (ndims .eq. vdata_rank+1)
then
245 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
246 call error(
"the slowest dimension must be unlimited.")
248 elseif (ndims .ne. vdata_rank)
then
249 call error(
"rank mismatch between vdata and dimensions arrays.")
251 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
252 chunksizes=chunksizes)
259 dimensions, is_optional, &
261 type(fmsnetcdffile_t),
intent(inout) :: fileobj
262 character(len=*),
intent(in) :: variable_name
263 class(*),
dimension(:,:,:),
intent(in),
target :: vdata
265 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
266 logical,
intent(in),
optional :: is_optional
268 integer,
intent(in),
optional :: chunksizes(:)
272 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
273 chunksizes=chunksizes)
279 dimensions, is_optional, &
281 class(fmsnetcdffile_t),
intent(inout) :: fileobj
282 character(len=*),
intent(in) :: variable_name
283 class(*),
dimension(:,:,:,:),
intent(in),
target :: vdata
285 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
286 logical,
intent(in),
optional :: is_optional
288 integer,
intent(in),
optional :: chunksizes(:)
291 character(len=8) :: buf
293 integer :: vdata_rank
295 if (fileobj%is_readonly .and.
present(is_optional))
then
296 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
300 call add_restart_var_to_array(fileobj, variable_name)
301 fileobj%restart_vars(fileobj%num_restart_vars)%data4d => vdata
302 if (.not. fileobj%is_readonly)
then
303 call get_data_type_string(vdata, buf)
304 if (.not.
present(dimensions))
then
305 call error(
"dimension names required if the file is not read-only.")
307 ndims =
size(dimensions)
308 vdata_rank =
size(shape(vdata))
309 if (ndims .eq. vdata_rank+1)
then
310 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
311 call error(
"the slowest dimension must be unlimited.")
313 elseif (ndims .ne. vdata_rank)
then
314 call error(
"rank mismatch between vdata and dimensions arrays.")
316 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
317 chunksizes=chunksizes)
324 dimensions, is_optional, &
326 type(fmsnetcdffile_t),
intent(inout) :: fileobj
327 character(len=*),
intent(in) :: variable_name
328 class(*),
dimension(:,:,:,:),
intent(in),
target :: vdata
330 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
331 logical,
intent(in),
optional :: is_optional
333 integer,
intent(in),
optional :: chunksizes(:)
337 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
338 chunksizes=chunksizes)
344 dimensions, is_optional, &
346 class(fmsnetcdffile_t),
intent(inout) :: fileobj
347 character(len=*),
intent(in) :: variable_name
348 class(*),
dimension(:,:,:,:,:),
intent(in),
target :: vdata
350 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
351 logical,
intent(in),
optional :: is_optional
353 integer,
intent(in),
optional :: chunksizes(:)
356 character(len=8) :: buf
358 integer :: vdata_rank
360 if (fileobj%is_readonly .and.
present(is_optional))
then
361 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
365 call add_restart_var_to_array(fileobj, variable_name)
366 fileobj%restart_vars(fileobj%num_restart_vars)%data5d => vdata
367 if (.not. fileobj%is_readonly)
then
368 call get_data_type_string(vdata, buf)
369 if (.not.
present(dimensions))
then
370 call error(
"dimension names required if the file is not read-only.")
372 ndims =
size(dimensions)
373 vdata_rank =
size(shape(vdata))
374 if (ndims .eq. vdata_rank+1)
then
375 if (.not. is_dimension_unlimited(fileobj, dimensions(ndims), .true.))
then
376 call error(
"the slowest dimension must be unlimited.")
378 elseif (ndims .ne. vdata_rank)
then
379 call error(
"rank mismatch between vdata and dimensions arrays.")
381 call netcdf_add_variable(fileobj, variable_name, buf, dimensions, &
382 chunksizes=chunksizes)
389 dimensions, is_optional, &
391 type(fmsnetcdffile_t),
intent(inout) :: fileobj
392 character(len=*),
intent(in) :: variable_name
393 class(*),
dimension(:,:,:,:,:),
intent(in),
target :: vdata
395 character(len=*),
dimension(:),
intent(in),
optional :: dimensions
396 logical,
intent(in),
optional :: is_optional
398 integer,
intent(in),
optional :: chunksizes(:)
402 call netcdf_add_restart_variable(fileobj, variable_name, vdata, dimensions, is_optional, &
403 chunksizes=chunksizes)
408 x_halo, y_halo, jshift, ishift, is_optional)
409 type(fmsnetcdffile_t),
intent(inout) :: fileobj
410 character(len=*),
intent(in) :: variable_name
411 class(*),
dimension(:,:),
intent(in),
target :: vdata
412 integer,
dimension(4),
intent(in) :: indices
414 integer,
dimension(:),
intent(in) :: global_size
415 integer,
dimension(:),
intent(in) :: pelist
417 logical,
intent(in) :: is_root_pe
419 integer,
intent(in),
optional :: x_halo
420 integer,
intent(in),
optional :: y_halo
421 integer,
intent(in),
optional :: jshift
422 integer,
intent(in),
optional :: ishift
423 logical,
intent(in),
optional :: is_optional
426 integer :: current_var
427 character(len=7) :: dimnames(4)
430 if (fileobj%is_readonly .and.
present(is_optional))
then
431 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
437 call set_dimensions(fileobj, fileobj%bc_dimensions, dimnames, global_size)
441 current_var = fileobj%num_restart_vars
442 fileobj%restart_vars(current_var)%is_bc_variable = .true.
443 fileobj%restart_vars(current_var)%bc_info%is_root_pe = is_root_pe
445 allocate(fileobj%restart_vars(current_var)%bc_info%indices(4))
446 fileobj%restart_vars(current_var)%bc_info%indices = indices
448 allocate(fileobj%restart_vars(current_var)%bc_info%global_size(2))
449 fileobj%restart_vars(current_var)%bc_info%global_size = global_size
451 if (any(fileobj%io_root .eq. pelist(:)))
then
452 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)))
453 fileobj%restart_vars(current_var)%bc_info%pelist = pelist
454 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .true.
456 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)+1))
457 fileobj%restart_vars(current_var)%bc_info%pelist = (/ fileobj%io_root, pelist(:) /)
458 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .false.
461 fileobj%restart_vars(current_var)%bc_info%x_halo = 0
462 fileobj%restart_vars(current_var)%bc_info%y_halo = 0
463 fileobj%restart_vars(current_var)%bc_info%ishift = 0
464 fileobj%restart_vars(current_var)%bc_info%jshift = 0
466 if (
present(x_halo)) fileobj%restart_vars(current_var)%bc_info%x_halo = x_halo
467 if (
present(y_halo)) fileobj%restart_vars(current_var)%bc_info%y_halo = y_halo
468 if (
present(ishift)) fileobj%restart_vars(current_var)%bc_info%ishift = ishift
469 if (
present(jshift)) fileobj%restart_vars(current_var)%bc_info%jshift = jshift
475 x_halo, y_halo, jshift, ishift, is_optional)
476 type(fmsnetcdffile_t),
intent(inout) :: fileobj
477 character(len=*),
intent(in) :: variable_name
478 class(*),
dimension(:,:,:),
intent(in),
target :: vdata
479 integer,
dimension(4),
intent(in) :: indices
481 integer,
dimension(:),
intent(in) :: global_size
483 integer,
dimension(:),
intent(in) :: pelist
485 logical,
intent(in) :: is_root_pe
487 integer,
intent(in),
optional :: x_halo
488 integer,
intent(in),
optional :: y_halo
489 integer,
intent(in),
optional :: jshift
490 integer,
intent(in),
optional :: ishift
491 logical,
intent(in),
optional :: is_optional
494 integer :: current_var
495 character(len=7) :: dimnames(4)
498 if (fileobj%is_readonly .and.
present(is_optional))
then
499 if (is_optional .and. .not. variable_exists(fileobj, variable_name))
then
505 call set_dimensions(fileobj, fileobj%bc_dimensions, dimnames, global_size)
509 current_var = fileobj%num_restart_vars
510 fileobj%restart_vars(current_var)%is_bc_variable = .true.
511 fileobj%restart_vars(current_var)%bc_info%is_root_pe = is_root_pe
513 allocate(fileobj%restart_vars(current_var)%bc_info%indices(4))
514 fileobj%restart_vars(current_var)%bc_info%indices = indices
516 allocate(fileobj%restart_vars(current_var)%bc_info%global_size(3))
517 fileobj%restart_vars(current_var)%bc_info%global_size = global_size
519 if (any(fileobj%io_root .eq. pelist(:)))
then
520 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)))
521 fileobj%restart_vars(current_var)%bc_info%pelist = pelist
522 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .true.
524 allocate(fileobj%restart_vars(current_var)%bc_info%pelist(
size(pelist)+1))
525 fileobj%restart_vars(current_var)%bc_info%pelist = (/ fileobj%io_root, pelist(:) /)
526 fileobj%restart_vars(current_var)%bc_info%data_on_file_root = .false.
529 fileobj%restart_vars(current_var)%bc_info%x_halo = 0
530 fileobj%restart_vars(current_var)%bc_info%y_halo = 0
531 fileobj%restart_vars(current_var)%bc_info%ishift = 0
532 fileobj%restart_vars(current_var)%bc_info%jshift = 0
534 if (
present(x_halo)) fileobj%restart_vars(current_var)%bc_info%x_halo = x_halo
535 if (
present(y_halo)) fileobj%restart_vars(current_var)%bc_info%y_halo = y_halo
536 if (
present(ishift)) fileobj%restart_vars(current_var)%bc_info%ishift = ishift
537 if (
present(jshift)) fileobj%restart_vars(current_var)%bc_info%jshift = jshift
544 type(fmsnetcdffile_t),
intent(inout) :: fileobj
545 type(dimension_information),
intent(inout) :: bc_dimensions
546 character(len=7),
intent(inout) :: dimnames(4)
551 integer,
dimension(:),
intent(in) :: global_size
555 character(len=1) :: suffix
556 character(len=7) :: axisname
557 integer :: i, found_index
559 if (.not. dimension_exists(fileobj,
"Time"))
call netcdf_add_dimension(fileobj,
"Time", unlimited)
560 dimnames(
size(global_size)+1) =
"Time"
564 do i = 1, bc_dimensions%cur_dim_len(1)
565 if (bc_dimensions%xlen(i) .eq. global_size(1))
then
567 write(suffix,
'(I1)') i
568 axisname =
'xaxis_'//suffix
569 dimnames(1) = axisname
575 if (found_index .eq. 0)
then
576 bc_dimensions%cur_dim_len(1) = bc_dimensions%cur_dim_len(1) + 1
577 bc_dimensions%xlen(bc_dimensions%cur_dim_len(1)) = global_size(1)
578 write(suffix,
'(I1)') bc_dimensions%cur_dim_len(1)
579 axisname =
'xaxis_'//suffix
580 call netcdf_add_dimension(fileobj, axisname, global_size(1))
581 dimnames(1) = axisname
586 do i = 1, bc_dimensions%cur_dim_len(2)
587 if (bc_dimensions%ylen(i) .eq. global_size(2))
then
589 write(suffix,
'(I1)') i
590 axisname =
'yaxis_'//suffix
591 dimnames(2) = axisname
597 if (found_index .eq. 0)
then
598 bc_dimensions%cur_dim_len(2) = bc_dimensions%cur_dim_len(2) + 1
599 bc_dimensions%ylen(bc_dimensions%cur_dim_len(2)) = global_size(2)
600 write(suffix,
'(I1)') bc_dimensions%cur_dim_len(2)
601 axisname =
'yaxis_'//suffix
602 call netcdf_add_dimension(fileobj, axisname, global_size(2))
603 dimnames(2) = axisname
607 if (
size(global_size) .eq. 3)
then
610 do i = 1, bc_dimensions%cur_dim_len(3)
611 if (bc_dimensions%zlen(i) .eq. global_size(3))
then
613 write(suffix,
'(I1)') i
614 axisname =
'zaxis_'//suffix
615 dimnames(3) = axisname
621 if (found_index .eq. 0)
then
622 bc_dimensions%cur_dim_len(3) = bc_dimensions%cur_dim_len(3) + 1
623 bc_dimensions%zlen(bc_dimensions%cur_dim_len(3)) = global_size(3)
624 write(suffix,
'(I1)') bc_dimensions%cur_dim_len(3)
625 axisname =
'zaxis_'//suffix
626 call netcdf_add_dimension(fileobj, axisname, global_size(3))
627 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.