MONC
monc.F90
Go to the documentation of this file.
1 
2 module monc_mod
8  use state_mod, only : model_state_type
20  use mpi, only : mpi_comm_world, mpi_thread_multiple, mpi_thread_serialized, mpi_thread_single, mpi_thread_funneled, mpi_wtime
22  implicit none
23 
24 #ifndef TEST_MODE
25  private
26 #endif
27  abstract interface
28 
31  subroutine io_server_run_procedure(options_database, io_communicator_arg, provided_threading, &
32  total_global_processes, continuation_run, io_configuration_file)
33  import hashmap_type, long_string_length
34  type(hashmap_type), intent(inout) :: options_database
35  integer, intent(in) :: io_communicator_arg, provided_threading, total_global_processes
36  logical, intent(in) :: continuation_run
37  character(len=LONG_STRING_LENGTH), intent(in) :: io_configuration_file
38  end subroutine io_server_run_procedure
39  end interface
40 
41  public monc_core_bootstrap
42 
43 contains
44 
51  subroutine monc_core_bootstrap(component_descriptions, io_server_run)
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)
98  end subroutine monc_core_bootstrap
99 
103  logical function determine_if_io_server_enabled(options_database)
104  type(hashmap_type), intent(inout) :: options_database
105 
106  determine_if_io_server_enabled=options_get_logical(options_database, "enable_io_server")
108  determine_if_io_server_enabled=options_get_logical(options_database, "iobridge_enabled")
109  end if
110  end function determine_if_io_server_enabled
111 
114  subroutine load_model_configuration(state, options_database)
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)
133  end subroutine load_model_configuration
134 
138  subroutine monc_run(component_descriptions, state)
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) &
167  if (is_present_and_true(state%options_database, "showcallbacks") .and. state%parallel%my_rank==0) &
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
182  end subroutine monc_run
183 
188  subroutine perform_model_steps(state, timestepping_time, modeldump_time)
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()
222  end subroutine perform_model_steps
223 
227  subroutine display_timestep_information(timestep, start_time)
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")
236  end subroutine display_timestep_information
237 
239  subroutine fill_registry_with_components(options_database, component_descriptions)
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
256  end subroutine fill_registry_with_components
257 
263  logical function is_present_and_true(options_database, key)
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.
272  end function is_present_and_true
273 
275  subroutine display_registed_components()
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
287  end subroutine display_registed_components
288 
296  subroutine split_communicator_into_monc_and_io(moncs_per_io, monc_communicator, io_communicator, &
297  am_i_monc_process, corresponding_io_server_process)
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)
358 
364  integer function get_number_io_processes(total_ranks, moncs_per_io)
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
372  end function get_number_io_processes
373 
377  subroutine get_io_configuration(options_database, ioserver_configuration_file, moncs_per_io_server)
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
393  end subroutine get_io_configuration
394 
397  integer function get_mpi_threading_mode()
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
412  end function get_mpi_threading_mode
413 
417  character(len=STRING_LENGTH) function mpi_threading_level_to_string(lvl)
418  integer, intent(in) :: lvl
419 
420  if (lvl == mpi_thread_single) then
422  else if (lvl == mpi_thread_funneled) then
424  else if (lvl == mpi_thread_serialized) then
425  mpi_threading_level_to_string="serialized"
426  else if (lvl == mpi_thread_multiple) then
428  else
430  end if
431  end function mpi_threading_level_to_string
432 end module monc_mod
integer, parameter, public long_string_length
Length of longer strings.
Definition: datadefn.F90:11
type(component_descriptor_type) function, pointer, public get_component_info(name)
Retrieves detailed information about a specific component.
Definition: registry.F90:241
subroutine, public monc_core_bootstrap(component_descriptions, io_server_run)
Main core entry point to bootstrap running the model.
Definition: monc.F90:52
IO server entry procedure which may be passed to the core entry point (if IO server is enabled) ...
Definition: monc.F90:31
subroutine, public load_command_line_into_options_database(options_database)
Loads in the command line arguments and stores them in the options database.
subroutine, public display_callbacks_in_order_at_each_stage()
Displays the registered callbacks of each stage in the order that they will be called.
Definition: registry.F90:348
logical function determine_if_io_server_enabled(options_database)
Determines whether the IO server should be enabled or not.
Definition: monc.F90:104
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
character(len=string_length) function, public options_get_string(options_database, key, index)
Retrieves a string value from the database that matches the provided key.
subroutine, public finalise_timestepper()
Finalises the timestepper by cleaning up allocated memory.
Definition: timestepper.F90:45
Logging utility.
Definition: logging.F90:2
type(map_type) function, public get_all_registered_components()
Returns a brief summary of all registered components.
Definition: registry.F90:258
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
The ModelState which represents the current state of a run.
Definition: state.F90:39
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
integer, parameter, public log_debug
Log DEBUG, INFO, WARNING and ERROR messages.
Definition: logging.F90:14
A hashmap structure, the same as a map but uses hashing for greatly improved performance when storing...
Definition: collections.F90:94
subroutine monc_run(component_descriptions, state)
Called by MONC processes to run the MONC model.
Definition: monc.F90:139
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
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...
Definition: monc.F90:378
integer function get_mpi_threading_mode()
Retrives the configured MPI threading mode, this is serialized by default but can be overridden via e...
Definition: monc.F90:398
Converts data types to strings.
Definition: conversions.F90:36
subroutine, public initialise_science_constants(current_state)
Initialises the scientific constants to read in any values that are overridden in the configuration...
subroutine load_model_configuration(state, options_database)
Loads the configuration into the options database, either from a file or checkpoint.
Definition: monc.F90:115
Main core entry point to the rest of the model, this is called by the program main.
Definition: monc.F90:2
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
Converts data types to logical.
Definition: conversions.F90:69
Scientific constant values used throughout simulations. Each has a default value and this can be over...
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
subroutine, public order_all_callbacks()
Orders all callbacks in the prospective stages based upon the priorities of each descriptor.
Definition: registry.F90:305
Returns the number of elements in the collection.
subroutine display_registed_components()
Displays the registered components and their version numbers.
Definition: monc.F90:276
subroutine, public log_set_logging_level(level)
Sets the logging level, messages with less priority will be ignored.
Definition: logging.F90:114
Determines whether a data item can be represented as a logical or not.
Definition: conversions.F90:98
subroutine, public timestep(current_state)
Performs a timestep, which is comprised of executing each group of components in the order that they ...
Definition: timestepper.F90:30
Interfaces and types that MONC components must specify.
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 depe...
Definition: monc.F90:298
Collection data structures.
Definition: collections.F90:7
subroutine, public init_timestepper()
Initialises the timestepper by prefetching the groups in the order that they will be executed...
Definition: timestepper.F90:23
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 get...
Definition: monc.F90:264
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
Converts data types to real.
Definition: conversions.F90:58
integer, parameter, public string_length
Default length of strings.
Definition: datadefn.F90:10
subroutine, public initialise_logging(pid)
Initialises the logging. This is done to make it easier for master logging only, so that we don't hav...
Definition: logging.F90:37
List data structure which implements a doubly linked list. This list will preserve its order...
Definition: collections.F90:60
subroutine display_timestep_information(timestep, start_time)
Provides timestepping information about the current step and performance.
Definition: monc.F90:228
Performs the actual time stepping over groups of components. Each group can be the whole (which is on...
Definition: timestepper.F90:4
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
Manages the options database. Contains administration functions and deduce runtime options from the c...
integer, parameter, public log_info
Log INFO, WARNING and ERROR messages.
Definition: logging.F90:13
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 proces...
Definition: monc.F90:365
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
subroutine, public execute_initialisation_callbacks(current_state)
Calls all initialisation callbacks with the specified state.
Definition: registry.F90:275
subroutine, public parse_configuration_file(options_database, user_configuration_file)
Parses a specific configuration and adds the contents into the options database.
Parses a configuration file and loads the contents into the options database which can then be intero...
subroutine fill_registry_with_components(options_database, component_descriptions)
Registers each supplied component description.
Definition: monc.F90:240
subroutine, public register_component(options_database, descriptor)
Will register a component and install the nescesary callback hooks.
Definition: registry.F90:100
subroutine perform_model_steps(state, timestepping_time, modeldump_time)
Will run through the actual model stages and call the appropriate callbacks at each stage...
Definition: monc.F90:189
Gets a specific double precision real element out of the list, stack, queue or map with the correspon...
logical function, public options_has_key(options_database, key)
Determines whether a specific key is in the database.
The model state which represents the current state of a run.
Definition: state.F90:2
character(len=string_length) function mpi_threading_level_to_string(lvl)
Converts an MPI threading level to the string representation of it.
Definition: monc.F90:418
integer function, public log_get_logging_level()
Retrieves the current logging level.
Definition: logging.F90:122
subroutine, public init_registry(options_database)
Initialises the registry with the provided configuration file.
Definition: registry.F90:67
subroutine, public init_data_defn()
Will initialise the data definitions. This should be called as soon as MONC starts up...
Definition: datadefn.F90:27
subroutine, public execute_finalisation_callbacks(current_state)
Calls all finalisation callbacks with the specified state.
Definition: registry.F90:294
Loads in the configuration stored in a NetCDF checkpoint file for the model to start from...
subroutine, public parse_configuration_checkpoint_netcdf(options_database, checkpoint_name, communicator)
Will parse the NetCDF checkpoint file and loads the configuration into the options database...
MONC component registry.
Definition: registry.F90:5