MONC
writecheckpoint.F90
Go to the documentation of this file.
1 
3 #ifndef TEST_MODE
4  use netcdf, only : nf90_double, nf90_real, nf90_int, nf90_char, nf90_global, nf90_clobber, nf90_netcdf4, nf90_mpiio, &
5  nf90_collective, nf90_def_var, nf90_var_par_access, nf90_def_var_fill, nf90_put_att, nf90_create, nf90_put_var, &
6  nf90_def_dim, nf90_enddef, nf90_close, nf90_inq_dimid, nf90_inq_varid
7 #else
10 #endif
11  use state_mod, only : model_state_type
24  use mpi, only : mpi_info_null
25  implicit none
26 
27 #ifndef TEST_MODE
28  private
29 #endif
30 
31  character(len=*), parameter :: checkpoint_title = "MONC checkpoint file"
32 
34 
35 contains
36 
40  subroutine write_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_id, y_dim_id, x_dim_id, q_dim_id, x_id, y_id, z_id, th_id, p_id, time_id,&
45  u_id, v_id, w_id, q_id, zu_id, zv_id, zw_id, zth_id, zq_id, timestep_id, ugal_id, &
46  vgal_id, number_q_fields_id, string_dim_id, key_value_dim_id, options_id, q_indices_id, &
47  dtm_id, dtm_new_id, absolute_new_dtm_id
48  logical :: q_indices_declared
49 
50 #ifdef SINGLE_MONC_DO_SEQUENTIAL_NETCDF
51  if (current_state%parallel%processes .gt. 1) then
52  call check_status(nf90_create(filename, ior(nf90_netcdf4, nf90_mpiio), ncid, &
53  comm = current_state%parallel%monc_communicator, info = mpi_info_null))
54  else
55  call check_status(nf90_create(filename, nf90_clobber, ncid))
56  end if
57 #else
58  call check_status(nf90_create(filename, ior(nf90_netcdf4, nf90_mpiio), ncid, &
59  comm = current_state%parallel%monc_communicator, info = mpi_info_null))
60 #endif
62  call define_grid_dimensions(current_state, ncid, z_dim_id, y_dim_id, x_dim_id)
63  if (current_state%number_q_fields .gt. 0) call define_q_field_dimension(current_state, ncid, q_dim_id)
64 
65  call define_options_variable(current_state, ncid, string_dim_id, key_value_dim_id, options_id)
66  q_indices_declared=define_q_indices_variable(ncid, string_dim_id, key_value_dim_id, q_indices_id)
67  call define_grid_variables(current_state, ncid)
68  call define_mean_fields(current_state, ncid)
69  if (current_state%number_q_fields .gt. 0) call define_q_variable(ncid, current_state%parallel%processes .gt. 1, &
70  q_dim_id, z_dim_id, y_dim_id, x_dim_id, q_id, zq_id)
71  call define_prognostic_variables(current_state, current_state%parallel%processes .gt. 1, ncid, z_dim_id, y_dim_id, &
72  x_dim_id, u_id, v_id, w_id, th_id, p_id, zu_id, zv_id, zw_id, zth_id)
73  call define_misc_variables(ncid, timestep_id, time_id, ugal_id, vgal_id, number_q_fields_id, &
74  dtm_id, dtm_new_id, absolute_new_dtm_id)
75 
76  call check_status(nf90_enddef(ncid))
77 
78  if (current_state%parallel%my_rank==0) call write_out_grid(ncid, current_state%global_grid)
79  if (current_state%parallel%my_rank==0) call write_out_mean_fields(ncid, current_state%global_grid)
80  call write_out_all_fields(current_state, ncid, u_id, v_id, w_id, zu_id, zv_id, zw_id, th_id, zth_id, q_id, zq_id, p_id)
81  if (current_state%parallel%my_rank==0) then
82  call write_out_options(current_state, ncid, options_id)
83  if (q_indices_declared) call write_out_q_indices(ncid, q_indices_id)
84  call write_out_misc_variables(current_state, ncid, timestep_id, time_id, &
85  ugal_id, vgal_id, number_q_fields_id, dtm_id, dtm_new_id, absolute_new_dtm_id)
86  end if
87 
89  call define_pdf_fields(current_state, ncid)
90  if (current_state%parallel%my_rank==0) call write_out_pdf_fields(ncid, current_state%global_grid)
91 
92  call check_status(nf90_close(ncid))
93  end subroutine write_checkpoint_file
94 
97  subroutine write_out_global_attributes(ncid)
98  integer, intent(in) :: ncid
99 
100  integer :: date_values(8)
101 
102  call date_and_time(values=date_values)
103 
105  call check_status(nf90_put_att(ncid, nf90_global, created_attribute_key, trim(conv_to_string(date_values(3)))//"/"//&
106  trim(conv_to_string(date_values(2)))//"/"//trim(conv_to_string(date_values(1)))//" "//trim(conv_to_string(&
107  date_values(5)))// ":"//trim(conv_to_string(date_values(6)))//":"//trim(conv_to_string(date_values(7)))))
108  end subroutine write_out_global_attributes
109 
113  subroutine write_out_q_indices(ncid, q_indices_id)
114  integer, intent(in) :: ncid, q_indices_id
115 
116  integer :: i, current_index
117  type(q_metadata_type) :: specific_q_data
118 
119  current_index=1
120  do i=1, get_max_number_q_indices()
121  specific_q_data=get_indices_descriptor(i)
122  if (specific_q_data%l_used) then
123  call check_status(nf90_put_var(ncid, q_indices_id, trim(specific_q_data%name), (/ 1, 1, current_index /)))
124  call check_status(nf90_put_var(ncid, q_indices_id, trim(conv_to_string(i)), (/ 1, 2, current_index /)))
125  current_index=current_index+1
126  end if
127  end do
128  end subroutine write_out_q_indices
129 
134  subroutine write_out_options(current_state, ncid, options_id)
135  type(model_state_type), intent(inout) :: current_state
136  integer, intent(in) :: ncid, options_id
137 
138  integer :: i
139  character(len=STRING_LENGTH), pointer :: sized_raw_character
140  class(*), pointer :: raw_data, raw_to_string
141 
142  do i=1,options_size(current_state%options_database)
143  raw_data=> options_value_at(current_state%options_database, i)
144  raw_to_string=>raw_data
145  call check_status(nf90_put_var(ncid, options_id, trim(options_key_at(current_state%options_database, i)), (/ 1, 1, i /)))
146  select type (raw_data)
147  type is(integer)
148  call check_status(nf90_put_var(ncid, options_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
149  type is(real(kind=single_precision))
150  call check_status(nf90_put_var(ncid, options_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
151  type is(real(kind=double_precision))
152  call check_status(nf90_put_var(ncid, options_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
153  type is(logical)
154  call check_status(nf90_put_var(ncid, options_id, trim(conv_to_string(raw_data)), (/ 1, 2, i /)))
155  type is(character(len=*))
156  ! Done this way to give the character size information and keep the (unsafe) cast in the conversion module
157  sized_raw_character=>conv_to_string(raw_to_string, .false., string_length)
158  call check_status(nf90_put_var(ncid, options_id, trim(sized_raw_character), (/ 1, 2, i /)))
159  end select
160  end do
161  end subroutine write_out_options
162 
169  subroutine write_out_all_fields(current_state, ncid, u_id, v_id, w_id, zu_id, zv_id, zw_id, th_id, zth_id, q_id, zq_id, p_id)
170  type(model_state_type), intent(inout) :: current_state
171  integer, intent(in) :: ncid, u_id, v_id, w_id, zu_id, zv_id, zw_id, th_id, zth_id, q_id, zq_id, p_id
172 
173  integer :: i
174  logical :: multi_process
175 
176  multi_process = current_state%parallel%processes .gt. 1
177 #ifdef U_ACTIVE
178  call write_out_velocity_field(ncid, current_state%local_grid, current_state%u, u_id, multi_process)
179  call write_out_velocity_field(ncid, current_state%local_grid, current_state%zu, zu_id, multi_process)
180 #endif
181 #ifdef V_ACTIVE
182  call write_out_velocity_field(ncid, current_state%local_grid, current_state%v, v_id, multi_process)
183  call write_out_velocity_field(ncid, current_state%local_grid, current_state%zv, zv_id, multi_process)
184 #endif
185 #ifdef W_ACTIVE
186  call write_out_velocity_field(ncid, current_state%local_grid, current_state%w, w_id, multi_process)
187  call write_out_velocity_field(ncid, current_state%local_grid, current_state%zw, zw_id, multi_process)
188 #endif
189  if (current_state%th%active) then
190  call write_out_velocity_field(ncid, current_state%local_grid, current_state%th, th_id, multi_process)
191  call write_out_velocity_field(ncid, current_state%local_grid, current_state%zth, zth_id, multi_process)
192  end if
193  if (current_state%p%active) call write_out_velocity_field(ncid, current_state%local_grid, current_state%p, &
194  p_id, multi_process)
195  do i=1,current_state%number_q_fields
196  if (current_state%q(i)%active) then
197  call write_out_velocity_field(ncid, current_state%local_grid, current_state%q(i), q_id, multi_process, i)
198  call write_out_velocity_field(ncid, current_state%local_grid, current_state%zq(i), zq_id, multi_process, i)
199  end if
200  end do
201  end subroutine write_out_all_fields
202 
208  subroutine write_out_velocity_field(ncid, local_grid, field, variable_id, multi_process, fourth_dim_loc)
209  integer, intent(in) :: ncid, variable_id
210  type(prognostic_field_type), intent(in) :: field
211  type(local_grid_type), intent(inout) :: local_grid
212  logical, intent(in) :: multi_process
213  integer, optional, intent(in) :: fourth_dim_loc
214 
215  integer :: start(4), count(4), i, map(4)
216 
217  if (multi_process .or. present(fourth_dim_loc)) then
218  do i=1,3
219  if (i==1) then
220  map(i)=1
221  else
222  map(i)=map(i-1)*local_grid%size(i-1)
223  end if
224  start(i) = local_grid%start(i)
225  count(i) = local_grid%size(i)
226  end do
227  if (present(fourth_dim_loc)) then
228  start(4) = fourth_dim_loc
229  count(4) = 1
230  map(4)=map(3)*local_grid%size(3)
231  end if
232 
233  call check_status(nf90_put_var(ncid, variable_id, field%data(local_grid%local_domain_start_index(z_index):&
234  local_grid%local_domain_end_index(z_index),local_grid%local_domain_start_index(y_index):&
235  local_grid%local_domain_end_index(y_index), local_grid%local_domain_start_index(x_index):&
236  local_grid%local_domain_end_index(x_index)), start=start, count=count))
237  else
238  call check_status(nf90_put_var(ncid, variable_id, field%data(local_grid%local_domain_start_index(z_index):&
239  local_grid%local_domain_end_index(z_index),local_grid%local_domain_start_index(y_index):&
240  local_grid%local_domain_end_index(y_index), local_grid%local_domain_start_index(x_index):&
241  local_grid%local_domain_end_index(x_index))))
242  end if
243  end subroutine write_out_velocity_field
244 
251  subroutine write_out_grid(ncid, grid)
252  integer, intent(in) :: ncid
253  type(global_grid_type), intent(in) :: grid
254 
255  integer :: var_id
256 
257  if (grid%active(z_index)) then
258  call write_z_grid_gimension(ncid, grid%configuration%vertical)
259  end if
260  if (grid%active(y_index)) then
261  call check_status(nf90_inq_varid(ncid, y_resolution, var_id))
262  call check_status(nf90_put_var(ncid, var_id, grid%resolution(y_index)))
263  call check_status(nf90_inq_varid(ncid, y_top, var_id))
264  call check_status(nf90_put_var(ncid, var_id, grid%top(y_index)))
265  call check_status(nf90_inq_varid(ncid, y_bottom, var_id))
266  call check_status(nf90_put_var(ncid, var_id, grid%bottom(y_index)))
267  end if
268  if (grid%active(x_index)) then
269  call check_status(nf90_inq_varid(ncid, x_resolution, var_id))
270  call check_status(nf90_put_var(ncid, var_id, grid%resolution(x_index)))
271  call check_status(nf90_inq_varid(ncid, x_top, var_id))
272  call check_status(nf90_put_var(ncid, var_id, grid%top(x_index)))
273  call check_status(nf90_inq_varid(ncid, x_bottom, var_id))
274  call check_status(nf90_put_var(ncid, var_id, grid%bottom(x_index)))
275  end if
276  end subroutine write_out_grid
277 
278  subroutine write_out_mean_fields(ncid, grid)
279  integer, intent(in) :: ncid
280  type(global_grid_type), intent(in) :: grid
281 
282  integer :: var_id
283 
284  if (allocated(grid%configuration%vertical%olubar)) then
285  call check_status(nf90_inq_varid(ncid, olubar, var_id))
286  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olubar))
287  end if
288  if (allocated(grid%configuration%vertical%olzubar)) then
289  call check_status(nf90_inq_varid(ncid, olzubar, var_id))
290  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olzubar))
291  end if
292  if (allocated(grid%configuration%vertical%olvbar)) then
293  call check_status(nf90_inq_varid(ncid, olvbar, var_id))
294  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olvbar))
295  end if
296  if (allocated(grid%configuration%vertical%olzvbar)) then
297  call check_status(nf90_inq_varid(ncid, olzvbar, var_id))
298  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olzvbar))
299  end if
300  if (allocated(grid%configuration%vertical%olthbar)) then
301  call check_status(nf90_inq_varid(ncid, olthbar, var_id))
302  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olthbar))
303  end if
304  if (allocated(grid%configuration%vertical%olzthbar)) then
305  call check_status(nf90_inq_varid(ncid, olzthbar, var_id))
306  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olzthbar))
307  end if
308  if (allocated(grid%configuration%vertical%olqbar)) then
309  call check_status(nf90_inq_varid(ncid, olqbar, var_id))
310  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olqbar))
311  end if
312  if (allocated(grid%configuration%vertical%olzqbar)) then
313  call check_status(nf90_inq_varid(ncid, olzqbar, var_id))
314  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%olzqbar))
315  end if
316  end subroutine write_out_mean_fields
317 
322  subroutine write_z_grid_gimension(ncid, vertical_grid)
323  type(vertical_grid_configuration_type), intent(in) :: vertical_grid
324  integer, intent(in) :: ncid
325 
326  integer :: z_var_id, zn_var_id, thref_var_id
327 
328  call check_status(nf90_inq_varid(ncid, z_key, z_var_id))
329  call check_status(nf90_put_var(ncid, z_var_id, vertical_grid%z))
330  call check_status(nf90_inq_varid(ncid, zn_key, zn_var_id))
331  call check_status(nf90_put_var(ncid, zn_var_id, vertical_grid%zn))
332  call check_status(nf90_inq_varid(ncid, thref, thref_var_id))
333  call check_status(nf90_put_var(ncid, thref_var_id, vertical_grid%thref))
334  end subroutine write_z_grid_gimension
335 
341  subroutine define_options_variable(current_state, ncid, string_dim_id, key_value_dim_id, options_id)
342  type(model_state_type), intent(inout) :: current_state
343  integer, intent(in) :: ncid
344  integer, intent(out) :: string_dim_id, key_value_dim_id, options_id
345 
346  integer :: options_dim_id, command_dimensions(3)
347 
348  call check_status(nf90_def_dim(ncid, string_dim_key, string_length, string_dim_id))
349  call check_status(nf90_def_dim(ncid, key_value_pair_key, 2, key_value_dim_id))
350  call check_status(nf90_def_dim(ncid, options_dim_key, options_size(current_state%options_database), options_dim_id))
351 
352  command_dimensions = (/ string_dim_id, key_value_dim_id, options_dim_id /)
353 
354  call check_status(nf90_def_var(ncid, options_key, nf90_char, command_dimensions, options_id))
355  end subroutine define_options_variable
356 
364  logical function define_q_indices_variable(ncid, string_dim_id, key_value_dim_id, q_indices_id)
365  integer, intent(in) :: ncid, string_dim_id, key_value_dim_id
366  integer, intent(out) :: q_indices_id
367 
368  integer :: q_indices_dim_id, command_dimensions(3), number_active_q
369 
370  number_active_q=get_number_active_q_indices()
371 
372  if (number_active_q == 0) then
374  else
375  call check_status(nf90_def_dim(ncid, q_indices_dim_key, number_active_q, q_indices_dim_id))
376 
377  command_dimensions = (/ string_dim_id, key_value_dim_id, q_indices_dim_id /)
378 
379  call check_status(nf90_def_var(ncid, q_indices_key, nf90_char, command_dimensions, q_indices_id))
381  end if
382  end function define_q_indices_variable
383 
388  subroutine define_q_field_dimension(current_state, ncid, q_dim_id)
389  type(model_state_type), intent(inout) :: current_state
390  integer, intent(in) :: ncid
391  integer, intent(out) :: q_dim_id
392 
393  call check_status(nf90_def_dim(ncid, q_dim_key, current_state%number_q_fields, q_dim_id))
394  end subroutine define_q_field_dimension
395 
402  subroutine define_grid_dimensions(current_state, ncid, z_dim_id, y_dim_id, x_dim_id)
403  type(model_state_type), intent(inout) :: current_state
404  integer, intent(in) :: ncid
405  integer, intent(out) :: z_dim_id, y_dim_id, x_dim_id
406 
407  integer :: empty_dim_id
408 
409  call check_status(nf90_def_dim(ncid, empty_dim_key, 1, empty_dim_id))
410 
411  if (current_state%global_grid%active(z_index)) then
412  call check_status(nf90_def_dim(ncid, z_dim_key, current_state%global_grid%size(z_index), z_dim_id))
413  call check_status(nf90_def_dim(ncid, zn_dim_key, current_state%global_grid%size(z_index), z_dim_id))
414  else
415  z_dim_id = empty_dim_id
416  end if
417  if (current_state%global_grid%active(y_index)) then
418  call check_status(nf90_def_dim(ncid, y_dim_key, current_state%global_grid%size(y_index), y_dim_id))
419  else
420  y_dim_id = empty_dim_id
421  end if
422  if (current_state%global_grid%active(x_index)) then
423  call check_status(nf90_def_dim(ncid, x_dim_key, current_state%global_grid%size(x_index), x_dim_id))
424  else
425  x_dim_id = empty_dim_id
426  end if
427  end subroutine define_grid_dimensions
428 
438  subroutine define_grid_variables(current_state, ncid)
439  type(model_state_type), intent(inout) :: current_state
440  integer, intent(in) :: ncid
441 
442  integer :: var_id, z_dim_id
443 
444  if (current_state%global_grid%active(x_index)) then
445  call check_status(nf90_def_var(ncid, x_resolution, nf90_double, var_id))
446  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
447  call check_status(nf90_def_var(ncid, x_top, nf90_double, var_id))
448  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
449  call check_status(nf90_def_var(ncid, x_bottom, nf90_double, var_id))
450  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
451  end if
452  if (current_state%global_grid%active(y_index)) then
453  call check_status(nf90_def_var(ncid, y_resolution, nf90_double, var_id))
454  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
455  call check_status(nf90_def_var(ncid, y_top, nf90_double, var_id))
456  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
457  call check_status(nf90_def_var(ncid, y_bottom, nf90_double, var_id))
458  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
459  end if
460  if (current_state%global_grid%active(z_index)) then
461  call check_status(nf90_inq_dimid(ncid, z_dim_key, z_dim_id))
462  call check_status(nf90_def_var(ncid, z_key, nf90_double, z_dim_id, var_id))
463  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
464  call check_status(nf90_inq_dimid(ncid, zn_dim_key, z_dim_id))
465  call check_status(nf90_def_var(ncid, zn_key, nf90_double, z_dim_id, var_id))
466  call check_status(nf90_put_att(ncid, var_id, "units", "m"))
467  end if
468  call check_status(nf90_inq_dimid(ncid, z_dim_key, z_dim_id))
469  call check_status(nf90_def_var(ncid, thref, nf90_double, z_dim_id, var_id))
470  end subroutine define_grid_variables
471 
472  subroutine define_mean_fields(current_state, ncid)
473  type(model_state_type), intent(inout) :: current_state
474  integer, intent(in) :: ncid
475 
476  integer :: var_id, z_dim_id, q_dim_id, qdimids(2)
477 
478  call check_status(nf90_inq_dimid(ncid, z_dim_key, z_dim_id))
479 
480  if (allocated(current_state%global_grid%configuration%vertical%olubar)) then
481  call check_status(nf90_def_var(ncid, olubar, nf90_double, z_dim_id, var_id))
482  end if
483  if (allocated(current_state%global_grid%configuration%vertical%olzubar)) then
484  call check_status(nf90_def_var(ncid, olzubar, nf90_double, z_dim_id, var_id))
485  end if
486  if (allocated(current_state%global_grid%configuration%vertical%olvbar)) then
487  call check_status(nf90_def_var(ncid, olvbar, nf90_double, z_dim_id, var_id))
488  end if
489  if (allocated(current_state%global_grid%configuration%vertical%olzvbar)) then
490  call check_status(nf90_def_var(ncid, olzvbar, nf90_double, z_dim_id, var_id))
491  end if
492  if (allocated(current_state%global_grid%configuration%vertical%olthbar)) then
493  call check_status(nf90_def_var(ncid, olthbar, nf90_double, z_dim_id, var_id))
494  end if
495  if (allocated(current_state%global_grid%configuration%vertical%olzthbar)) then
496  call check_status(nf90_def_var(ncid, olzthbar, nf90_double, z_dim_id, var_id))
497  end if
498  if (allocated(current_state%global_grid%configuration%vertical%olqbar) .or. &
499  allocated(current_state%global_grid%configuration%vertical%olzqbar)) then
500  call check_status(nf90_inq_dimid(ncid, q_dim_key, q_dim_id))
501  qdimids=(/ z_dim_id, q_dim_id /)
502  if (allocated(current_state%global_grid%configuration%vertical%olqbar)) then
503  call check_status(nf90_def_var(ncid, olqbar, nf90_double, qdimids, var_id))
504  end if
505  if (allocated(current_state%global_grid%configuration%vertical%olzqbar)) then
506  call check_status(nf90_def_var(ncid, olzqbar, nf90_double, qdimids, var_id))
507  end if
508  end if
509  end subroutine define_mean_fields
510 
520  subroutine define_q_variable(ncid, multi_process, q_dim_id, z_dim_id, y_dim_id, x_dim_id, q_id, zq_id)
521  logical, intent(in) :: multi_process
522  integer, intent(in) :: ncid, z_dim_id, y_dim_id, x_dim_id, q_dim_id
523  integer, intent(out) :: q_id, zq_id
524 
525  integer, dimension(:), allocatable :: dimids
526 
527  allocate(dimids(4))
528  dimids = (/ z_dim_id, y_dim_id, x_dim_id, q_dim_id /)
529 
530  call check_status(nf90_def_var(ncid, q_key, merge(nf90_double, nf90_real, &
531  default_precision == double_precision), dimids, q_id))
533  default_precision == double_precision), dimids, zq_id))
534 
535  if (multi_process) then
536  call check_status(nf90_def_var_fill(ncid, q_id, 1, 1))
537  call check_status(nf90_def_var_fill(ncid, zq_id, 1, 1))
538  call check_status(nf90_var_par_access(ncid, q_id, nf90_collective))
539  call check_status(nf90_var_par_access(ncid, zq_id, nf90_collective))
540  end if
541  end subroutine define_q_variable
542 
555  subroutine define_prognostic_variables(current_state, multi_process, ncid, z_dim_id, &
556  y_dim_id, x_dim_id, u_id, v_id, w_id, th_id, p_id, zu_id, zv_id, zw_id, zth_id)
557  type(model_state_type), intent(inout) :: current_state
558  logical, intent(in) :: multi_process
559  integer, intent(in) :: ncid, z_dim_id, y_dim_id, x_dim_id
560  integer, intent(out) :: u_id, v_id, w_id, th_id, p_id, zu_id, zv_id, zw_id, zth_id
561 
562 #ifdef U_ACTIVE
563  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=u_key, field_id=u_id)
564  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=zu_key, field_id=zu_id)
565 #endif
566 #ifdef V_ACTIVE
567  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=v_key, field_id=v_id)
568  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=zv_key, field_id=zv_id)
569 #endif
570 #ifdef W_ACTIVE
571  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=w_key, field_id=w_id)
572  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=zw_key, field_id=zw_id)
573 #endif
574  if (current_state%th%active) then
575  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=th_key, field_id=th_id)
576  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=zth_key, field_id=zth_id)
577  end if
578  if (current_state%p%active) then
579  call define_velocity_variable(ncid, multi_process, z_dim_id, y_dim_id, x_dim_id, field_name=p_key, field_id=p_id)
580  end if
581  end subroutine define_prognostic_variables
582 
586  subroutine define_misc_variables(ncid, timestep_id, time_id, ugal_id, vgal_id, number_q_fields_id, &
587  dtm_id, dtm_new_id, absolute_new_dtm_id)
588  integer, intent(in) :: ncid
589  integer, intent(out) :: timestep_id, time_id, ugal_id, vgal_id, number_q_fields_id, dtm_id, dtm_new_id, absolute_new_dtm_id
590 
591  call check_status(nf90_def_var(ncid, timestep, nf90_int, timestep_id))
592  call check_status(nf90_def_var(ncid, time_key, nf90_double, time_id))
593  call check_status(nf90_def_var(ncid, ugal, nf90_double, ugal_id))
594  call check_status(nf90_def_var(ncid, vgal, nf90_double, vgal_id))
595  call check_status(nf90_def_var(ncid, nqfields, nf90_int, number_q_fields_id))
596  call check_status(nf90_def_var(ncid, dtm_key, nf90_double, dtm_id))
597  call check_status(nf90_def_var(ncid, dtm_new_key, nf90_double, dtm_new_id))
598  call check_status(nf90_def_var(ncid, absolute_new_dtm_key, nf90_double, absolute_new_dtm_id))
599  end subroutine define_misc_variables
600 
605  subroutine write_out_misc_variables(current_state, ncid, timestep_id, time_id, ugal_id, &
606  vgal_id, number_q_fields_id, dtm_id, dtm_new_id, absolute_new_dtm_id)
607  type(model_state_type), intent(inout) :: current_state
608  integer, intent(in) :: ncid, timestep_id, time_id, ugal_id, vgal_id, number_q_fields_id, &
609  dtm_id, dtm_new_id, absolute_new_dtm_id
610 
611  call check_status(nf90_put_var(ncid, timestep_id, current_state%timestep))
612  ! The time is incremented with dtm as the model was about to increment for the next step and this is needed for diagnostics
613  call check_status(nf90_put_var(ncid, time_id, current_state%time+current_state%dtm))
614  call check_status(nf90_put_var(ncid, ugal_id, current_state%ugal))
615  call check_status(nf90_put_var(ncid, vgal_id, current_state%vgal))
616  call check_status(nf90_put_var(ncid, number_q_fields_id, current_state%number_q_fields))
617  call check_status(nf90_put_var(ncid, dtm_id, current_state%dtm))
618  call check_status(nf90_put_var(ncid, dtm_new_id, current_state%dtm_new))
619  call check_status(nf90_put_var(ncid, absolute_new_dtm_id, current_state%absolute_new_dtm))
620  end subroutine write_out_misc_variables
621 
629  subroutine define_velocity_variable(ncid, multi_process, dimone, dimtwo, dimthree, field_name, field_id)
630  integer, intent(in) :: ncid, dimone
631  integer, intent(in), optional :: dimtwo, dimthree
632  integer, intent(out) :: field_id
633  character(len=*), intent(in) :: field_name
634  logical, intent(in) :: multi_process
635 
636  integer, dimension(:), allocatable :: dimids
637 
638  if (present(dimtwo) .and. present(dimthree)) then
639  allocate(dimids(3))
640  dimids = (/ dimone, dimtwo, dimthree /)
641  else if (present(dimtwo) .or. present(dimthree)) then
642  allocate(dimids(2))
643  dimids = (/ dimone, merge(dimtwo, dimthree, present(dimtwo)) /)
644  else
645  allocate(dimids(1))
646  dimids = (/ dimone /)
647  end if
648 
650  dimids, field_id))
651  if (multi_process) then
652  call check_status(nf90_def_var_fill(ncid, field_id, 1, 1))
653  call check_status(nf90_var_par_access(ncid, field_id, nf90_collective))
654  end if
655  call check_status(nf90_put_att(ncid, field_id, "units", "m/s"))
656  end subroutine define_velocity_variable
657 
658  subroutine define_pdf_fields(current_state, ncid)
659  type(model_state_type), intent(inout) :: current_state
660  integer, intent(in) :: ncid
661 
662  integer :: var_id, z_dim_id
663 
664  call check_status(nf90_inq_dimid(ncid, z_dim_key, z_dim_id))
665 
666  if (allocated(current_state%global_grid%configuration%vertical%w_up)) then
667  call check_status(nf90_def_var(ncid, wup, nf90_double, z_dim_id, var_id))
668  end if
669  if (allocated(current_state%global_grid%configuration%vertical%w_dwn)) then
670  call check_status(nf90_def_var(ncid, wdwn, nf90_double, z_dim_id, var_id))
671  end if
672  end subroutine define_pdf_fields
673 
674  subroutine write_out_pdf_fields(ncid, grid)
675  integer, intent(in) :: ncid
676  type(global_grid_type), intent(in) :: grid
677 
678  integer :: var_id
679 
680  if (allocated(grid%configuration%vertical%w_up)) then
681  call check_status(nf90_inq_varid(ncid, wup, var_id))
682  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%w_up))
683  end if
684  if (allocated(grid%configuration%vertical%w_dwn)) then
685  call check_status(nf90_inq_varid(ncid, wdwn, var_id))
686  call check_status(nf90_put_var(ncid, var_id, grid%configuration%vertical%w_dwn))
687  end if
688  end subroutine write_out_pdf_fields
689 
checkpointer_write_checkpoint_mod::define_grid_dimensions
subroutine define_grid_dimensions(current_state, ncid, z_dim_id, y_dim_id, x_dim_id)
Will define the grid dimensions and works for 1, 2 or 3D grids_mod.
Definition: writecheckpoint.F90:403
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
checkpointer_write_checkpoint_mod::write_out_q_indices
subroutine write_out_q_indices(ncid, q_indices_id)
Writes out the specific Q indicies that are active and need writing.
Definition: writecheckpoint.F90:114
checkpointer_common_mod::olubar
character(len= *), parameter olubar
Definition: checkpointcommon.F90:11
checkpointer_common_mod::p_key
character(len= *), parameter p_key
Pressure variable NetCDF key.
Definition: checkpointcommon.F90:11
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
optionsdatabase_mod::options_key_at
character(len=string_length) function, public options_key_at(options_database, i)
Returns the ith key in the options database.
Definition: optionsdatabase.F90:53
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
checkpointer_common_mod::thref
character(len= *), parameter thref
Definition: checkpointcommon.F90:11
checkpointer_common_mod::key_value_pair_key
character(len= *), parameter key_value_pair_key
Key-value pair dimension key.
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::write_checkpoint_file
subroutine, public write_checkpoint_file(current_state, filename)
Will write out the current model state_mod into a NetCDF checkpoint file.
Definition: writecheckpoint.F90:41
checkpointer_write_checkpoint_mod::write_out_misc_variables
subroutine write_out_misc_variables(current_state, ncid, timestep_id, time_id, ugal_id, vgal_id, number_q_fields_id, dtm_id, dtm_new_id, absolute_new_dtm_id)
Will dump out (write) misc model data to the checkpoint.
Definition: writecheckpoint.F90:607
checkpointer_common_mod::zv_key
character(len= *), parameter zv_key
Definition: checkpointcommon.F90:11
checkpointer_common_mod::y_top
character(len= *), parameter y_top
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_create
integer function nf90_create(path, mode, ncid, comm, info)
Definition: dummy_netcdf.F90:74
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
dummy_netcdf_mod::nf90_netcdf4
integer, parameter nf90_netcdf4
Definition: dummy_netcdf.F90:24
checkpointer_write_checkpoint_mod::write_out_options
subroutine write_out_options(current_state, ncid, options_id)
Writes out the options that the model was run with.
Definition: writecheckpoint.F90:135
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
checkpointer_common_mod::x_key
character(len= *), parameter x_key
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::define_grid_variables
subroutine define_grid_variables(current_state, ncid)
Defines the NetCDF grid variables. This works for 1, 2 or 3D grids_mod.
Definition: writecheckpoint.F90:439
dummy_netcdf_mod::nf90_def_dim
integer function nf90_def_dim(ncid, key, length, dimension_id)
Definition: dummy_netcdf.F90:367
checkpointer_common_mod::v_key
character(len= *), parameter v_key
V variable NetCDF key.
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::define_q_indices_variable
logical function define_q_indices_variable(ncid, string_dim_id, key_value_dim_id, q_indices_id)
Defines the NetCDF Q indices variable which is, same as the options, stored as key-value pair of stri...
Definition: writecheckpoint.F90:365
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
checkpointer_common_mod::olzvbar
character(len= *), parameter olzvbar
Definition: checkpointcommon.F90:11
checkpointer_common_mod::zu_key
character(len= *), parameter zu_key
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::define_q_variable
subroutine define_q_variable(ncid, multi_process, q_dim_id, z_dim_id, y_dim_id, x_dim_id, q_id, zq_id)
Defines the Q variable in the checkpoint file.
Definition: writecheckpoint.F90:521
dummy_netcdf_mod::nf90_char
integer, parameter nf90_char
Definition: dummy_netcdf.F90:24
dummy_netcdf_mod::nf90_mpiio
integer, parameter nf90_mpiio
Definition: dummy_netcdf.F90:24
checkpointer_common_mod::z_dim_key
character(len= *), parameter z_dim_key
Z dimension/variable key.
Definition: checkpointcommon.F90:11
checkpointer_common_mod::options_dim_key
character(len= *), parameter options_dim_key
Options dimension key.
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::write_out_mean_fields
subroutine write_out_mean_fields(ncid, grid)
Definition: writecheckpoint.F90:279
q_indices_mod::get_number_active_q_indices
integer function, public get_number_active_q_indices()
Gets the number of active Q indicies (i.e. those allocated to specific uses)
Definition: q_indices.F90:87
checkpointer_common_mod::wup
character(len= *), parameter wup
Definition: checkpointcommon.F90:11
checkpointer_common_mod::x_bottom
character(len= *), parameter x_bottom
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::define_velocity_variable
subroutine define_velocity_variable(ncid, multi_process, dimone, dimtwo, dimthree, field_name, field_id)
Will define a single velocity variable in the NetCDF file.
Definition: writecheckpoint.F90:630
checkpointer_write_checkpoint_mod::define_mean_fields
subroutine define_mean_fields(current_state, ncid)
Definition: writecheckpoint.F90:473
checkpointer_common_mod::olvbar
character(len= *), parameter olvbar
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::write_out_all_fields
subroutine write_out_all_fields(current_state, ncid, u_id, v_id, w_id, zu_id, zv_id, zw_id, th_id, zth_id, q_id, zq_id, p_id)
Will write out all prognostic model fields to the checkpoint. It will work in 1, 2 or 3D depending on...
Definition: writecheckpoint.F90:170
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_write_checkpoint_mod::write_out_pdf_fields
subroutine write_out_pdf_fields(ncid, grid)
Definition: writecheckpoint.F90:675
checkpointer_common_mod::w_key
character(len= *), parameter w_key
W variable NetCDF key.
Definition: checkpointcommon.F90:11
datadefn_mod::single_precision
integer, parameter, public single_precision
Single precision (32 bit) kind.
Definition: datadefn.F90:13
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
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
dummy_netcdf_mod::nf90_def_var
Definition: dummy_netcdf.F90:38
optionsdatabase_mod::options_size
integer function, public options_size(options_database)
Returns the number of entries in the options database.
Definition: optionsdatabase.F90:43
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
checkpointer_common_mod::y_bottom
character(len= *), parameter y_bottom
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::write_out_grid
subroutine write_out_grid(ncid, grid)
Will write out the grid to the checkpoint, it will work in 1, 2 or 3D depending on what is in the mod...
Definition: writecheckpoint.F90:252
checkpointer_common_mod::string_dim_key
character(len= *), parameter string_dim_key
String dimension key.
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod
Writes out model state_mod to a checkpoint NetCDF file.
Definition: writecheckpoint.F90:2
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
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
dummy_netcdf_mod::nf90_int
integer, parameter nf90_int
Definition: dummy_netcdf.F90:24
checkpointer_write_checkpoint_mod::define_options_variable
subroutine define_options_variable(current_state, ncid, string_dim_id, key_value_dim_id, options_id)
Defines the NetCDF options variable which is basically a 3D character array to form key-value pair st...
Definition: writecheckpoint.F90:342
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
checkpointer_common_mod::olzqbar
character(len= *), parameter olzqbar
Definition: checkpointcommon.F90:11
checkpointer_common_mod::q_dim_key
character(len= *), parameter q_dim_key
Definition: checkpointcommon.F90:11
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
checkpointer_common_mod::zn_dim_key
character(len= *), parameter zn_dim_key
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_put_var
Definition: dummy_netcdf.F90:32
dummy_netcdf_mod::nf90_real
integer, parameter nf90_real
Definition: dummy_netcdf.F90:24
dummy_netcdf_mod::nf90_double
integer, parameter nf90_double
Definition: dummy_netcdf.F90:24
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::x_resolution
character(len= *), parameter x_resolution
Definition: checkpointcommon.F90:11
prognostics_mod::prognostic_field_type
A prognostic field which is assumed to be 3D.
Definition: prognostics.F90:13
datadefn_mod::double_precision
integer, parameter, public double_precision
Double precision (64 bit) kind.
Definition: datadefn.F90:14
grids_mod::vertical_grid_configuration_type
The configuration of the grid vertically.
Definition: grids.F90:28
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
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_write_checkpoint_mod::define_q_field_dimension
subroutine define_q_field_dimension(current_state, ncid, q_dim_id)
Defines the Q field dimension in the NetCDF.
Definition: writecheckpoint.F90:389
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_write_checkpoint_mod::checkpoint_title
character(len= *), parameter checkpoint_title
Title of the NetCDF file.
Definition: writecheckpoint.F90:31
q_indices_mod::get_max_number_q_indices
integer function, public get_max_number_q_indices()
Gets the maximum number of Q indicies.
Definition: q_indices.F90:81
checkpointer_write_checkpoint_mod::write_out_global_attributes
subroutine write_out_global_attributes(ncid)
Writes out global attributes into the checkpoint.
Definition: writecheckpoint.F90:98
checkpointer_write_checkpoint_mod::define_prognostic_variables
subroutine define_prognostic_variables(current_state, multi_process, ncid, z_dim_id, y_dim_id, x_dim_id, u_id, v_id, w_id, th_id, p_id, zu_id, zv_id, zw_id, zth_id)
Defines prognostic variables in the NetCDF. This handles 1, 2 and 3D grids_mod and 1,...
Definition: writecheckpoint.F90:557
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
optionsdatabase_mod::options_value_at
class(*) function, pointer, public options_value_at(options_database, i)
Returns the value at index in the database.
Definition: optionsdatabase.F90:64
checkpointer_common_mod::th_key
character(len= *), parameter th_key
Theta variable NetCDF key.
Definition: checkpointcommon.F90:11
dummy_netcdf_mod::nf90_enddef
integer function nf90_enddef(ncid)
Definition: dummy_netcdf.F90:101
checkpointer_common_mod::x_dim_key
character(len= *), parameter x_dim_key
X dimension/variable key.
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::write_z_grid_gimension
subroutine write_z_grid_gimension(ncid, vertical_grid)
Writes out the Z dimension of the grids_mod points which are explicitly calculated.
Definition: writecheckpoint.F90:323
checkpointer_common_mod::nqfields
character(len= *), parameter nqfields
Definition: checkpointcommon.F90:11
checkpointer_common_mod::y_resolution
character(len= *), parameter y_resolution
Definition: checkpointcommon.F90:11
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
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
checkpointer_write_checkpoint_mod::define_pdf_fields
subroutine define_pdf_fields(current_state, ncid)
Definition: writecheckpoint.F90:659
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
dummy_netcdf_mod::nf90_clobber
integer, parameter nf90_clobber
Definition: dummy_netcdf.F90:24
checkpointer_write_checkpoint_mod::write_out_velocity_field
subroutine write_out_velocity_field(ncid, local_grid, field, variable_id, multi_process, fourth_dim_loc)
Will write out a single velocity field to the checkpoint file. If there are multiple processes then w...
Definition: writecheckpoint.F90:209
dummy_netcdf_mod::nf90_put_att
integer function nf90_put_att(ncid, attribute, key, value)
Definition: dummy_netcdf.F90:86
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_common_mod::ugal
character(len= *), parameter ugal
Definition: checkpointcommon.F90:11
checkpointer_write_checkpoint_mod::define_misc_variables
subroutine define_misc_variables(ncid, timestep_id, time_id, ugal_id, vgal_id, number_q_fields_id, dtm_id, dtm_new_id, absolute_new_dtm_id)
Defines misc variables in the NetCDF file.
Definition: writecheckpoint.F90:588
checkpointer_common_mod::options_key
character(len= *), parameter options_key
Options variable key.
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::x_top
character(len= *), parameter x_top
Definition: checkpointcommon.F90:11
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