MONC
Data Types | Functions/Subroutines
monc_mod Module Reference

Main core entry point to the rest of the model, this is called by the program main. More...

Data Types

interface  io_server_run_procedure
 IO server entry procedure which may be passed to the core entry point (if IO server is enabled) More...
 

Functions/Subroutines

subroutine, public monc_core_bootstrap (component_descriptions, io_server_run)
 Main core entry point to bootstrap running the model. More...
 
logical function determine_if_io_server_enabled (options_database)
 Determines whether the IO server should be enabled or not. More...
 
subroutine load_model_configuration (state, options_database)
 Loads the configuration into the options database, either from a file or checkpoint. More...
 
subroutine monc_run (component_descriptions, state)
 Called by MONC processes to run the MONC model. More...
 
subroutine perform_model_steps (state, timestepping_time, modeldump_time)
 Will run through the actual model stages and call the appropriate callbacks at each stage. More...
 
subroutine display_timestep_information (timestep, start_time)
 Provides timestepping information about the current step and performance. More...
 
subroutine fill_registry_with_components (options_database, component_descriptions)
 Registers each supplied component description. More...
 
logical function is_present_and_true (options_database, key)
 Determines whether an option is present in the database and true. This combines the key check and getting the value. Just calling to get the value directly will error if it does not exist, we don't nescesarily want for checking optional command line flags. More...
 
subroutine display_registed_components ()
 Displays the registered components and their version numbers. More...
 
subroutine split_communicator_into_monc_and_io (moncs_per_io, monc_communicator, io_communicator, am_i_monc_process, corresponding_io_server_process)
 Splits the MPI_COMM_WORLD communicator into MONC and IO separate communicators. The size of each depends on the stride supplied. This will deal with the case where you only have 1 extra process, for instance 3 MONCs to an IO server with 5 processes. 0=IO server, 1-3 are MONCS but by rights 4 would be an IO server. However we dont want to waste a process as an IO server which is not serving anything, hence in this edge case it will be used as a MONC instead. More...
 
integer function get_number_io_processes (total_ranks, moncs_per_io)
 Based upon the total number of processes and the IO process id stride determines the number of processes that will be used for the IO server. The MONC processes is total processes - io processes. More...
 
subroutine get_io_configuration (options_database, ioserver_configuration_file, moncs_per_io_server)
 Reads the IO server configuration and populates the required variables of the configuration file name and the placement period. More...
 
integer function get_mpi_threading_mode ()
 Retrives the configured MPI threading mode, this is serialized by default but can be overridden via environment variable. More...
 
character(len=string_length) function mpi_threading_level_to_string (lvl)
 Converts an MPI threading level to the string representation of it. More...
 

Detailed Description

Main core entry point to the rest of the model, this is called by the program main.

Function/Subroutine Documentation

◆ determine_if_io_server_enabled()

logical function monc_mod::determine_if_io_server_enabled ( type(hashmap_type), intent(inout)  options_database)
private

Determines whether the IO server should be enabled or not.

Parameters
options_databaseThe options database
Returns
Whether to enable the IO server or not

Definition at line 104 of file monc.F90.

104  type(hashmap_type), intent(inout) :: options_database
105 
106  determine_if_io_server_enabled=options_get_logical(options_database, "enable_io_server")
107  if (determine_if_io_server_enabled) then
108  determine_if_io_server_enabled=options_get_logical(options_database, "iobridge_enabled")
109  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ display_registed_components()

subroutine monc_mod::display_registed_components ( )
private

Displays the registered components and their version numbers.

Definition at line 276 of file monc.F90.

