MONC
Data Types | Functions/Subroutines
io_server_state_reader_mod Module Reference

Reads the IO server state that was stored in a NetCDF checkpoint file. More...

Data Types

interface  nc_get_vara_long
 ISO C binding for NetCDF get long scalar variable, required for retrieving long variables. More...
 
interface  nc_get_vars_text
 ISO C binding for NetCDF get text vars, required for 64 bit start, count & stride. More...
 
interface  nc_inq_dim
 ISO C binding for NetCDF inquire dimension, required for 64 bit dimension length. More...
 
interface  writer_field_manager_unserialise_state
 

Functions/Subroutines

subroutine, public read_io_server_configuration (checkpoint_filename, io_xml_configuration, io_communicator_arg)
 Reads the IO server configuration, which is the XML configuration initially run with and stored in the checkpoint. Note that this will open, read the XML in and then close the file. More...
 
subroutine, public reactivate_writer_federator_state (io_configuration, writer_entries, time_points)
 Reactivates the writer federator and everything beneath it (i.e. just not the writer field manager.) For memory reasons this explicitly reopens the checkpoint file, will read each individual byte code entry in & repackage before deallocating memory and moving onto the next entry. The file is then closed. More...
 
subroutine, public reactivate_writer_field_manager_state (io_configuration, unserialise_writer_field_manager)
 Reactivates the writer field manager state from the checkpoint file, for memory reasons this will open the file, read in and deserialise the byte code before closing it. More...
 
subroutine get_io_server_configuration (ncid, io_xml_configuration)
 Retrieves the IO server XML configuration from the checkpoint file. More...
 
subroutine get_io_server_serialised_bytes (ncid, number_io_server, my_io_server_rank, base_key, raw_bytes)
 Retrieves some IO server serialised bytes which will make up the state of a specific facet. Note that this uses the ISO C bindings in order to support 64 bit starts, counts & strides along with 64 bit scalar long variable fields. More...
 
subroutine restart_writer_state_from_checkpoint (writer_entries, raw_bytes)
 Restarts the writer state from a specific checkpoint byte data chunk of memory. More...
 
subroutine restart_writer_state_timepoints (time_points, raw_bytes)
 Restarts the writer state timepoints held in the writer federator. More...
 
subroutine restart_timeaveraged_state_from_checkpoint (raw_bytes)
 Will restart the time averaged manipulation state from the checkpoint file. More...
 
subroutine restart_instantaneous_state_from_checkpoint (raw_bytes)
 Will restart the instantaneous manipulation state from the checkpoint file. More...
 
subroutine restart_writer_field_manager_from_checkpoint (unserialise_writer_field_manager, raw_bytes)
 Will restart the field manager state from the checkpoint file. More...
 

Detailed Description

Reads the IO server state that was stored in a NetCDF checkpoint file.

Function/Subroutine Documentation

◆ get_io_server_configuration()

subroutine io_server_state_reader_mod::get_io_server_configuration ( integer, intent(in)  ncid,
character, dimension(:), intent(inout), allocatable  io_xml_configuration 
)
private

Retrieves the IO server XML configuration from the checkpoint file.

Parameters
ncidThe NetCDF checkpoint file ID
io_xml_configurationXML configuration is read from the checkpoint and placed into here

Definition at line 169 of file io_state_reader.F90.

170  integer, intent(in) :: ncid
171  character, dimension(:), allocatable, intent(inout) :: io_xml_configuration
172 
173  integer :: dim_id, var_id, dim_size
174  logical :: found
175 
176  call check_netcdf_status(nf90_inq_dimid(ncid, "io_configuration_dim", dim_id), found)
177  if (.not. found) return
178  call check_netcdf_status(nf90_inquire_dimension(ncid, dim_id, len=dim_size))
179 
180  call check_netcdf_status(nf90_inq_varid(ncid, "io_configuration", var_id), found)
181  if (.not. found) return
182  allocate(io_xml_configuration(dim_size))
183  call check_netcdf_status(nf90_get_var(ncid, var_id, io_xml_configuration, count=(/dim_size/)))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ get_io_server_serialised_bytes()

subroutine io_server_state_reader_mod::get_io_server_serialised_bytes ( integer, intent(in)  ncid,
integer, intent(in)  number_io_server,
integer, intent(in)  my_io_server_rank,
character(len=*), intent(in)  base_key,
character, dimension(:), intent(out), allocatable  raw_bytes 
)
private

Retrieves some IO server serialised bytes which will make up the state of a specific facet. Note that this uses the ISO C bindings in order to support 64 bit starts, counts & strides along with 64 bit scalar long variable fields.

