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 perform_options_compatibility_checks (options_database)
 Performs options_database compatibility checks. 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 106 of file monc.F90.

107  type(hashmap_type), intent(inout) :: options_database
108 
109  determine_if_io_server_enabled=options_get_logical(options_database, "enable_io_server")
110  if (determine_if_io_server_enabled) then
111  determine_if_io_server_enabled=options_get_logical(options_database, "iobridge_enabled")
112  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 300 of file monc.F90.

301  type(map_type) :: registered_components
302  type(iterator_type) :: iterator
303  type(mapentry_type):: map_entry
304 
305  registered_components = get_all_registered_components()
306  call log_log(log_info, "Registered components: "//conv_to_string(c_size(registered_components)))
307  iterator=c_get_iterator(registered_components)
308  do while (c_has_next(iterator))
309  map_entry=c_next_mapentry(iterator)
310  call log_log(log_info, trim(map_entry%key)//" "//trim(conv_to_string(c_get_real(map_entry))))
311  end do
Here is the call graph for this function:
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 252 of file monc.F90.

253  integer, intent(in) :: timestep
254  double precision, intent(in) :: start_time
255 
256  double precision :: end_time
257 
258  end_time=mpi_wtime()
259  call log_log(log_debug, "Timestep "//trim(conv_to_string(timestep))//" completed in "//&
260  trim(conv_to_string(int((end_time-start_time) * 1000)))//"ms")
Here is the call graph for this function:
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 264 of file monc.F90.

265  type(hashmap_type), intent(inout) :: options_database
266  type(list_type), intent(inout) :: component_descriptions
267 
268  class(*), pointer :: raw_data
269  type(iterator_type) :: iterator
270 
271  iterator=c_get_iterator(component_descriptions)
272  do while (c_has_next(iterator))
273  raw_data=>c_next_generic(iterator)
274  select type(raw_data)
275  type is (component_descriptor_type)
276  call register_component(options_database, raw_data)
277  class default
278  call log_log(log_warn, "Can not register component due to corrupted data")
279  end select
280  end do
Here is the call graph for this function:
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 402 of file monc.F90.

403  type(hashmap_type), intent(inout) :: options_database
404  character(len=LONG_STRING_LENGTH), intent(out) :: ioserver_configuration_file
405  integer, intent(out) :: moncs_per_io_server
406 
407  integer :: myrank, ierr
408 
409  ioserver_configuration_file=options_get_string(options_database, "ioserver_configuration_file")
410  moncs_per_io_server=options_get_integer(options_database, "moncs_per_io_server")
411 
412  if (moncs_per_io_server == -1 .or. ioserver_configuration_file == "") then
413  call mpi_comm_rank(mpi_comm_world, myrank, ierr)
414  if (myrank == 0) call log_log(log_error, "To run an IO server you must provide the placement period and configuration file")
415  call mpi_barrier(mpi_comm_world) ! All other processes barrier here to ensure 0 displays the message before quit
416  stop
417  end if
Here is the call graph for this function:
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 422 of file monc.F90.

423  character(len=STRING_LENGTH) :: thread_multiple_config_value
424  integer :: status
425 
426  call get_environment_variable("MONC_THREAD_MULTIPLE", thread_multiple_config_value, status=status)
427 
428  if (status == 0 .and. conv_is_logical(trim(thread_multiple_config_value))) then
429  if (conv_to_logical(trim(thread_multiple_config_value))) then
430  get_mpi_threading_mode=mpi_thread_multiple
431  else
432  get_mpi_threading_mode=mpi_thread_serialized
433  end if
434  else
435  get_mpi_threading_mode=mpi_thread_serialized
436  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 389 of file monc.F90.

390  integer, intent(in) :: total_ranks, moncs_per_io
391 
392  integer :: io_stride
393 
394  io_stride=moncs_per_io
395  get_number_io_processes=total_ranks/io_stride
396  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 288 of file monc.F90.

289  type(hashmap_type), intent(inout) :: options_database
290  character(len=*), intent(in) :: key
291 
292  if (options_has_key(options_database, key)) then
293  is_present_and_true=options_get_logical(options_database, key)
294  return
295  end if
296  is_present_and_true=.false.
Here is the call graph for this function:
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 117 of file monc.F90.

118  type(model_state_type), intent(inout) :: state
119  type(hashmap_type), intent(inout) :: options_database
120 
121  call load_command_line_into_options_database(options_database)
122  if (options_has_key(options_database, "config")) then
123  state%continuation_run=.false.
124  call parse_configuration_file(options_database, options_get_string(options_database, "config"))
125  else if (options_has_key(options_database, "checkpoint")) then
126  state%continuation_run=.true.
127  call parse_configuration_checkpoint_netcdf(options_database, &
128  options_get_string(options_database, "checkpoint"), mpi_comm_world)
129  else
130  call log_master_log(log_error, "You must either provide a configuration file or checkpoint to restart from")
131  call mpi_barrier(mpi_comm_world) ! All other processes barrier here to ensure 0 displays the message before quit
132  stop
133  end if
134 
135  ! Reload command line arguments to override any stuff in the configuration files
136  call load_command_line_into_options_database(options_database)
137 
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 51 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  ! Check options_database for conflicts
80  !call perform_options_compatibility_checks(state%options_database)
81 
82  if (state%io_server_enabled) then
83  call mpi_comm_size(mpi_comm_world, size, ierr)
84  if (size==1) call log_log(log_error, &
85  "Run with 1 process, With IO server enabled then the minimum process size is 2 (1 for IO, 1 for MONC)")
86  call get_io_configuration(state%options_database, io_server_config_file, io_server_placement_period)
87  call split_communicator_into_monc_and_io(io_server_placement_period, state%parallel%monc_communicator, &
88  state%parallel%io_communicator, i_am_monc_process, state%parallel%corresponding_io_server_process)
89  if (.not. i_am_monc_process) then
90  call io_server_run(state%options_database, state%parallel%io_communicator, provided_threading, &
91  size, state%continuation_run, io_server_config_file)
92  else
93  call monc_run(component_descriptions, state)
94  end if
95  else
96  state%parallel%monc_communicator=mpi_comm_world
97  call monc_run(component_descriptions, state)
98  end if
99 
100  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 163 of file monc.F90.

164  type(list_type), intent(inout) :: component_descriptions
165  type(model_state_type), intent(inout) :: state
166 
167  integer :: ierr, total_size
168  double precision :: end_time, timestepping_time, modeldump_time
169 
170  state%model_start_wtime=mpi_wtime()
171  call mpi_comm_rank(state%parallel%monc_communicator, state%parallel%my_rank, ierr)
172  call mpi_comm_size(state%parallel%monc_communicator, state%parallel%processes, ierr)
173  call mpi_comm_size(mpi_comm_world, total_size, ierr)
174 
175  call initialise_logging(state%parallel%my_rank)
176 
177  call log_master_log(log_info,"MONC running with "//trim(conv_to_string(state%parallel%processes))//" processes, "// &
178  trim(conv_to_string(total_size-state%parallel%processes))// " IO server(s)")
179 
180 #ifdef DEBUG_MODE
181  call log_master_log(log_warn,"MONC compiled with debug options, you probably want to recompile without for production runs")
182 #endif
183 
184  call init_registry(state%options_database) ! Initialise the registry
185 
186  call fill_registry_with_components(state%options_database, component_descriptions)
187  call initialise_science_constants(state)
188  call order_all_callbacks()
189  ! If the option has been provided then display the registered component information
190  if (is_present_and_true(state%options_database, "registered") .and. state%parallel%my_rank==0) &
191  call display_registed_components()
192  if (is_present_and_true(state%options_database, "showcallbacks") .and. state%parallel%my_rank==0) &
193  call display_callbacks_in_order_at_each_stage()
194 
195  if (.not. is_present_and_true(state%options_database, "norun")) then
196  ! Unless configured otherwise then run through the different stages of execution
197  call perform_model_steps(state, timestepping_time, modeldump_time)
198  end if
199  call mpi_barrier(state%parallel%monc_communicator, ierr)
200  end_time=mpi_wtime()
201  if (state%parallel%my_rank==0) then
202  call log_log(log_info, "Entire MONC run completed in "//trim(conv_to_string(int((end_time-state%model_start_wtime)*1000)))//&
203  "ms (timestepping="//trim(conv_to_string(int(timestepping_time * 1000)))//"ms, modeldump="//&
204  trim(conv_to_string(int(modeldump_time * 1000)))//"ms, misc="//trim(conv_to_string((&
205  int((end_time-state%model_start_wtime) * 1000)) - (int(timestepping_time * 1000) + int(modeldump_time * 1000))))//"ms)")
206  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 442 of file monc.F90.

443  integer, intent(in) :: lvl
444 
445  if (lvl == mpi_thread_single) then
446  mpi_threading_level_to_string="single"
447  else if (lvl == mpi_thread_funneled) then
448  mpi_threading_level_to_string="funneled"
449  else if (lvl == mpi_thread_serialized) then
450  mpi_threading_level_to_string="serialized"
451  else if (lvl == mpi_thread_multiple) then
452  mpi_threading_level_to_string="multiple"
453  else
454  mpi_threading_level_to_string="unknown"
455  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 @timestepping_time The time spent in doing actual timestepping (computation) @modeldump_time The time spent in doing the model dump

Definition at line 213 of file monc.F90.

214  type(model_state_type), intent(inout) :: state
215  double precision, intent(out) :: timestepping_time, modeldump_time
216 
217  integer :: logging_mod_level
218  double precision :: start_time, end_time, start_iteration_time
219 
220  timestepping_time=0.0_default_precision
221  modeldump_time=0.0_default_precision
222 
223  call init_timestepper()
224 
225  logging_mod_level = log_get_logging_level()
226  call execute_initialisation_callbacks(state)
227  state%continue_timestep=.true.
228  start_time=mpi_wtime()
229  do while (state%continue_timestep)
230  if (state%update_dtm) state%dtm=state%dtm_new
231  ! The start of a timestep
232  if (logging_mod_level .ge. log_debug) start_iteration_time=mpi_wtime()
233  call timestep(state) ! Call out to the timestepper to do the actual timestepping per component
234  if (logging_mod_level .ge. log_debug .and. state%parallel%my_rank==0) &
235  call display_timestep_information(state%timestep, start_iteration_time)
236  if (state%continue_timestep) then
237  state%timestep = state%timestep+1
238  state%time = state%time + state%dtm
239  end if
240  end do
241  end_time=mpi_wtime()
242  state%timestep_runtime=end_time-start_time
243  timestepping_time=timestepping_time+state%timestep_runtime
244  call execute_finalisation_callbacks(state)
245 
246  call finalise_timestepper()
Here is the call graph for this function:
Here is the caller graph for this function:

◆ perform_options_compatibility_checks()

subroutine monc_mod::perform_options_compatibility_checks ( type(hashmap_type), intent(inout)  options_database)
private

Performs options_database compatibility checks.

Parameters
options_databaseThe options database

If conditional diagnostics are operating, both components should be enabled.

Definition at line 142 of file monc.F90.

143  type(hashmap_type), intent(inout) :: options_database
144 
146  if (is_present_and_true(options_database, "conditional_diagnostics_column_enabled") .NEQV. &
147  is_present_and_true(options_database, "conditional_diagnostics_whole_enabled") ) then
148 
149  if ( .not. is_present_and_true(options_database, "conditional_diagnostics_column_enabled")) &
150  call options_add(options_database, "conditional_diagnostics_column_enabled", .true.)
151  if ( .not. is_present_and_true(options_database, "conditional_diagnostics_whole_enabled")) &
152  call options_add(options_database, "conditional_diagnostics_whole_enabled", .true.)
153 
154  call log_master_log(log_info, "Only one conditional_diagnostics component is enabled, but both are required to function.")
155  call log_master_log(log_info, "We assume you would like conditional_diagnostics enabled so have enabled the other, too.")
156  end if
157 
Here is the call 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 321 of file monc.F90.

323  integer, intent(in) :: moncs_per_io
324  integer, intent(out) :: monc_communicator, io_communicator, corresponding_io_server_process
325  logical, intent(out) :: am_i_monc_process
326 
327  integer, dimension(:), allocatable :: members_monc_group, members_io_group
328  integer :: total_ranks, monc_group, io_group, io_processes, monc_processes, i, io_index, &
329  monc_index, my_rank, ierr, global_group, io_stride
330 
331  call mpi_comm_size(mpi_comm_world, total_ranks, ierr)
332  call mpi_comm_rank(mpi_comm_world, my_rank, ierr)
333 
334  io_stride=moncs_per_io+1
335  io_processes=get_number_io_processes(total_ranks, io_stride)
336  monc_processes=total_ranks-io_processes
337  allocate(members_io_group(io_processes), members_monc_group(monc_processes))
338  io_index=1
339  monc_index=1
340  corresponding_io_server_process=-1
341  am_i_monc_process=.true.
342 
343  do i=0, total_ranks-1
344  if (mod(i, io_stride) == 0 .and. i .lt. total_ranks) then
345  if (io_index .le. io_processes) then
346  members_io_group(io_index)=i
347  else
348  members_monc_group(monc_index)=i
349  monc_index=monc_index+1
350  end if
351  io_index=io_index+1
352  if (my_rank == i) am_i_monc_process=.false.
353  if (my_rank .gt. i .and. my_rank .lt. i+io_stride) then
354  corresponding_io_server_process=i
355  end if
356  else
357  members_monc_group(monc_index)=i
358  monc_index=monc_index+1
359  end if
360  end do
361 
362  if (.not. am_i_monc_process .and. my_rank .eq. total_ranks-1) then
363  am_i_monc_process=.true.
364  corresponding_io_server_process=my_rank-io_stride
365  end if
366 
367  if (am_i_monc_process .and. corresponding_io_server_process .lt. 0) then
368  call log_log(log_error, "MONC can not deduce its IO server rank, try with a different number of IO to MONC setting")
369  end if
370 
371  if (log_get_logging_level() .ge. log_debug) then
372  call log_log(log_debug, "IO server assignment, rank="//conv_to_string(my_rank)//" IO server="//&
373  conv_to_string(corresponding_io_server_process)//" am I a MONC="//conv_to_string(am_i_monc_process))
374  end if
375 
376  call mpi_comm_group(mpi_comm_world, global_group, ierr)
377  call mpi_group_incl(global_group, monc_processes, members_monc_group, monc_group, ierr)
378  call mpi_group_incl(global_group, io_processes, members_io_group, io_group, ierr)
379  call mpi_comm_create(mpi_comm_world, monc_group, monc_communicator, ierr)
380  call mpi_comm_create(mpi_comm_world, io_group, io_communicator, ierr)
381  deallocate(members_io_group, members_monc_group)
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
optionsdatabase_mod::options_get_integer
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
Definition: optionsdatabase.F90:217
logging_mod::log_info
integer, parameter, public log_info
Log INFO, WARNING and ERROR messages.
Definition: logging.F90:13
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_get_logging_level
integer function, public log_get_logging_level()
Retrieves the current logging level.
Definition: logging.F90:122
logging_mod::log_debug
integer, parameter, public log_debug
Log DEBUG, INFO, WARNING and ERROR messages.
Definition: logging.F90:14
optionsdatabase_mod::options_add
Generic add interface for adding different types of data to the databases.
Definition: optionsdatabase.F90:28
optionsdatabase_mod::options_get_string
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.
Definition: optionsdatabase.F90:280
optionsdatabase_mod::options_get_logical
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
Definition: optionsdatabase.F90:154
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47