276  type(map_type) :: registered_components
277  type(iterator_type) :: iterator
278  type(mapentry_type):: map_entry
279 
280  registered_components = get_all_registered_components()
281  call log_log(log_info, "Registered components: "//conv_to_string(c_size(registered_components)))
282  iterator=c_get_iterator(registered_components)
283  do while (c_has_next(iterator))
284  map_entry=c_next_mapentry(iterator)
285  call log_log(log_info, trim(map_entry%key)//" "//trim(conv_to_string(c_get_real(map_entry))))
286  end do
Here is the caller graph for this function:

◆ display_timestep_information()

subroutine monc_mod::display_timestep_information ( integer, intent(in)  timestep,
double precision, intent(in)  start_time 
)
private

Provides timestepping information about the current step and performance.

Parameters
timestepThe current timestep which has been completed
startTimeThe F95 CPU time that the current timestep was started at

Definition at line 228 of file monc.F90.

228  integer, intent(in) :: timestep
229  double precision, intent(in) :: start_time
230 
231  double precision :: end_time
232 
233  end_time=mpi_wtime()
234  call log_log(log_debug, "Timestep "//trim(conv_to_string(timestep))//" completed in "//&
235  trim(conv_to_string(int((end_time-start_time) * 1000)))//"ms")
Here is the caller graph for this function:

◆ fill_registry_with_components()

subroutine monc_mod::fill_registry_with_components ( type(hashmap_type), intent(inout)  options_database,
type(list_type), intent(inout)  component_descriptions 
)
private

Registers each supplied component description.

Definition at line 240 of file monc.F90.

240  type(hashmap_type), intent(inout) :: options_database
241  type(list_type), intent(inout) :: component_descriptions
242 
243  class(*), pointer :: raw_data
244  type(iterator_type) :: iterator
245 
246  iterator=c_get_iterator(component_descriptions)
247  do while (c_has_next(iterator))
248  raw_data=>c_next_generic(iterator)
249  select type(raw_data)
250  type is (component_descriptor_type)
251  call register_component(options_database, raw_data)
252  class default
253  call log_log(log_warn, "Can not register component due to corrupted data")
254  end select
255  end do
Here is the caller graph for this function:

◆ get_io_configuration()

subroutine monc_mod::get_io_configuration ( type(hashmap_type), intent(inout)  options_database,
character(len=long_string_length), intent(out)  ioserver_configuration_file,
integer, intent(out)  moncs_per_io_server 
)
private

Reads the IO server configuration and populates the required variables of the configuration file name and the placement period.

Parameters
options_databaseThe options database

Definition at line 378 of file monc.F90.

378  type(hashmap_type), intent(inout) :: options_database
379  character(len=LONG_STRING_LENGTH), intent(out) :: ioserver_configuration_file
380  integer, intent(out) :: moncs_per_io_server
381 
382  integer :: myrank, ierr
383 
384  ioserver_configuration_file=options_get_string(options_database, "ioserver_configuration_file")
385  moncs_per_io_server=options_get_integer(options_database, "moncs_per_io_server")
386 
387  if (moncs_per_io_server == -1 .or. ioserver_configuration_file == "") then
388  call mpi_comm_rank(mpi_comm_world, myrank, ierr)
389  if (myrank == 0) call log_log(log_error, "To run an IO server you must provide the placement period and configuration file")
390  call mpi_barrier(mpi_comm_world) ! All other processes barrier here to ensure 0 displays the message before quit
391  stop
392  end if
Here is the caller graph for this function:

◆ get_mpi_threading_mode()

integer function monc_mod::get_mpi_threading_mode ( )
private

Retrives the configured MPI threading mode, this is serialized by default but can be overridden via environment variable.

Returns
The MONC MPI threading mode

Definition at line 398 of file monc.F90.

398  character(len=STRING_LENGTH) :: thread_multiple_config_value
399  integer :: status
400 
401  call get_environment_variable("MONC_THREAD_MULTIPLE", thread_multiple_config_value, status=status)
402 
403  if (status == 0 .and. conv_is_logical(trim(thread_multiple_config_value))) then
404  if (conv_to_logical(trim(thread_multiple_config_value))) then
405  get_mpi_threading_mode=mpi_thread_multiple
406  else
407  get_mpi_threading_mode=mpi_thread_serialized
408  end if
409  else
410  get_mpi_threading_mode=mpi_thread_serialized
411  end if
Here is the caller graph for this function:

◆ get_number_io_processes()

integer function monc_mod::get_number_io_processes ( integer, intent(in)  total_ranks,
integer, intent(in)  moncs_per_io 
)
private

Based upon the total number of processes and the IO process id stride determines the number of processes that will be used for the IO server. The MONC processes is total processes - io processes.

Parameters
total_ranksTotal number of processes in use
io_strideThe absolute process id stride for IO processes
Returns
The number of processes used for running the IO server

Definition at line 365 of file monc.F90.

365  integer, intent(in) :: total_ranks, moncs_per_io
366 
367  integer :: io_stride
368 
369  io_stride=moncs_per_io
370  get_number_io_processes=total_ranks/io_stride
371  if (get_number_io_processes * io_stride .lt. total_ranks-1) get_number_io_processes=get_number_io_processes+1
Here is the caller graph for this function:

◆ is_present_and_true()

logical function monc_mod::is_present_and_true ( type(hashmap_type), intent(inout)  options_database,
character(len=*), intent(in)  key 
)
private

Determines whether an option is present in the database and true. This combines the key check and getting the value. Just calling to get the value directly will error if it does not exist, we don't nescesarily want for checking optional command line flags.

Parameters
options_databaseThe options database
keyThe key to test for

Definition at line 264 of file monc.F90.

264  type(hashmap_type), intent(inout) :: options_database
265  character(len=*), intent(in) :: key
266 
267  if (options_has_key(options_database, key)) then
268  is_present_and_true=options_get_logical(options_database, key)
269  return
270  end if
271  is_present_and_true=.false.
Here is the caller graph for this function:

◆ load_model_configuration()

subroutine monc_mod::load_model_configuration ( type(model_state_type), intent(inout)  state,
type(hashmap_type), intent(inout)  options_database 
)
private

Loads the configuration into the options database, either from a file or checkpoint.

Parameters
options_databaseThe options database

Definition at line 115 of file monc.F90.

115  type(model_state_type), intent(inout) :: state
116  type(hashmap_type), intent(inout) :: options_database
117 
118  call load_command_line_into_options_database(options_database)
119  if (options_has_key(options_database, "config")) then
120  state%continuation_run=.false.
121  call parse_configuration_file(options_database, options_get_string(options_database, "config"))
122  else if (options_has_key(options_database, "checkpoint")) then
123  state%continuation_run=.true.
124  call parse_configuration_checkpoint_netcdf(options_database, &
125  options_get_string(options_database, "checkpoint"), mpi_comm_world)
126  else
127  call log_master_log(log_error, "You must either provide a configuration file or checkpoint to restart from")
128  call mpi_barrier(mpi_comm_world) ! All other processes barrier here to ensure 0 displays the message before quit
129  stop
130  end if
131  ! Reload command line arguments to override any stuff in the configuration files
132  call load_command_line_into_options_database(options_database)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ monc_core_bootstrap()

subroutine, public monc_mod::monc_core_bootstrap ( type(list_type), intent(inout)  component_descriptions,
procedure(io_server_run_procedure io_server_run 
)

Main core entry point to bootstrap running the model.

Reads in command line arguments, sets up the model state and registers components. Then runs through and calls the execution of each model stage.

Parameters
componentDescriptionsDescriptions of existing components which should be registered
io_server_runOptional IO server entry procedure

Definition at line 52 of file monc.F90.

52  type(list_type), intent(inout) :: component_descriptions
53  procedure(io_server_run_procedure) :: io_server_run
54 
55  type(model_state_type) :: state
56  integer :: ierr, myrank, size, io_server_placement_period, provided_threading, selected_threading_mode
57  logical :: i_am_monc_process
58  character(len=LONG_STRING_LENGTH) :: io_server_config_file
59 
60  selected_threading_mode=get_mpi_threading_mode()
61  call mpi_init_thread(selected_threading_mode, provided_threading, ierr)
62  if (selected_threading_mode .gt. provided_threading) then
63  call log_master_log(log_error, "You have selected to thread at level '"//&
64  trim(mpi_threading_level_to_string(selected_threading_mode))//&
65  "' but the maximum level your MPI implementation can provide is '"//&
66  trim(mpi_threading_level_to_string(provided_threading))//"'")
67  end if
68  call load_model_configuration(state, state%options_database)
69 
70  state%io_server_enabled=determine_if_io_server_enabled(state%options_database)
71 
72  call init_data_defn()
73  ! Set up the logging with comm world PIDs initially for logging from the configuration parsing
74  call mpi_comm_rank(mpi_comm_world, myrank, ierr)
75  call initialise_logging(myrank)
76 
77  call log_set_logging_level(options_get_integer(state%options_database, "logging"))
78 
79  if (state%io_server_enabled) then
80  call mpi_comm_size(mpi_comm_world, size, ierr)
81  if (size==1) call log_log(log_error, &
82  "Run with 1 process, With IO server enabled then the minimum process size is 2 (1 for IO, 1 for MONC)")
83  call get_io_configuration(state%options_database, io_server_config_file, io_server_placement_period)
84  call split_communicator_into_monc_and_io(io_server_placement_period, state%parallel%monc_communicator, &
85  state%parallel%io_communicator, i_am_monc_process, state%parallel%corresponding_io_server_process)
86  if (.not. i_am_monc_process) then
87  call io_server_run(state%options_database, state%parallel%io_communicator, provided_threading, &
88  size, state%continuation_run, io_server_config_file)
89  else
90  call monc_run(component_descriptions, state)
91  end if
92  else
93  state%parallel%monc_communicator=mpi_comm_world
94  call monc_run(component_descriptions, state)
95  end if
96 
97  call mpi_finalize(ierr)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ monc_run()

subroutine monc_mod::monc_run ( type(list_type), intent(inout)  component_descriptions,
type(model_state_type), intent(inout)  state 
)
private

Called by MONC processes to run the MONC model.

Parameters
componentDescriptionsDescriptions of existing components which should be registered
stateThe current model state

Definition at line 139 of file monc.F90.

139  type(list_type), intent(inout) :: component_descriptions
140  type(model_state_type), intent(inout) :: state
141 
142  integer :: ierr, total_size
143  double precision :: end_time, timestepping_time, modeldump_time
144 
145  state%model_start_wtime=mpi_wtime()
146  call mpi_comm_rank(state%parallel%monc_communicator, state%parallel%my_rank, ierr)
147  call mpi_comm_size(state%parallel%monc_communicator, state%parallel%processes, ierr)
148  call mpi_comm_size(mpi_comm_world, total_size, ierr)
149 
150  call initialise_logging(state%parallel%my_rank)
151 
152  call log_master_log(log_info,"MONC running with "//trim(conv_to_string(state%parallel%processes))//" processes, "// &
153  trim(conv_to_string(total_size-state%parallel%processes))// " IO server(s)")
154 
155 #ifdef DEBUG_MODE
156  call log_master_log(log_warn,"MONC compiled with debug options, you probably want to recompile without for production runs")
157 #endif
158 
159  call init_registry(state%options_database) ! Initialise the registry
160 
161  call fill_registry_with_components(state%options_database, component_descriptions)
162  call initialise_science_constants(state)
163  call order_all_callbacks()
164  ! If the option has been provided then display the registered component information
165  if (is_present_and_true(state%options_database, "registered") .and. state%parallel%my_rank==0) &
166  call display_registed_components()
167  if (is_present_and_true(state%options_database, "showcallbacks") .and. state%parallel%my_rank==0) &
168  call display_callbacks_in_order_at_each_stage()
169 
170  if (.not. is_present_and_true(state%options_database, "norun")) then
171  ! Unless configured otherwise then run through the different stages of execution
172  call perform_model_steps(state, timestepping_time, modeldump_time)
173  end if
174  call mpi_barrier(state%parallel%monc_communicator, ierr)
175  end_time=mpi_wtime()
176  if (state%parallel%my_rank==0) then
177  call log_log(log_info, "Entire MONC run completed in "//trim(conv_to_string(int((end_time-state%model_start_wtime)*1000)))//&
178  "ms (timestepping="//trim(conv_to_string(int(timestepping_time * 1000)))//"ms, modeldump="//&
179  trim(conv_to_string(int(modeldump_time * 1000)))//"ms, misc="//trim(conv_to_string((&
180  int((end_time-state%model_start_wtime) * 1000)) - (int(timestepping_time * 1000) + int(modeldump_time * 1000))))//"ms)")
181  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ mpi_threading_level_to_string()

character(len=string_length) function monc_mod::mpi_threading_level_to_string ( integer, intent(in)  lvl)
private

Converts an MPI threading level to the string representation of it.

Parameters
lvlThe integer MPI level
Returns
The string representation of the level

Definition at line 418 of file monc.F90.

418  integer, intent(in) :: lvl
419 
420  if (lvl == mpi_thread_single) then
421  mpi_threading_level_to_string="single"
422  else if (lvl == mpi_thread_funneled) then
423  mpi_threading_level_to_string="funneled"
424  else if (lvl == mpi_thread_serialized) then
425  mpi_threading_level_to_string="serialized"
426  else if (lvl == mpi_thread_multiple) then
427  mpi_threading_level_to_string="multiple"
428  else
429  mpi_threading_level_to_string="unknown"
430  end if
Here is the caller graph for this function:

◆ perform_model_steps()

subroutine monc_mod::perform_model_steps ( type(model_state_type), intent(inout)  state,
double precision, intent(out)  timestepping_time,
double precision, intent(out)  modeldump_time 
)
private

Will run through the actual model stages and call the appropriate callbacks at each stage.

Parameters
stateThe model state The time spent in doing actual timestepping (computation) The time spent in doing the model dump

Definition at line 189 of file monc.F90.

189  type(model_state_type), intent(inout) :: state
190  double precision, intent(out) :: timestepping_time, modeldump_time
191 
192  integer :: logging_mod_level
193  double precision :: start_time, end_time, start_iteration_time
194 
195  timestepping_time=0.0_default_precision
196  modeldump_time=0.0_default_precision
197 
198  call init_timestepper()
199 
200  logging_mod_level = log_get_logging_level()
201  call execute_initialisation_callbacks(state)
202  state%continue_timestep=.true.
203  start_time=mpi_wtime()
204  do while (state%continue_timestep)
205  if (state%update_dtm) state%dtm=state%dtm_new
206  ! The start of a timestep
207  if (logging_mod_level .ge. log_debug) start_iteration_time=mpi_wtime()
208  call timestep(state) ! Call out to the timestepper to do the actual timestepping per component
209  if (logging_mod_level .ge. log_debug .and. state%parallel%my_rank==0) &
210  call display_timestep_information(state%timestep, start_iteration_time)
211  if (state%continue_timestep) then
212  state%timestep = state%timestep+1
213  state%time = state%time + state%dtm
214  end if
215  end do
216  end_time=mpi_wtime()
217  state%timestep_runtime=end_time-start_time
218  timestepping_time=timestepping_time+state%timestep_runtime
219  call execute_finalisation_callbacks(state)
220 
221  call finalise_timestepper()
Here is the call graph for this function:
Here is the caller graph for this function:

◆ split_communicator_into_monc_and_io()

subroutine monc_mod::split_communicator_into_monc_and_io ( integer, intent(in)  moncs_per_io,
integer, intent(out)  monc_communicator,
integer, intent(out)  io_communicator,
logical, intent(out)  am_i_monc_process,
integer, intent(out)  corresponding_io_server_process 
)
private

Splits the MPI_COMM_WORLD communicator into MONC and IO separate communicators. The size of each depends on the stride supplied. This will deal with the case where you only have 1 extra process, for instance 3 MONCs to an IO server with 5 processes. 0=IO server, 1-3 are MONCS but by rights 4 would be an IO server. However we dont want to waste a process as an IO server which is not serving anything, hence in this edge case it will be used as a MONC instead.

Parameters
io_strideThe absolute process id stride for IO processes
monc_communicatorThe communicator associated with MONC processes
io_communicatorThe communicator associated with IO processes

Definition at line 298 of file monc.F90.

298  integer, intent(in) :: moncs_per_io
299  integer, intent(out) :: monc_communicator, io_communicator, corresponding_io_server_process
300  logical, intent(out) :: am_i_monc_process
301 
302  integer, dimension(:), allocatable :: members_monc_group, members_io_group
303  integer :: total_ranks, monc_group, io_group, io_processes, monc_processes, i, io_index, &
304  monc_index, my_rank, ierr, global_group, io_stride
305 
306  call mpi_comm_size(mpi_comm_world, total_ranks, ierr)
307  call mpi_comm_rank(mpi_comm_world, my_rank, ierr)
308 
309  io_stride=moncs_per_io+1
310  io_processes=get_number_io_processes(total_ranks, io_stride)
311  monc_processes=total_ranks-io_processes
312  allocate(members_io_group(io_processes), members_monc_group(monc_processes))
313  io_index=1
314  monc_index=1
315  corresponding_io_server_process=-1
316  am_i_monc_process=.true.
317 
318  do i=0, total_ranks-1
319  if (mod(i, io_stride) == 0 .and. i .lt. total_ranks) then
320  if (io_index .le. io_processes) then
321  members_io_group(io_index)=i
322  else
323  members_monc_group(monc_index)=i
324  monc_index=monc_index+1
325  end if
326  io_index=io_index+1
327  if (my_rank == i) am_i_monc_process=.false.
328  if (my_rank .gt. i .and. my_rank .lt. i+io_stride) then
329  corresponding_io_server_process=i
330  end if
331  else
332  members_monc_group(monc_index)=i
333  monc_index=monc_index+1
334  end if
335  end do
336 
337  if (.not. am_i_monc_process .and. my_rank .eq. total_ranks-1) then
338  am_i_monc_process=.true.
339  corresponding_io_server_process=my_rank-io_stride
340  end if
341 
342  if (am_i_monc_process .and. corresponding_io_server_process .lt. 0) then
343  call log_log(log_error, "MONC can not deduce its IO server rank, try with a different number of IO to MONC setting")
344  end if
345 
346  if (log_get_logging_level() .ge. log_debug) then
347  call log_log(log_debug, "IO server assignment, rank="//conv_to_string(my_rank)//" IO server="//&
348  conv_to_string(corresponding_io_server_process)//" am I a MONC="//conv_to_string(am_i_monc_process))
349  end if
350 
351  call mpi_comm_group(mpi_comm_world, global_group, ierr)
352  call mpi_group_incl(global_group, monc_processes, members_monc_group, monc_group, ierr)
353  call mpi_group_incl(global_group, io_processes, members_io_group, io_group, ierr)
354  call mpi_comm_create(mpi_comm_world, monc_group, monc_communicator, ierr)
355  call mpi_comm_create(mpi_comm_world, io_group, io_communicator, ierr)
356  deallocate(members_io_group, members_monc_group)
Here is the call graph for this function:
Here is the caller graph for this function: