MONC
readcheckpoint.F90
Go to the documentation of this file.
1 
3 #ifndef TEST_MODE
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
6 #else
9 #endif
10  use datadefn_mod, only : string_length
11  use state_mod, only : model_state_type
24  wup, wdwn
27  implicit none
28 
29 #ifndef TEST_MODE
30  private
31 #endif
32 
34 
35 contains
36 
40  subroutine read_checkpoint_file(current_state, filename)
41  type(model_state_type), intent(inout) :: current_state
42  character(len=*), intent(in) :: filename
43 
44  integer :: ncid, z_dim, y_dim, x_dim
45  logical :: z_found, y_found, x_found
46  character(len=:), allocatable :: attribute_value
47 
48  call check_status(nf90_open(path = filename, mode = nf90_nowrite, ncid = ncid))
49  attribute_value=read_specific_global_attribute(ncid, "created")
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)
52 
53  call decompose_grid(current_state)
54 
55  call load_q_indices(ncid)
56  call load_misc(current_state, ncid)
57  call load_all_fields(current_state, ncid)
58  call initalise_source_and_sav_fields(current_state)
59  call load_mean_profiles(current_state, ncid, z_dim)
60  call load_pdf_profiles(current_state, ncid, z_dim)
61  call check_status(nf90_close(ncid))
62 
63  if (current_state%number_q_fields .gt. 0) then
64  ! Retrieve standard q indices
65  current_state%water_vapour_mixing_ratio_index=get_q_index(standard_q_names%VAPOUR, 'checkpoint')
66  current_state%liquid_water_mixing_ratio_index=get_q_index(standard_q_names%CLOUD_LIQUID_MASS, 'checkpoint')
67  end if
68 
69  call log_master_log(log_info, "Restarted configuration from checkpoint file `"//trim(filename)//"` created at "&
70  //attribute_value)
71  deallocate(attribute_value)
72  current_state%initialised=.true.
73  end subroutine read_checkpoint_file
74 
78  subroutine decompose_grid(current_state)
79  type(model_state_type), intent(inout) :: current_state
80 
81  if (associated(current_state%parallel%decomposition_procedure)) then
82  call current_state%parallel%decomposition_procedure(current_state)
83  else
84  call log_log(log_error, "No decomposition specified")
85  end if
86  end subroutine decompose_grid
87 
90  subroutine initalise_source_and_sav_fields(current_state)
91  type(model_state_type), intent(inout) :: current_state
92 
93  integer :: x_size, y_size, z_size, i
94 
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
98 #ifdef U_ACTIVE
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.
105 #endif
106 #ifdef V_ACTIVE
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.
113 #endif
114 #ifdef W_ACTIVE
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.
121 #endif
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.
126  end if
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.
131  end do
132  end subroutine initalise_source_and_sav_fields
133 
137  subroutine load_misc(current_state, ncid)
138  type(model_state_type), intent(inout) :: current_state
139  integer, intent(in) :: ncid
140 
141  integer :: i_data(1) ! Procedure requires a vector rather than scalar
142  real(kind=default_precision) :: r_data(1)
143 
144  call read_single_variable(ncid, timestep, integer_data_1d=i_data)
145  current_state%timestep = i_data(1)+1 ! plus one to increment for next timestep
146  !current_state%start_timestep = current_state%timestep
147  call read_single_variable(ncid, ugal, real_data_1d_double=r_data)
148  current_state%ugal = r_data(1)
149  call read_single_variable(ncid, vgal, real_data_1d_double=r_data)
150  current_state%vgal = r_data(1)
151  call read_single_variable(ncid, nqfields, integer_data_1d=i_data)
152  current_state%number_q_fields = i_data(1)
153  call read_single_variable(ncid, dtm_key, real_data_1d_double=r_data)
154  current_state%dtm = r_data(1)
155  call read_single_variable(ncid, dtm_new_key, real_data_1d_double=r_data)
156  current_state%dtm_new = r_data(1)
157  current_state%update_dtm = current_state%dtm .ne. current_state%dtm_new
158  call read_single_variable(ncid, absolute_new_dtm_key, real_data_1d_double=r_data)
159  current_state%absolute_new_dtm = r_data(1)
160  call read_single_variable(ncid, time_key, real_data_1d_double=r_data)
161  ! The time is written into checkpoint as time+dtm, therefore the time as read in has been correctly advanced
162  current_state%time = r_data(1)
163  call read_single_variable(ncid, rad_last_time_key, real_data_1d_double=r_data)
164  current_state%rad_last_time = r_data(1)
165  end subroutine load_misc
166 
171  function read_specific_global_attribute(ncid, key)
172  integer, intent(in) :: ncid
173  character(len=*), intent(in) :: key
174 
175  integer :: length
176  character(len=:),allocatable,target :: read_specific_global_attribute
177 
178  call check_status(nf90_inquire_attribute(ncid, nf90_global, key, len = length))
179  allocate(character(length) :: read_specific_global_attribute)
181  end function read_specific_global_attribute
182 
192  subroutine load_all_fields(current_state, ncid)
193  type(model_state_type), intent(inout) :: current_state
194  integer, intent(in) :: ncid
195 
196  integer :: i
197  logical :: multi_process
198  type(q_metadata_type) :: q_metadata
199  character(len=STRING_LENGTH) :: q_field_name, zq_field_name
200 
201  multi_process = current_state%parallel%processes .gt. 1
202 
203  if (does_field_exist(ncid, u_key)) then
204  call load_single_3d_field(ncid, current_state%local_grid, current_state%u, dual_grid, &
205  dual_grid, primal_grid, u_key, multi_process)
206  call load_single_3d_field(ncid, current_state%local_grid, current_state%zu, dual_grid, &
207  dual_grid, primal_grid, zu_key, multi_process)
208  end if
209  if (does_field_exist(ncid, v_key)) then
210  call load_single_3d_field(ncid, current_state%local_grid, current_state%v, dual_grid, &
211  primal_grid, dual_grid, v_key, multi_process)
212  call load_single_3d_field(ncid, current_state%local_grid, current_state%zv, dual_grid, &
213  primal_grid, dual_grid, zv_key, multi_process)
214  end if
215  if (does_field_exist(ncid, w_key)) then
216  call load_single_3d_field(ncid, current_state%local_grid, current_state%w, primal_grid, &
217  dual_grid, dual_grid, w_key, multi_process)
218  call load_single_3d_field(ncid, current_state%local_grid, current_state%zw, primal_grid, &
219  dual_grid, dual_grid, zw_key, multi_process)
220  end if
221  if (does_field_exist(ncid, th_key)) then
222  call load_single_3d_field(ncid, current_state%local_grid, current_state%th, dual_grid, &
223  dual_grid, dual_grid, th_key, multi_process)
224  call load_single_3d_field(ncid, current_state%local_grid, current_state%zth, dual_grid, &
225  dual_grid, dual_grid, zth_key, multi_process)
226  end if
227  if (does_field_exist(ncid, p_key)) then
228  call load_single_3d_field(ncid, current_state%local_grid, current_state%p, dual_grid, &
229  dual_grid, dual_grid, p_key, multi_process)
230  end if
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))
233  if (does_field_exist(ncid, q_key)) then
234  do i=1,current_state%number_q_fields
235  call load_single_3d_field(ncid, current_state%local_grid, current_state%q(i), dual_grid, &
236  dual_grid, dual_grid, q_key, multi_process, i)
237  call load_single_3d_field(ncid, current_state%local_grid, current_state%zq(i), dual_grid, &
238  dual_grid, dual_grid, zq_key, multi_process, i)
239  end do
240  else
241  do i=1,current_state%number_q_fields
242  q_metadata=get_indices_descriptor(i)
243  q_field_name=trim(q_key)//"_"//trim(q_metadata%name)
244  zq_field_name=trim(zq_key)//"_"//trim(q_metadata%name)
245  if (.not. does_field_exist(ncid, q_field_name)) then
246  q_field_name=trim(q_field_anonymous_name)//"_"//trim(conv_to_string(i))
247  zq_field_name=trim(zq_field_anonymous_name)//"_"//trim(conv_to_string(i))
248  if (.not. does_field_exist(ncid, q_field_name)) then
249  call log_log(log_error, "No entry in checkpoint file for Q field "//trim(conv_to_string(i)))
250  end if
251  end if
252  if (.not. does_field_exist(ncid, zq_field_name)) then
253  call log_log(log_error, "Missmatch between q and zq field name in the checkpoint file")
254  end if
255  call load_single_3d_field(ncid, current_state%local_grid, current_state%q(i), dual_grid, &
256  dual_grid, dual_grid, q_field_name, multi_process)
257  call load_single_3d_field(ncid, current_state%local_grid, current_state%zq(i), dual_grid, &
258  dual_grid, dual_grid, zq_field_name, multi_process)
259  end do
260  end if
261  if (does_field_exist(ncid, sth_lw_key)) then
262  call load_single_3d_field(ncid, current_state%local_grid, current_state%sth_lw, dual_grid, &
263  dual_grid, dual_grid, sth_lw_key, multi_process)
264  end if
265  if (does_field_exist(ncid, sth_lw_key)) then
266  call load_single_3d_field(ncid, current_state%local_grid, current_state%sth_sw, dual_grid, &
267  dual_grid, dual_grid, sth_sw_key, multi_process)
268  endif
269  end subroutine load_all_fields
270 
274  logical function does_field_exist(ncid, variable_key)
275  integer, intent(in) :: ncid
276  character(len=*), intent(in) :: variable_key
277 
278  integer :: variable_id
279 
280  call check_status(nf90_inq_varid(ncid, variable_key, variable_id), does_field_exist)
281  end function does_field_exist
282 
285  subroutine load_q_indices(ncid)
286  integer, intent(in) :: ncid
287 
288  integer :: number_q_indices, i, q_indices_id
289  character(len=MAX_STRING_LENGTH) :: key, value
290 
291  number_q_indices=get_number_q_indices(ncid)
292  if (number_q_indices .gt. 0) then
293  call check_status(nf90_inq_varid(ncid, q_indices_key, q_indices_id))
294  do i=1, number_q_indices
295  call check_status(nf90_get_var(ncid, q_indices_id, key, (/ 1, 1, i /)))
296  call check_status(nf90_get_var(ncid, q_indices_id, value, (/ 1, 2, i /)))
299  call set_q_index(conv_to_integer(trim(value)), key)
300  end do
301  end if
302  end subroutine load_q_indices
303 
306  integer function get_number_q_indices(ncid)
307  integer, intent(in) :: ncid
308 
309  integer :: q_indices_dimid, q_indices_dim
310  logical :: found_flag
311 
312  call check_status(nf90_inq_dimid(ncid, q_indices_dim_key, q_indices_dimid), found_flag)
313  if (found_flag) then
314  call check_status(nf90_inquire_dimension(ncid, q_indices_dimid, len=q_indices_dim))
315  get_number_q_indices=q_indices_dim
316  else
318  end if
319  end function get_number_q_indices
320 
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
333  type(prognostic_field_type), intent(inout) :: field
334  type(local_grid_type), intent(inout) :: local_grid
335  logical, intent(in) :: multi_process
336  integer, optional, intent(in) :: fourth_dim_loc
337 
338  integer :: start(5), count(5), i, map(5)
339  integer :: variable_id, nd
340 
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) + &
343  local_grid%halo_size(y_index) * 2, local_grid%size(x_index) + local_grid%halo_size(x_index) * 2))
344  field%data(:,:,:)=0.
345 
346  if (multi_process .or. present(fourth_dim_loc)) then
347  do i=1,3
348  if (i==1) then
349  map(i)=1
350  else
351  map(i)=map(i-1)*local_grid%size(i-1)
352  end if
353  start(i) = local_grid%start(i)
354  count(i) = local_grid%size(i)
355  end do
356  if (present(fourth_dim_loc)) then
357  start(4) = fourth_dim_loc
358  count(4) = 1
359  map(4)=map(3)*local_grid%size(3)
360 
361  start(5)=1
362  count(5)=1
363  map(5)=map(4)
364  else
365  start(4)=1
366  map(4)=map(3)*local_grid%size(3)
367  count(4)=1
368  end if
369 
370  call read_single_variable(ncid, variable_key, real_data_3d=field%data(local_grid%local_domain_start_index(z_index):&
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)
374  else
375  call read_single_variable(ncid, variable_key, real_data_3d=field%data(local_grid%local_domain_start_index(z_index):&
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)))
379  end if
380 
381  field%grid(z_index) = z_grid
382  field%grid(y_index) = y_grid
383  field%grid(x_index) = x_grid
384  field%active = .true.
385  end subroutine load_single_3d_field
386 
396  subroutine load_global_grid(current_state, ncid, z_dim, y_dim, x_dim, z_found, y_found, x_found)
397  type(model_state_type), intent(inout) :: current_state
398  integer, intent(in) :: ncid, z_dim, y_dim, x_dim
399  logical, intent(in) :: z_found, y_found, x_found
400 
401  current_state%global_grid%dimensions = 0
402 
403  if (z_found) then
404  call read_dimension_of_grid(ncid, current_state%global_grid, z_key, z_index, z_dim)
405  call define_vertical_levels(ncid, current_state, z_key, z_dim)
406 
407  end if
408  if (y_found) call read_dimension_of_grid(ncid, current_state%global_grid, y_key, y_index, y_dim)
409  if (x_found) call read_dimension_of_grid(ncid, current_state%global_grid, x_key, x_index, x_dim)
410  end subroutine load_global_grid
411 
412  subroutine load_mean_profiles(current_state, ncid, z_dim_id)
413  type(model_state_type), intent(inout) :: current_state
414  integer, intent(in) :: ncid, z_dim_id
415 
416  integer :: z_size, i
417  type(q_metadata_type) :: q_metadata
418  character(len=STRING_LENGTH) :: q_field_name, zq_field_name
419 
420  call check_status(nf90_inquire_dimension(ncid, z_dim_id, len=z_size))
421  if (does_field_exist(ncid, olubar)) then
422  allocate(current_state%global_grid%configuration%vertical%olubar(z_size))
423  call read_single_variable(ncid, olubar, real_data_1d_double=current_state%global_grid%configuration%vertical%olubar)
424  end if
425  if (does_field_exist(ncid, olzubar)) then
426  allocate(current_state%global_grid%configuration%vertical%olzubar(z_size))
427  call read_single_variable(ncid, olzubar, real_data_1d_double=current_state%global_grid%configuration%vertical%olzubar)
428  end if
429  if (does_field_exist(ncid, olvbar)) then
430  allocate(current_state%global_grid%configuration%vertical%olvbar(z_size))
431  call read_single_variable(ncid, olvbar, real_data_1d_double=current_state%global_grid%configuration%vertical%olvbar)
432  end if
433  if (does_field_exist(ncid, olzvbar)) then
434  allocate(current_state%global_grid%configuration%vertical%olzvbar(z_size))
435  call read_single_variable(ncid, olzvbar, real_data_1d_double=current_state%global_grid%configuration%vertical%olzvbar)
436  end if
437  if (does_field_exist(ncid, olthbar)) then
438  allocate(current_state%global_grid%configuration%vertical%olthbar(z_size))
439  call read_single_variable(ncid, olthbar, real_data_1d_double=current_state%global_grid%configuration%vertical%olthbar)
440  end if
441  if (does_field_exist(ncid, olzthbar)) then
442  allocate(current_state%global_grid%configuration%vertical%olzthbar(z_size))
443  call read_single_variable(ncid, olzthbar, real_data_1d_double=current_state%global_grid%configuration%vertical%olzthbar)
444  end if
445  if (does_field_exist(ncid, olqbar)) then
446  allocate(current_state%global_grid%configuration%vertical%olqbar(z_size, current_state%number_q_fields))
447  call read_single_variable(ncid, olqbar, real_data_2d_double=current_state%global_grid%configuration%vertical%olqbar)
448  else if (current_state%number_q_fields .gt. 0) then
449  do i=1,current_state%number_q_fields
450  q_metadata=get_indices_descriptor(i)
451  q_field_name=trim(olqbar)//"_"//trim(q_metadata%name)
452  if (.not. does_field_exist(ncid, q_field_name)) then
453  q_field_name=trim(olqbar_anonymous_name)//"_"//trim(conv_to_string(i))
454  if (.not. does_field_exist(ncid, q_field_name)) then
455  cycle
456  end if
457  end if
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))
460  end if
461  call read_single_variable(ncid, q_field_name, &
462  real_data_1d_double=current_state%global_grid%configuration%vertical%olqbar(:, i))
463  end do
464  end if
465  if (does_field_exist(ncid, olzqbar)) then
466  allocate(current_state%global_grid%configuration%vertical%olzqbar(z_size, current_state%number_q_fields))
467  call read_single_variable(ncid, olzqbar, real_data_2d_double=current_state%global_grid%configuration%vertical%olzqbar)
468  else if (current_state%number_q_fields .gt. 0) then
469  do i=1,current_state%number_q_fields
470  q_metadata=get_indices_descriptor(i)
471  q_field_name=trim(olzqbar)//"_"//trim(q_metadata%name)
472  if (.not. does_field_exist(ncid, q_field_name)) then
473  q_field_name=trim(olzqbar_anonymous_name)//"_"//trim(conv_to_string(i))
474  if (.not. does_field_exist(ncid, q_field_name)) then
475  cycle
476  end if
477  end if
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))
480  end if
481  call read_single_variable(ncid, q_field_name, &
482  real_data_1d_double=current_state%global_grid%configuration%vertical%olzqbar(:, i))
483  end do
484  end if
485  end subroutine load_mean_profiles
486 
487 
488  subroutine load_pdf_profiles(current_state, ncid, z_dim_id)
489  type(model_state_type), intent(inout) :: current_state
490  integer, intent(in) :: ncid, z_dim_id
491 
492  integer :: z_size, i
493 
494  call check_status(nf90_inquire_dimension(ncid, z_dim_id, len=z_size))
495  if (does_field_exist(ncid, wup)) then
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)
498  end if
499  if (does_field_exist(ncid, wdwn)) then
500  allocate(current_state%global_grid%configuration%vertical%w_dwn(z_size))
501  call read_single_variable(ncid, wdwn, real_data_1d_double=current_state%global_grid%configuration%vertical%w_dwn)
502  end if
503  end subroutine load_pdf_profiles
504 
505 
511  subroutine define_vertical_levels(ncid, current_state, z_key, z_dim_id)
512  type(model_state_type), intent(inout) :: current_state
513  character(len=*), intent(in) :: z_key
514  integer, intent(in) :: z_dim_id, ncid
515 
516  integer :: i, z_size
517  real, dimension(:), allocatable :: data
518 
519  call check_status(nf90_inquire_dimension(ncid, z_dim_id, len=z_size))
520  allocate(data(z_size))
521  call read_single_variable(ncid, z_key, real_data_1d=data)
522 
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))
526 
527  call read_single_variable(ncid, thref, real_data_1d_double=current_state%global_grid%configuration%vertical%thref)
528 
529  do i=1,z_size
530  current_state%global_grid%configuration%vertical%kgd(i) = i
531  current_state%global_grid%configuration%vertical%hgd(i) = real(data(i))
532  end do
533  deallocate(data)
534  end subroutine define_vertical_levels
535 
542  subroutine read_dimension_of_grid(ncid, grid, variable_key, dimension, dimension_id)
543  integer, intent(in) :: ncid, dimension_id, dimension
544  character(len=*), intent(in) :: variable_key
545  type(global_grid_type), intent(inout) :: grid
546 
547  integer :: dim_size
548 
549  call check_status(nf90_inquire_dimension(ncid, dimension_id, len=dim_size))
550 
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))
553  call read_single_variable(ncid, trim(variable_key)//"_top", real_data=grid%top(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))
557  call read_single_variable(ncid, z_key, real_data_1d_double=grid%configuration%vertical%z)
558  call read_single_variable(ncid, zn_key, real_data_1d_double=grid%configuration%vertical%zn)
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))
561  ! For now hard code the bottom of the grid in each dimension as 0, first element is the 0th + size
562  ! I.e. if dxx=100, start=0 then first point is 100 rather than 0 (in x and y), is correct in z in CP file
563  grid%bottom(dimension) = 0
564  end if
565  grid%size(dimension) = dim_size
566  grid%dimensions = grid%dimensions + 1
567  grid%active(dimension) = .true.
568  end subroutine read_dimension_of_grid
569 
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
582  real(kind=default_precision) , intent(inout), optional :: real_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
589 
590  integer :: variable_id
591 
592  call check_status(nf90_inq_varid(ncid, key, variable_id))
593 
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
597 
598  if (present(int_data)) then
599  call check_status(nf90_get_var(ncid, variable_id, int_data))
600  return
601  end if
602 
603  if (present(real_data)) then
604  call check_status(nf90_get_var(ncid, variable_id, real_data))
605  return
606  end if
607 
608  if (present(real_data_1d)) then
609  if (present(start) .and. present(count) .and. present(map)) then
610  call check_status(nf90_get_var(ncid, variable_id, real_data_1d, start=start, count=count, map=map))
611  else if (present(start) .and. present(count)) then
612  call check_status(nf90_get_var(ncid, variable_id, real_data_1d, start=start, count=count))
613  else
614  call check_status(nf90_get_var(ncid, variable_id, real_data_1d))
615  end if
616  else if (present(real_data_1d_double)) then
617  if (present(start) .and. present(count) .and. present(map)) then
618  call check_status(nf90_get_var(ncid, variable_id, real_data_1d_double, start=start, count=count, map=map))
619  else if (present(start) .and. present(count)) then
620  call check_status(nf90_get_var(ncid, variable_id, real_data_1d_double, start=start, count=count))
621  else
622  call check_status(nf90_get_var(ncid, variable_id, real_data_1d_double))
623  end if
624  else if (present(real_data_2d_double)) then
625  if (present(start) .and. present(count) .and. present(map)) then
626  call check_status(nf90_get_var(ncid, variable_id, real_data_2d_double, start=start, count=count, map=map))
627  else if (present(start) .and. present(count)) then
628  call check_status(nf90_get_var(ncid, variable_id, real_data_2d_double, start=start, count=count))
629  else
630  call check_status(nf90_get_var(ncid, variable_id, real_data_2d_double))
631  end if
632  else if (present(real_data_3d)) then
633  if (present(start) .and. present(count) .and. present(map)) then
634  call check_status(nf90_get_var(ncid, variable_id, real_data_3d, start=start, count=count, map=map))
635  else if (present(start) .and. present(count)) then
636  call check_status(nf90_get_var(ncid, variable_id, real_data_3d, start=start, count=count))
637  else
638  call check_status(nf90_get_var(ncid, variable_id, real_data_3d))
639  end if
640  else if (present(integer_data_1d)) then
641  if (present(start) .and. present(count) .and. present(map)) then
642  call check_status(nf90_get_var(ncid, variable_id, integer_data_1d, start, count, map))
643  else if (present(start) .and. present(count)) then
644  call check_status(nf90_get_var(ncid, variable_id, integer_data_1d, start, count))
645  else
646  call check_status(nf90_get_var(ncid, variable_id, integer_data_1d))
647  end if
648  end if
649  end subroutine read_single_variable
650 
663  subroutine read_dimensions(ncid, z_dim, y_dim, x_dim, z_found, y_found, x_found)
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
667 
668  call check_status(nf90_inq_dimid(ncid, z_dim_key, z_dim), z_found)
669  call check_status(nf90_inq_dimid(ncid, y_dim_key, y_dim), y_found)
670  call check_status(nf90_inq_dimid(ncid, x_dim_key, x_dim), x_found)
671  end subroutine read_dimensions
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
checkpointer_read_checkpoint_mod::load_misc
subroutine load_misc(current_state, ncid)
Loads in misc data from the checkpoint file.
Definition: readcheckpoint.F90:138
checkpointer_common_mod::olubar
character(len= *), parameter olubar
Definition: checkpointcommon.F90:11
checkpointer_common_mod::remove_null_terminator_from_string
subroutine remove_null_terminator_from_string(net_cdf_string)
Removes NetCDF C style null termination of string. This is placed right at the end,...
Definition: checkpointcommon.F90:99
checkpointer_read_checkpoint_mod::read_checkpoint_file
subroutine, public read_checkpoint_file(current_state, filename)
Reads in a NetCDF checkpoint file and uses this to initialise the model.
Definition: readcheckpoint.F90:41
checkpointer_common_mod::p_key
character(len= *), parameter p_key
Pressure variable NetCDF key.
Definition: checkpointcommon.F90:11
conversions_mod::conv_is_logical
Determines whether a data item can be represented as a logical or not.
Definition: conversions.F90:100
checkpointer_common_mod::q_key
character(len= *), parameter q_key
Q variable NetCDF key.
Definition: checkpointcommon.F90:11
checkpointer_common_mod::empty_dim_key
character(len= *), parameter empty_dim_key
Empty dimension key.
Definition: checkpointcommon.F90:11
prognostics_mod
Contains prognostic field definitions and functions.
Definition: prognostics.F90:2
checkpointer_common_mod::zn_key
character(len= *), parameter zn_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::y_dim_key
character(len= *), parameter y_dim_key
Y dimension/variable key.
Definition: checkpointcommon.F90:11
checkpointer_common_mod::u_key
character(len= *), parameter u_key
U variable NetCDF key.
Definition: checkpointcommon.F90:11
grids_mod::dual_grid
integer, parameter, public dual_grid
Definition: grids.F90:16
checkpointer_common_mod::thref
character(len= *), parameter thref
Definition: checkpointcommon.F90:11
conversions_mod::conv_to_integer
Converts data types to integers.
Definition: conversions.F90:49
checkpointer_common_mod::rad_last_time_key
character(len= *), parameter rad_last_time_key
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::get_number_q_indices
integer function get_number_q_indices(ncid)
Retrieve sthe number of Q indice entries in the NetCDF. This is optional, so may return 0.
Definition: readcheckpoint.F90:307
checkpointer_common_mod::zv_key
character(len= *), parameter zv_key
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_get_var
Definition: dummy_netcdf.F90:43
checkpointer_common_mod::olzqbar_anonymous_name
character(len= *), parameter olzqbar_anonymous_name
Definition: checkpointcommon.F90:11
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
dummy_netcdf_mod::nf90_close
integer function nf90_close(ncid)
Definition: dummy_netcdf.F90:109
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
checkpointer_common_mod::zth_key
character(len= *), parameter zth_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::created_attribute_key
character(len= *), parameter created_attribute_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::max_string_length
integer, parameter max_string_length
Maximum string length (stored size)
Definition: checkpointcommon.F90:73
conversions_mod::conv_to_logical
Converts data types to logical.
Definition: conversions.F90:71
checkpointer_read_checkpoint_mod::read_specific_global_attribute
character(len=:) function, allocatable, target read_specific_global_attribute(ncid, key)
Will read a global attribute from the checkpoint file - note that it allocates string memory here so ...
Definition: readcheckpoint.F90:172
logging_mod::log_info
integer, parameter, public log_info
Log INFO, WARNING and ERROR messages.
Definition: logging.F90:13
checkpointer_common_mod::x_key
character(len= *), parameter x_key
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::read_dimensions
subroutine read_dimensions(ncid, z_dim, y_dim, x_dim, z_found, y_found, x_found)
Will read in the dimension sizes from the NetCDF file along with whether the z, y and x dimensions ha...
Definition: readcheckpoint.F90:664
logging_mod::log_log
subroutine, public log_log(level, message, str)
Logs a message at the specified level. If the level is above the current level then the message is ig...
Definition: logging.F90:75
checkpointer_common_mod::v_key
character(len= *), parameter v_key
V variable NetCDF key.
Definition: checkpointcommon.F90:11
q_indices_mod::set_q_index
subroutine, public set_q_index(index, name)
Sets a Q index to be active at a specific index and sets the name.
Definition: q_indices.F90:71
checkpointer_common_mod::zq_field_anonymous_name
character(len= *), parameter zq_field_anonymous_name
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::load_single_3d_field
subroutine load_single_3d_field(ncid, local_grid, field, z_grid, y_grid, x_grid, variable_key, multi_process, fourth_dim_loc)
Loads in and initialises a single 3D prognostic field. Even if the model is being run in 1 or 2D,...
Definition: readcheckpoint.F90:331
grids_mod::global_grid_type
Defines the global grid.
Definition: grids.F90:107
checkpointer_common_mod::time_key
character(len= *), parameter time_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::absolute_new_dtm_key
character(len= *), parameter absolute_new_dtm_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::timestep
character(len= *), parameter timestep
Timestep NetCDF key.
Definition: checkpointcommon.F90:11
optionsdatabase_mod::options_add
Generic add interface for adding different types of data to the databases.
Definition: optionsdatabase.F90:28
checkpointer_common_mod::olzvbar
character(len= *), parameter olzvbar
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::load_mean_profiles
subroutine load_mean_profiles(current_state, ncid, z_dim_id)
Definition: readcheckpoint.F90:413
checkpointer_common_mod::zu_key
character(len= *), parameter zu_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::sth_lw_key
character(len= *), parameter sth_lw_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::z_dim_key
character(len= *), parameter z_dim_key
Z dimension/variable key.
Definition: checkpointcommon.F90:11
checkpointer_common_mod::wup
character(len= *), parameter wup
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::read_single_variable
subroutine read_single_variable(ncid, key, int_data, real_data, real_data_1d, real_data_1d_double, real_data_2d_double, real_data_3d, integer_data_1d, start, count, map)
Reads in a single variable and sets the values of the data based upon this. Handles reading in and se...
Definition: readcheckpoint.F90:579
checkpointer_common_mod::olvbar
character(len= *), parameter olvbar
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::initalise_source_and_sav_fields
subroutine initalise_source_and_sav_fields(current_state)
Initialises the source and sav (for u,v,w) fields for allocated prognostics.
Definition: readcheckpoint.F90:91
checkpointer_read_checkpoint_mod::define_vertical_levels
subroutine define_vertical_levels(ncid, current_state, z_key, z_dim_id)
Defines the vertical levels of the grid. This is both the grid points and corresponding height for ea...
Definition: readcheckpoint.F90:512
dummy_netcdf_mod::nf90_inquire_dimension
integer function nf90_inquire_dimension(ncid, id, len)
Definition: dummy_netcdf.F90:344
dummy_netcdf_mod
Definition: dummy_netcdf.F90:4
checkpointer_common_mod::q_indices_key
character(len= *), parameter q_indices_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::w_key
character(len= *), parameter w_key
W variable NetCDF key.
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::load_all_fields
subroutine load_all_fields(current_state, ncid)
Reads in and initialises all prognostic fields. It will check the NetCDF checkpoint file and dependin...
Definition: readcheckpoint.F90:193
checkpointer_common_mod::title_attribute_key
character(len= *), parameter title_attribute_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::dtm_key
character(len= *), parameter dtm_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::check_status
subroutine check_status(status, found_flag)
Will check a NetCDF status and write to log_log error any decoded statuses. Can be used to decode whe...
Definition: checkpointcommon.F90:82
checkpointer_common_mod::z_key
character(len= *), parameter z_key
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_open
integer function nf90_open(path, mode, ncid)
Definition: dummy_netcdf.F90:63
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
checkpointer_common_mod::string_dim_key
character(len= *), parameter string_dim_key
String dimension key.
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_get_att
integer function nf90_get_att(ncid, attributeid, key, value)
Definition: dummy_netcdf.F90:126
conversions_mod::conv_is_real
Determines whether a data item can be represented as a real or not.
Definition: conversions.F90:91
q_indices_mod::get_indices_descriptor
type(q_metadata_type) function, public get_indices_descriptor(i)
Retrieves the indicies descriptor at a specific location.
Definition: q_indices.F90:100
q_indices_mod::standard_q_names
type(standard_q_names_type), public standard_q_names
Definition: q_indices.F90:59
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
conversions_mod::conv_is_integer
Determines whether a data item can be represented as an integer or not.
Definition: conversions.F90:81
checkpointer_read_checkpoint_mod::decompose_grid
subroutine decompose_grid(current_state)
Calls out to the parallel decomposition strategy to decompose the grid based upon the configuration r...
Definition: readcheckpoint.F90:79
checkpointer_common_mod::q_field_anonymous_name
character(len= *), parameter q_field_anonymous_name
Definition: checkpointcommon.F90:11
checkpointer_common_mod::olzubar
character(len= *), parameter olzubar
Definition: checkpointcommon.F90:11
checkpointer_common_mod
Common checkpoint functionality which is used by reader and writers to NetCDF checkpoints.
Definition: checkpointcommon.F90:2
dummy_netcdf_mod::nf90_inquire_attribute
integer function nf90_inquire_attribute(ncid, attributeid, key, len)
Definition: dummy_netcdf.F90:116
checkpointer_common_mod::olzqbar
character(len= *), parameter olzqbar
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_inq_dimid
integer function nf90_inq_dimid(ncid, key, dim_id)
Definition: dummy_netcdf.F90:327
checkpointer_common_mod::q_dim_key
character(len= *), parameter q_dim_key
Definition: checkpointcommon.F90:11
grids_mod::primal_grid
integer, parameter, public primal_grid
Grid type parameters (usually applied to each dimension of a prognostic)
Definition: grids.F90:16
checkpointer_common_mod::olthbar
character(len= *), parameter olthbar
Definition: checkpointcommon.F90:11
checkpointer_common_mod::dtm_new_key
character(len= *), parameter dtm_new_key
Definition: checkpointcommon.F90:11
q_indices_mod::q_metadata_type
Definition: q_indices.F90:15
grids_mod::local_grid_type
Defined the local grid, i.e. the grid held on this process after decomposition.
Definition: grids.F90:118
checkpointer_common_mod::sth_sw_key
character(len= *), parameter sth_sw_key
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::does_field_exist
logical function does_field_exist(ncid, variable_key)
Determines whether a variable (field) exists within the NetCDF checkpoint file @ncid The NetCDF file ...
Definition: readcheckpoint.F90:275
q_indices_mod::get_q_index
integer function, public get_q_index(name, assigning_component)
Add in a new entry into the register if the name does not already exist or return the index of the pr...
Definition: q_indices.F90:112
logging_mod
Logging utility.
Definition: logging.F90:2
prognostics_mod::prognostic_field_type
A prognostic field which is assumed to be 3D.
Definition: prognostics.F90:13
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
checkpointer_read_checkpoint_mod::load_pdf_profiles
subroutine load_pdf_profiles(current_state, ncid, z_dim_id)
Definition: readcheckpoint.F90:489
checkpointer_common_mod::q_indices_dim_key
character(len= *), parameter q_indices_dim_key
Definition: checkpointcommon.F90:11
datadefn_mod::string_length
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
checkpointer_read_checkpoint_mod::load_global_grid
subroutine load_global_grid(current_state, ncid, z_dim, y_dim, x_dim, z_found, y_found, x_found)
Reads in and initialises the primal grid from the NetCDF checkpoint and will handle 1,...
Definition: readcheckpoint.F90:397
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
q_indices_mod
This manages the Q variables and specifically the mapping between names and the index that they are s...
Definition: q_indices.F90:2
checkpointer_read_checkpoint_mod
Will read in a NetCDF checkpoint file and initialise the model state_mod based upon this.
Definition: readcheckpoint.F90:2
checkpointer_common_mod::olqbar_anonymous_name
character(len= *), parameter olqbar_anonymous_name
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_global
integer, parameter nf90_global
Definition: dummy_netcdf.F90:24
checkpointer_common_mod::zq_key
character(len= *), parameter zq_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::th_key
character(len= *), parameter th_key
Theta variable NetCDF key.
Definition: checkpointcommon.F90:11
checkpointer_common_mod::x_dim_key
character(len= *), parameter x_dim_key
X dimension/variable key.
Definition: checkpointcommon.F90:11
checkpointer_common_mod::nqfields
character(len= *), parameter nqfields
Definition: checkpointcommon.F90:11
conversions_mod::conv_to_real
Converts data types to real.
Definition: conversions.F90:60
dummy_netcdf_mod::nf90_nowrite
integer, parameter nf90_nowrite
Definition: dummy_netcdf.F90:24
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
dummy_netcdf_mod::nf90_inq_varid
integer function nf90_inq_varid(ncid, key, varid)
Definition: dummy_netcdf.F90:141
checkpointer_read_checkpoint_mod::load_q_indices
subroutine load_q_indices(ncid)
Loads the Q indices (if they exist) into the model Q index register.
Definition: readcheckpoint.F90:286
checkpointer_common_mod::wdwn
character(len= *), parameter wdwn
Definition: checkpointcommon.F90:11
checkpointer_common_mod::zw_key
character(len= *), parameter zw_key
Definition: checkpointcommon.F90:11
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
checkpointer_common_mod::olqbar
character(len= *), parameter olqbar
Definition: checkpointcommon.F90:11
checkpointer_common_mod::vgal
character(len= *), parameter vgal
Definition: checkpointcommon.F90:11
checkpointer_common_mod::olzthbar
character(len= *), parameter olzthbar
Definition: checkpointcommon.F90:11
checkpointer_read_checkpoint_mod::read_dimension_of_grid
subroutine read_dimension_of_grid(ncid, grid, variable_key, dimension, dimension_id)
Reads a specific dimension of the grid from the NetCDF and sets this up in the state_mod.
Definition: readcheckpoint.F90:543
checkpointer_common_mod::ugal
character(len= *), parameter ugal
Definition: checkpointcommon.F90:11
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
checkpointer_common_mod::y_key
character(len= *), parameter y_key
Definition: checkpointcommon.F90:11
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2