4 use netcdf,
only : nf90_global, nf90_nowrite, nf90_inquire_attribute, nf90_open, nf90_inq_dimid, nf90_inquire_dimension, &
5 nf90_inq_varid, nf90_get_var, nf90_get_att, nf90_close
19 z_dim_key,
q_dim_key,
q_key,
zq_key,
th_key,
zth_key,
p_key,
u_key,
v_key,
w_key,
zu_key,
zv_key,
zw_key,
x_key,
y_key, &
20 z_key,
zn_key,
nqfields,
ugal,
vgal,
time_key,
timestep,
created_attribute_key,
title_attribute_key,
absolute_new_dtm_key, &
22 max_string_length,
thref,
olubar,
olzubar,
olvbar,
olzvbar,
olthbar,
olzthbar,
olqbar,
olzqbar,
olqbar_anonymous_name, &
42 character(len=*),
intent(in) :: filename
44 integer :: ncid, z_dim, y_dim, x_dim
45 logical :: z_found, y_found, x_found
46 character(len=:),
allocatable :: attribute_value
50 call read_dimensions(ncid, z_dim, y_dim, x_dim, z_found, y_found, x_found)
51 call load_global_grid(current_state, ncid, z_dim, y_dim, x_dim, z_found, y_found, x_found)
63 if (current_state%number_q_fields .gt. 0)
then
69 call log_master_log(
log_info,
"Restarted configuration from checkpoint file `"//trim(filename)//
"` created at "&
71 deallocate(attribute_value)
72 current_state%initialised=.true.
81 if (
associated(current_state%parallel%decomposition_procedure))
then
82 call current_state%parallel%decomposition_procedure(current_state)
93 integer :: x_size, y_size, z_size, i
95 z_size = current_state%local_grid%size(
z_index) + current_state%local_grid%halo_size(
z_index) * 2
96 y_size = current_state%local_grid%size(
y_index) + current_state%local_grid%halo_size(
y_index) * 2
97 x_size = current_state%local_grid%size(
x_index) + current_state%local_grid%halo_size(
x_index) * 2
99 allocate(current_state%su%data(z_size, y_size, x_size))
100 current_state%su%data(:,:,:) = 0.
101 current_state%su%active=.true.
102 allocate(current_state%savu%data(z_size, y_size, x_size))
103 current_state%savu%data(:,:,:) = 0.
104 current_state%savu%active=.true.
107 allocate(current_state%sv%data(z_size, y_size, x_size))
108 current_state%sv%data(:,:,:) = 0.
109 current_state%sv%active=.true.
110 allocate(current_state%savv%data(z_size, y_size, x_size))
111 current_state%savv%data(:,:,:) = 0.
112 current_state%savv%active=.true.
115 allocate(current_state%sw%data(z_size, y_size, x_size))
116 current_state%sw%data(:,:,:) = 0.
117 current_state%sw%active=.true.
118 allocate(current_state%savw%data(z_size, y_size, x_size))
119 current_state%savw%data(:,:,:) = 0.
120 current_state%savw%active=.true.
122 if (current_state%th%active)
then
123 allocate(current_state%sth%data(z_size, y_size, x_size))
124 current_state%sth%data(:,:,:) = 0.
125 current_state%sth%active=.true.
127 do i=1,current_state%number_q_fields
128 current_state%sq(i)%active=.true.
129 allocate(current_state%sq(i)%data(z_size, y_size, x_size))
130 current_state%sq(i)%data(:,:,:) = 0.
139 integer,
intent(in) :: ncid
145 current_state%timestep = i_data(1)+1
148 current_state%ugal = r_data(1)
150 current_state%vgal = r_data(1)
152 current_state%number_q_fields = i_data(1)
154 current_state%dtm = r_data(1)
156 current_state%dtm_new = r_data(1)
157 current_state%update_dtm = current_state%dtm .ne. current_state%dtm_new
159 current_state%absolute_new_dtm = r_data(1)
162 current_state%time = r_data(1)
164 current_state%rad_last_time = r_data(1)
172 integer,
intent(in) :: ncid
173 character(len=*),
intent(in) :: key
194 integer,
intent(in) :: ncid
197 logical :: multi_process
199 character(len=STRING_LENGTH) :: q_field_name, zq_field_name
201 multi_process = current_state%parallel%processes .gt. 1
231 allocate(current_state%q(current_state%number_q_fields), current_state%zq(current_state%number_q_fields), &
232 current_state%sq(current_state%number_q_fields))
234 do i=1,current_state%number_q_fields
241 do i=1,current_state%number_q_fields
243 q_field_name=trim(
q_key)//
"_"//trim(q_metadata%name)
244 zq_field_name=trim(
zq_key)//
"_"//trim(q_metadata%name)
253 call log_log(
log_error,
"Missmatch between q and zq field name in the checkpoint file")
275 integer,
intent(in) :: ncid
276 character(len=*),
intent(in) :: variable_key
278 integer :: variable_id
286 integer,
intent(in) :: ncid
288 integer :: number_q_indices, i, q_indices_id
289 character(len=MAX_STRING_LENGTH) :: key, value
292 if (number_q_indices .gt. 0)
then
294 do i=1, number_q_indices
307 integer,
intent(in) :: ncid
309 integer :: q_indices_dimid, q_indices_dim
310 logical :: found_flag
330 subroutine load_single_3d_field(ncid, local_grid, field, z_grid, y_grid, x_grid, variable_key, multi_process, fourth_dim_loc)
331 character(len=*),
intent(in) :: variable_key
332 integer,
intent(in) :: z_grid, y_grid, x_grid, ncid
335 logical,
intent(in) :: multi_process
336 integer,
optional,
intent(in) :: fourth_dim_loc
338 integer :: start(5), count(5), i, map(5)
339 integer :: variable_id, nd
341 if (
allocated(field%data))
deallocate(field%data)
342 allocate(field%data(local_grid%size(
z_index) + local_grid%halo_size(
z_index) * 2, local_grid%size(
y_index) + &
346 if (multi_process .or.
present(fourth_dim_loc))
then
351 map(i)=map(i-1)*local_grid%size(i-1)
353 start(i) = local_grid%start(i)
354 count(i) = local_grid%size(i)
356 if (
present(fourth_dim_loc))
then
357 start(4) = fourth_dim_loc
359 map(4)=map(3)*local_grid%size(3)
366 map(4)=map(3)*local_grid%size(3)
371 local_grid%local_domain_end_index(
z_index),local_grid%local_domain_start_index(
y_index):&
372 local_grid%local_domain_end_index(
y_index), local_grid%local_domain_start_index(
x_index):&
373 local_grid%local_domain_end_index(
x_index)), start=start, count=count, map=map)
376 local_grid%local_domain_end_index(
z_index),local_grid%local_domain_start_index(
y_index):&
377 local_grid%local_domain_end_index(
y_index), local_grid%local_domain_start_index(
x_index):&
378 local_grid%local_domain_end_index(
x_index)))
384 field%active = .true.
396 subroutine load_global_grid(current_state, ncid, z_dim, y_dim, x_dim, z_found, y_found, x_found)
398 integer,
intent(in) :: ncid, z_dim, y_dim, x_dim
399 logical,
intent(in) :: z_found, y_found, x_found
401 current_state%global_grid%dimensions = 0
414 integer,
intent(in) :: ncid, z_dim_id
418 character(len=STRING_LENGTH) :: q_field_name, zq_field_name
422 allocate(current_state%global_grid%configuration%vertical%olubar(z_size))
426 allocate(current_state%global_grid%configuration%vertical%olzubar(z_size))
430 allocate(current_state%global_grid%configuration%vertical%olvbar(z_size))
434 allocate(current_state%global_grid%configuration%vertical%olzvbar(z_size))
438 allocate(current_state%global_grid%configuration%vertical%olthbar(z_size))
442 allocate(current_state%global_grid%configuration%vertical%olzthbar(z_size))
446 allocate(current_state%global_grid%configuration%vertical%olqbar(z_size, current_state%number_q_fields))
448 else if (current_state%number_q_fields .gt. 0)
then
449 do i=1,current_state%number_q_fields
451 q_field_name=trim(
olqbar)//
"_"//trim(q_metadata%name)
458 if (.not.
allocated(current_state%global_grid%configuration%vertical%olqbar))
then
459 allocate(current_state%global_grid%configuration%vertical%olqbar(z_size, current_state%number_q_fields))
462 real_data_1d_double=current_state%global_grid%configuration%vertical%olqbar(:, i))
466 allocate(current_state%global_grid%configuration%vertical%olzqbar(z_size, current_state%number_q_fields))
468 else if (current_state%number_q_fields .gt. 0)
then
469 do i=1,current_state%number_q_fields
471 q_field_name=trim(
olzqbar)//
"_"//trim(q_metadata%name)
478 if (.not.
allocated(current_state%global_grid%configuration%vertical%olzqbar))
then
479 allocate(current_state%global_grid%configuration%vertical%olzqbar(z_size, current_state%number_q_fields))
482 real_data_1d_double=current_state%global_grid%configuration%vertical%olzqbar(:, i))
490 integer,
intent(in) :: ncid, z_dim_id
496 allocate(current_state%global_grid%configuration%vertical%w_up(z_size))
497 call read_single_variable(ncid,
wup, real_data_1d_double=current_state%global_grid%configuration%vertical%w_up)
500 allocate(current_state%global_grid%configuration%vertical%w_dwn(z_size))
513 character(len=*),
intent(in) :: z_key
514 integer,
intent(in) :: z_dim_id, ncid
517 real,
dimension(:),
allocatable :: data
520 allocate(
data(z_size))
523 allocate(current_state%global_grid%configuration%vertical%kgd(z_size), &
524 current_state%global_grid%configuration%vertical%hgd(z_size), &
525 current_state%global_grid%configuration%vertical%thref(z_size))
530 current_state%global_grid%configuration%vertical%kgd(i) = i
531 current_state%global_grid%configuration%vertical%hgd(i) = real(
data(i))
543 integer,
intent(in) :: ncid, dimension_id, dimension
544 character(len=*),
intent(in) :: variable_key
551 if (variable_key .eq.
"x" .or. variable_key .eq.
"y")
then
552 call read_single_variable(ncid, trim(variable_key)//
"_resolution", real_data=grid%resolution(dimension))
554 call read_single_variable(ncid, trim(variable_key)//
"_bottom", real_data=grid%bottom(dimension))
555 else if (variable_key .eq.
"z")
then
556 allocate(grid%configuration%vertical%z(dim_size), grid%configuration%vertical%zn(dim_size))
559 grid%top(dimension) = int(grid%configuration%vertical%z(dim_size))
560 grid%resolution(dimension) = int(grid%configuration%vertical%z(2) - grid%configuration%vertical%z(1))
563 grid%bottom(dimension) = 0
565 grid%size(dimension) = dim_size
566 grid%dimensions = grid%dimensions + 1
567 grid%active(dimension) = .true.
577 subroutine read_single_variable(ncid, key, int_data, real_data, real_data_1d, real_data_1d_double, real_data_2d_double, &
578 real_data_3d, integer_data_1d, start, count, map)
579 integer,
intent(in) :: ncid
580 character(len=*),
intent(in) :: key
581 integer,
intent(inout),
optional :: int_data
583 real,
dimension(:),
intent(inout),
optional :: real_data_1d
584 real(kind=
default_precision),
dimension(:),
intent(inout),
optional :: real_data_1d_double
585 real(kind=
default_precision),
dimension(:,:),
intent(inout),
optional :: real_data_2d_double
586 real(kind=
default_precision),
dimension(:,:,:),
intent(inout),
optional :: real_data_3d
587 integer,
dimension(:),
intent(inout),
optional :: integer_data_1d
588 integer,
dimension(:),
intent(in),
optional :: start, count, map
590 integer :: variable_id
594 if (.not.
present(int_data) .and. .not.
present(real_data) .and. .not.
present(real_data_1d) .and. &
595 .not.
present(real_data_1d_double) .and. .not.
present(real_data_2d_double) .and. &
596 .not.
present(real_data_3d) .and. .not.
present(integer_data_1d))
return
598 if (
present(int_data))
then
603 if (
present(real_data))
then
608 if (
present(real_data_1d))
then
609 if (
present(start) .and.
present(count) .and.
present(map))
then
611 else if (
present(start) .and.
present(count))
then
616 else if (
present(real_data_1d_double))
then
617 if (
present(start) .and.
present(count) .and.
present(map))
then
619 else if (
present(start) .and.
present(count))
then
624 else if (
present(real_data_2d_double))
then
625 if (
present(start) .and.
present(count) .and.
present(map))
then
627 else if (
present(start) .and.
present(count))
then
632 else if (
present(real_data_3d))
then
633 if (
present(start) .and.
present(count) .and.
present(map))
then
635 else if (
present(start) .and.
present(count))
then
640 else if (
present(integer_data_1d))
then
641 if (
present(start) .and.
present(count) .and.
present(map))
then
643 else if (
present(start) .and.
present(count))
then
664 integer,
intent(in) :: ncid
665 integer,
intent(out) :: z_dim, y_dim, x_dim
666 logical,
intent(out) :: z_found, y_found, x_found