Parameters
ncidThe NetCDF checkpoint file ID
number_io_serverThe number of IO servers
my_io_server_rankMy IO server rank
base_keyThe base look up key to retrieve the state which is stored in the file
raw_bytesThe retrieved raw bytes as they sit in the file, this is allocated to hold the required data

Definition at line 193 of file io_state_reader.F90.

194  integer, intent(in) :: ncid, number_io_server, my_io_server_rank
195  character(len=*), intent(in) :: base_key
196  character, dimension(:), allocatable, intent(out) :: raw_bytes
197 
198  integer :: dim_id, var_id
199  logical :: found
200  integer(kind=8) :: dim_size, serialised_range(2), number_serialised_entries
201 
202  integer(kind=c_int) :: cncid, cdimid, cstatus, cvarid
203  integer(kind=c_size_t) :: cdlen
204  character(len=256) :: tmpname
205  integer(KIND=c_size_t), target :: cstart(1), ccounts(1)
206  Integer(KIND=c_ptrdiff_t), target :: cstrides(1)
207  type(c_ptr) :: cstartptr, ccountsptr, cstridesptr
208 
209  cncid=ncid
210  cstartptr=c_loc(cstart)
211  ccountsptr=c_loc(ccounts)
212  cstridesptr=c_loc(cstrides)
213 
214  call check_netcdf_status(nf90_inq_dimid(ncid, trim(base_key)//"_dim", dim_id), found)
215  if (.not. found) return
216 
217  cdimid=dim_id-1
218  call check_netcdf_status(nc_inq_dim(cncid, cdimid, tmpname, cdlen))
219  dim_size=cdlen
220 
221  call check_netcdf_status(nf90_inq_varid(ncid, trim(base_key)//"_directory", var_id), found)
222  if (.not. found) return
223  cvarid=var_id-1
224  cstart(1)=my_io_server_rank
225  if (my_io_server_rank .lt. number_io_server-1) then
226  ccounts(1)=2
227  call check_netcdf_status(nc_get_vara_long(cncid, cvarid, cstartptr, ccountsptr, serialised_range))
228  if (serialised_range(2) .gt. dim_size) then
229  call log_log(log_error, "Serialised entry beyond size in the file")
230  end if
231  else
232  ccounts(1)=1
233  call check_netcdf_status(nc_get_vara_long(cncid, cvarid, cstartptr, ccountsptr, serialised_range))
234  serialised_range(2)=dim_size
235  end if
236  number_serialised_entries=(serialised_range(2)-serialised_range(1)) + 1
237  call check_netcdf_status(nf90_inq_varid(ncid, trim(base_key), var_id), found)
238  if (.not. found) return
239  allocate(raw_bytes(number_serialised_entries))
240 
241  cvarid=var_id-1
242  cstart=serialised_range(1)-1
243  ccounts=number_serialised_entries
244  cstrides(1)=1
245  call check_netcdf_status(nc_get_vars_text(cncid, cvarid, cstartptr, ccountsptr, cstridesptr, raw_bytes))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ reactivate_writer_federator_state()

subroutine, public io_server_state_reader_mod::reactivate_writer_federator_state ( type(io_configuration_type), intent(inout)  io_configuration,
type(writer_type), dimension(:)  writer_entries,
type(hashmap_type), intent(inout), volatile  time_points 
)

Reactivates the writer federator and everything beneath it (i.e. just not the writer field manager.) For memory reasons this explicitly reopens the checkpoint file, will read each individual byte code entry in & repackage before deallocating memory and moving onto the next entry. The file is then closed.

Parameters
io_configurationThe IO server configuration
writer_entriesThe configured but empty writer entries to unpack the state into
time_pointsTime points to unpack the state into

Definition at line 105 of file io_state_reader.F90.

106  type(io_configuration_type), intent(inout) :: io_configuration
107  type(writer_type), dimension(:) :: writer_entries
108  type(hashmap_type), volatile, intent(inout) :: time_points
109 
110  integer :: ncid, ierr, i
111  character, dimension(:), allocatable :: raw_bytes
112 
113  call check_netcdf_status(nf90_open(path = options_get_string(io_configuration%options_database, "checkpoint"), &
114  mode = nf90_nowrite, ncid = ncid))
115 
116  do i=1, size(writer_entries)
117  ! Note that the different writer entries are dealt with separately for memory reasons
118  if (writer_entries(i)%include_in_io_state_write) then
119  call get_io_server_serialised_bytes(ncid, io_configuration%number_of_io_servers, io_configuration%my_io_rank, &
120  "serialised_writer_entry_"//trim(conv_to_string(i)), raw_bytes)
121  call unserialise_writer_type(writer_entries(i), raw_bytes)
122  deallocate(raw_bytes)
123  end if
124  end do
125 
126  call get_io_server_serialised_bytes(ncid, io_configuration%number_of_io_servers, io_configuration%my_io_rank, &
127  "serialised_timeaveraged_manipulation", raw_bytes)
128  call restart_timeaveraged_state_from_checkpoint(raw_bytes)
129  deallocate(raw_bytes)
130 
131  call get_io_server_serialised_bytes(ncid, io_configuration%number_of_io_servers, io_configuration%my_io_rank, &
132  "serialised_instantaneous_manipulation", raw_bytes)
133  call restart_instantaneous_state_from_checkpoint(raw_bytes)
134  deallocate(raw_bytes)
135 
136  call get_io_server_serialised_bytes(ncid, io_configuration%number_of_io_servers, io_configuration%my_io_rank, &
137  "serialised_timepoints", raw_bytes)
138  call restart_writer_state_timepoints(time_points, raw_bytes)
139  deallocate(raw_bytes)
140 
141  call check_netcdf_status(nf90_close(ncid))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ reactivate_writer_field_manager_state()

subroutine, public io_server_state_reader_mod::reactivate_writer_field_manager_state ( type(io_configuration_type), intent(inout)  io_configuration,
procedure(writer_field_manager_unserialise_state unserialise_writer_field_manager 
)

Reactivates the writer field manager state from the checkpoint file, for memory reasons this will open the file, read in and deserialise the byte code before closing it.

Parameters
io_configurationIO server configuration
unserialise_writer_field_managerProcedure pointer to the unserialisation for the writer field manager

Definition at line 148 of file io_state_reader.F90.

149  type(io_configuration_type), intent(inout) :: io_configuration
150  procedure(writer_field_manager_unserialise_state) :: unserialise_writer_field_manager
151 
152  integer :: ncid, ierr
153  character, dimension(:), allocatable :: raw_bytes
154 
155  call check_netcdf_status(nf90_open(path = options_get_string(io_configuration%options_database, "checkpoint"), &
156  mode = nf90_nowrite, ncid = ncid))
157 
158  call get_io_server_serialised_bytes(ncid, io_configuration%number_of_io_servers, io_configuration%my_io_rank, &
159  "serialised_writer_manager", raw_bytes)
160  call restart_writer_field_manager_from_checkpoint(unserialise_writer_field_manager, raw_bytes)
161  deallocate(raw_bytes)
162 
163  call check_netcdf_status(nf90_close(ncid))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ read_io_server_configuration()

subroutine, public io_server_state_reader_mod::read_io_server_configuration ( character(len=string_length), intent(in)  checkpoint_filename,
character, dimension(:), intent(inout), allocatable  io_xml_configuration,
integer, intent(in)  io_communicator_arg 
)

Reads the IO server configuration, which is the XML configuration initially run with and stored in the checkpoint. Note that this will open, read the XML in and then close the file.

Parameters
checkpoint_filenameThe checkpoint filename to open and read from
io_xml_configurationXML configuration is read from the checkpoint and placed into here
io_communicator_argThe MPI IO server communicator

Definition at line 71 of file io_state_reader.F90.

72  character(len=STRING_LENGTH), intent(in) :: checkpoint_filename
73  character, dimension(:), allocatable, intent(inout) :: io_xml_configuration
74  integer, intent(in) :: io_communicator_arg
75 
76  integer :: ncid, number_io_server, my_io_server_rank, ierr
77  integer :: dim_id, dim_size
78  logical :: found
79 
80  call mpi_comm_rank(io_communicator_arg, my_io_server_rank, ierr)
81  call mpi_comm_size(io_communicator_arg, number_io_server, ierr)
82  call check_netcdf_status(nf90_open(path = checkpoint_filename, mode = nf90_nowrite, ncid = ncid))
83  call check_netcdf_status(nf90_inq_dimid(ncid, "entries_directory_dim", dim_id), found)
84  if (.not. found) then
85  if (my_io_server_rank==0) then
86  call log_log(log_warn, "Restarting the IO server fresh as the checkpoint file does not contain IO state")
87  end if
88  return
89  end if
90  call check_netcdf_status(nf90_inquire_dimension(ncid, dim_id, len=dim_size))
91 
92  if (dim_size .ne. number_io_server) then
93  call log_log(log_error, "Can not restart IO server with a different number of IO servers")
94  end if
95  call get_io_server_configuration(ncid, io_xml_configuration)
96  call check_netcdf_status(nf90_close(ncid))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ restart_instantaneous_state_from_checkpoint()

subroutine io_server_state_reader_mod::restart_instantaneous_state_from_checkpoint ( character, dimension(:), allocatable  raw_bytes)
private

Will restart the instantaneous manipulation state from the checkpoint file.

Parameters
raw_byteThe serialised byte state to unpackage and restart from

Definition at line 312 of file io_state_reader.F90.

313  character, dimension(:), allocatable :: raw_bytes
314 
315  if (.not. allocated(raw_bytes)) then
316  call log_master_log(log_warn, "On restart no instantaneous state in checkpoint file")
317  return
318  end if
319  call unserialise_instantaneous_state(raw_bytes)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ restart_timeaveraged_state_from_checkpoint()

subroutine io_server_state_reader_mod::restart_timeaveraged_state_from_checkpoint ( character, dimension(:), allocatable  raw_bytes)
private

Will restart the time averaged manipulation state from the checkpoint file.

Parameters
raw_byteThe serialised byte state to unpackage and restart from

Definition at line 300 of file io_state_reader.F90.

301  character, dimension(:), allocatable :: raw_bytes
302 
303  if (.not. allocated(raw_bytes)) then
304  call log_master_log(log_warn, "On restart no time averaged state in checkpoint file")
305  return
306  end if
307  call unserialise_time_averaged_state(raw_bytes)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ restart_writer_field_manager_from_checkpoint()

subroutine io_server_state_reader_mod::restart_writer_field_manager_from_checkpoint ( procedure(writer_field_manager_unserialise_state unserialise_writer_field_manager,
character, dimension(:), allocatable  raw_bytes 
)
private

Will restart the field manager state from the checkpoint file.

Parameters
unserialise_writer_field_managerThe unserialise field manager procedure, done this way due to module ordering
raw_byteThe serialised byte state to unpackage and restart from

Definition at line 325 of file io_state_reader.F90.

326  procedure(writer_field_manager_unserialise_state) :: unserialise_writer_field_manager
327  character, dimension(:), allocatable :: raw_bytes
328 
329  if (.not. allocated(raw_bytes)) then
330  call log_master_log(log_warn, "On restart no writer field manager state in checkpoint file")
331  return
332  end if
333  call unserialise_writer_field_manager(raw_bytes)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ restart_writer_state_from_checkpoint()

subroutine io_server_state_reader_mod::restart_writer_state_from_checkpoint ( type(writer_type), dimension(:)  writer_entries,
character, dimension(:), allocatable  raw_bytes 
)
private

Restarts the writer state from a specific checkpoint byte data chunk of memory.

Parameters
writer_entriesThe array of writer entries to fill in
raw_byteThe serialised byte state to unpackage and restart from

Definition at line 251 of file io_state_reader.F90.

252  type(writer_type), dimension(:) :: writer_entries
253  character, dimension(:), allocatable :: raw_bytes
254 
255  integer :: i, number_entries, current_point, byte_size
256 
257  if (.not. allocated(raw_bytes)) then
258  call log_master_log(log_warn, "On restart no writer state in checkpoint file")
259  return
260  end if
261  current_point=1
262  number_entries=unpack_scalar_integer_from_bytedata(raw_bytes, current_point)
263  if (number_entries .ne. size(writer_entries)) then
264  call log_log(log_error, "On restart have a different number of configured entries than those in the checkpoint file")
265  end if
266  do i=1, size(writer_entries)
267  if (writer_entries(i)%include_in_io_state_write) then
268  byte_size=unpack_scalar_integer_from_bytedata(raw_bytes, current_point)
269  call unserialise_writer_type(writer_entries(i), raw_bytes(current_point:current_point+byte_size-1))
270  current_point=current_point+byte_size
271  end if
272  end do
Here is the call graph for this function:

◆ restart_writer_state_timepoints()

subroutine io_server_state_reader_mod::restart_writer_state_timepoints ( type(hashmap_type), intent(inout), volatile  time_points,
character, dimension(:), allocatable  raw_bytes 
)
private

Restarts the writer state timepoints held in the writer federator.

Parameters
time_pointsThe timepoints hashmap which is filled in from the serialised version
raw_byteThe serialised byte state to unpackage and restart from

Definition at line 278 of file io_state_reader.F90.

279  type(hashmap_type), volatile, intent(inout) :: time_points
280  character, dimension(:), allocatable :: raw_bytes
281 
282  integer :: i, number_entries, current_point, byte_size, timestep_key
283  real(kind=default_precision) :: r_value
284 
285  if (.not. allocated(raw_bytes)) then
286  call log_master_log(log_warn, "On restart no writer state timepoints in checkpoint file")
287  return
288  end if
289  current_point=1
290  number_entries=unpack_scalar_integer_from_bytedata(raw_bytes, current_point)
291  do i=1, number_entries
292  timestep_key=unpack_scalar_integer_from_bytedata(raw_bytes, current_point)
293  r_value=unpack_scalar_dp_real_from_bytedata(raw_bytes, current_point)
294  call c_put_real(time_points, conv_to_string(timestep_key), r_value)
295  end do
Here is the call graph for this function:
Here is the caller graph for this function:
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
logging_mod::log_warn
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
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
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
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